summaryrefslogtreecommitdiff
path: root/Presence
diff options
context:
space:
mode:
authorjoe <joe@jerkface.net>2017-11-14 22:03:27 -0500
committerjoe <joe@jerkface.net>2017-11-14 22:03:27 -0500
commit69e0c86ff42f9f14c16791305828dcfdfd40baa8 (patch)
tree8c85edcdd4c6dfe56c9fe9badfeaa99084b1cc21 /Presence
parent4df9b9c240219fc01bf9ee8f15a6a2ee80d2233b (diff)
More sensible DNSCache behavior for non-threaded runtime.
Diffstat (limited to 'Presence')
-rw-r--r--Presence/DNSCache.hs22
1 files changed, 19 insertions, 3 deletions
diff --git a/Presence/DNSCache.hs b/Presence/DNSCache.hs
index 4a936d57..82e0cb56 100644
--- a/Presence/DNSCache.hs
+++ b/Presence/DNSCache.hs
@@ -10,6 +10,7 @@
10-- this. 10-- this.
11{-# LANGUAGE TupleSections #-} 11{-# LANGUAGE TupleSections #-}
12{-# LANGUAGE RankNTypes #-} 12{-# LANGUAGE RankNTypes #-}
13{-# LANGUAGE CPP #-}
13module DNSCache 14module DNSCache
14 ( DNSCache 15 ( DNSCache
15 , reverseResolve 16 , reverseResolve
@@ -20,7 +21,12 @@ module DNSCache
20 , withPort 21 , withPort
21 ) where 22 ) where
22 23
23import Control.Concurrent 24#ifdef THREAD_DEBUG
25import Control.Concurrent.Lifted.Instrument
26#else
27import Control.Concurrent.Lifted
28import GHC.Conc (labelThread)
29#endif
24import Control.Concurrent.STM 30import Control.Concurrent.STM
25import Data.Text ( Text ) 31import Data.Text ( Text )
26import Network.Socket ( SockAddr(..), AddrInfoFlag(..), defaultHints, getAddrInfo, AddrInfo(..) ) 32import Network.Socket ( SockAddr(..), AddrInfoFlag(..), defaultHints, getAddrInfo, AddrInfo(..) )
@@ -37,6 +43,8 @@ import Data.Function
37import Data.List 43import Data.List
38import Data.Ord 44import Data.Ord
39import Data.Maybe 45import Data.Maybe
46import System.IO
47import System.IO.Error
40 48
41import SockAddr () 49import SockAddr ()
42import ControlMaybe ( handleIO_ ) 50import ControlMaybe ( handleIO_ )
@@ -95,6 +103,12 @@ make6mapped4 :: SockAddr -> SockAddr
95make6mapped4 addr@(SockAddrInet6 {}) = addr 103make6mapped4 addr@(SockAddrInet6 {}) = addr
96make6mapped4 addr@(SockAddrInet port a) = SockAddrInet6 port 0 (0,0,0xFFFF,fromBE32 a) 0 104make6mapped4 addr@(SockAddrInet port a) = SockAddrInet6 port 0 (0,0,0xFFFF,fromBE32 a) 0
97 105
106tryForkOS :: IO () -> IO ThreadId
107tryForkOS action = catchIOError (forkOS action) $ \e -> do
108 hPutStrLn stderr $ "DNSCache: Link with -threaded to avoid excessively long time-out."
109 forkIO action
110
111
98-- Attempt to resolve the given domain name. Returns an empty list if the 112-- Attempt to resolve the given domain name. Returns an empty list if the
99-- resolve operation takes longer than the timeout, but the 'DNSCache' will be 113-- resolve operation takes longer than the timeout, but the 'DNSCache' will be
100-- updated when the resolve completes. 114-- updated when the resolve completes.
@@ -107,7 +121,9 @@ rawForwardResolve ::
107rawForwardResolve dns fail timeout addrtext = do 121rawForwardResolve dns fail timeout addrtext = do
108 r <- atomically newEmptyTMVar 122 r <- atomically newEmptyTMVar
109 mvar <- atomically newEmptyTMVar 123 mvar <- atomically newEmptyTMVar
110 rt <- forkOS $ resolver r mvar 124 rt <- tryForkOS $ do
125 myThreadId >>= flip labelThread ("resolve."++show addrtext)
126 resolver r mvar
111 -- TODO: System.Timeout.timeout might be more appropriate than this 127 -- TODO: System.Timeout.timeout might be more appropriate than this
112 -- hack involving throwTo (ErrorCall "Interrupteddelay"). 128 -- hack involving throwTo (ErrorCall "Interrupteddelay").
113 tt <- forkIO $ timer (fail addrtext) timeout r rt 129 tt <- forkIO $ timer (fail addrtext) timeout r rt
@@ -137,7 +153,7 @@ strip_brackets s =
137 153
138reportTimeout :: forall a. Show a => a -> IO () 154reportTimeout :: forall a. Show a => a -> IO ()
139reportTimeout addrtext = do 155reportTimeout addrtext = do
140 putStrLn $ "timeout resolving: "++show addrtext 156 hPutStrLn stderr $ "timeout resolving: "++show addrtext
141 -- killThread rt 157 -- killThread rt
142 158
143timer :: forall t a. IO () -> Int -> TMVar [a] -> t -> IO () 159timer :: forall t a. IO () -> Int -> TMVar [a] -> t -> IO ()