summaryrefslogtreecommitdiff
path: root/Presence
diff options
context:
space:
mode:
Diffstat (limited to 'Presence')
-rw-r--r--Presence/DNSCache.hs40
1 files changed, 35 insertions, 5 deletions
diff --git a/Presence/DNSCache.hs b/Presence/DNSCache.hs
index e3ccc386..4a936d57 100644
--- a/Presence/DNSCache.hs
+++ b/Presence/DNSCache.hs
@@ -1,3 +1,13 @@
1-- | Both 'getAddrInfo' and 'getHostByAddr' have hard-coded timeouts for
2-- waiting upon network queries that can be a little too long for some use
3-- cases. This module wraps both of them so that they block for at most one
4-- second. It caches late-arriving results so that they can be returned by
5-- repeated timed-out queries.
6--
7-- In order to achieve the shorter timeout, it is likely that the you will need
8-- to build with GHC's -threaded option. Otherwise, if the wrapped FFI calls
9-- to resolve the address will block Haskell threads. Note: I didn't verify
10-- this.
1{-# LANGUAGE TupleSections #-} 11{-# LANGUAGE TupleSections #-}
2{-# LANGUAGE RankNTypes #-} 12{-# LANGUAGE RankNTypes #-}
3module DNSCache 13module DNSCache
@@ -23,6 +33,7 @@ import qualified Data.Map as Map
23import qualified Network.BSD as BSD 33import qualified Network.BSD as BSD
24import qualified Data.Text as Text 34import qualified Data.Text as Text
25import Control.Monad 35import Control.Monad
36import Data.Function
26import Data.List 37import Data.List
27import Data.Ord 38import Data.Ord
28import Data.Maybe 39import Data.Maybe
@@ -46,9 +57,6 @@ newDNSCache = do
46 rcache <- newTVarIO Map.empty 57 rcache <- newTVarIO Map.empty
47 return DNSCache { fcache=fcache, rcache=rcache } 58 return DNSCache { fcache=fcache, rcache=rcache }
48 59
49equivBy :: forall a t. Eq a => (t -> a) -> t -> t -> Bool
50equivBy f a b = f a == f b
51
52updateCache :: Eq x => 60updateCache :: Eq x =>
53 Bool -> TimeStamp -> [x] -> Maybe [(TimeStamp,x)] -> Maybe [(TimeStamp,x)] 61 Bool -> TimeStamp -> [x] -> Maybe [(TimeStamp,x)] -> Maybe [(TimeStamp,x)]
54updateCache withScrub utc xs mys = do 62updateCache withScrub utc xs mys = do
@@ -68,12 +76,12 @@ dnsObserve dns withScrub utc obs = do
68 r <- readTVar $ rcache dns 76 r <- readTVar $ rcache dns
69 let obs' = map (\(n,a)->(n,a `withPort` 0)) obs 77 let obs' = map (\(n,a)->(n,a `withPort` 0)) obs
70 gs = do 78 gs = do
71 g <- groupBy (equivBy fst) $ sortBy (comparing fst) obs' 79 g <- groupBy ((==) `on` fst) $ sortBy (comparing fst) obs'
72 (n,_) <- take 1 g 80 (n,_) <- take 1 g
73 return (n,map snd g) 81 return (n,map snd g)
74 f' = foldl' updatef f gs 82 f' = foldl' updatef f gs
75 hs = do 83 hs = do
76 h <- groupBy (equivBy snd) $ sortBy (comparing snd) obs' 84 h <- groupBy ((==) `on` snd) $ sortBy (comparing snd) obs'
77 (_,a) <- take 1 h 85 (_,a) <- take 1 h
78 return (a,map fst h) 86 return (a,map fst h)
79 r' = foldl' updater r hs 87 r' = foldl' updater r hs
@@ -87,12 +95,21 @@ make6mapped4 :: SockAddr -> SockAddr
87make6mapped4 addr@(SockAddrInet6 {}) = addr 95make6mapped4 addr@(SockAddrInet6 {}) = addr
88make6mapped4 addr@(SockAddrInet port a) = SockAddrInet6 port 0 (0,0,0xFFFF,fromBE32 a) 0 96make6mapped4 addr@(SockAddrInet port a) = SockAddrInet6 port 0 (0,0,0xFFFF,fromBE32 a) 0
89 97
98-- 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
100-- updated when the resolve completes.
101--
102-- When the resolve operation does complete, any entries less than a minute old
103-- will be overwritten with the new results. Older entries are allowed to
104-- persist for reasons I don't understand as of this writing. (See 'updateCache')
90rawForwardResolve :: 105rawForwardResolve ::
91 DNSCache -> (Text -> IO ()) -> Int -> Text -> IO [SockAddr] 106 DNSCache -> (Text -> IO ()) -> Int -> Text -> IO [SockAddr]
92rawForwardResolve dns fail timeout addrtext = do 107rawForwardResolve dns fail timeout addrtext = do
93 r <- atomically newEmptyTMVar 108 r <- atomically newEmptyTMVar
94 mvar <- atomically newEmptyTMVar 109 mvar <- atomically newEmptyTMVar
95 rt <- forkOS $ resolver r mvar 110 rt <- forkOS $ resolver r mvar
111 -- TODO: System.Timeout.timeout might be more appropriate than this
112 -- hack involving throwTo (ErrorCall "Interrupteddelay").
96 tt <- forkIO $ timer (fail addrtext) timeout r rt 113 tt <- forkIO $ timer (fail addrtext) timeout r rt
97 atomically $ putTMVar mvar tt 114 atomically $ putTMVar mvar tt
98 atomically $ readTMVar r 115 atomically $ readTMVar r
@@ -155,6 +172,8 @@ rawReverseResolve dns fail timeout addr = do
155 atomically $ dnsObserve dns False utc $ map (,addr) xs 172 atomically $ dnsObserve dns False utc $ map (,addr) xs
156 atomically $ putTMVar r xs 173 atomically $ putTMVar r xs
157 174
175-- Returns expired (older than a minute) cached reverse-dns results
176-- and removes them from the cache.
158expiredReverse :: DNSCache -> SockAddr -> IO [Text] 177expiredReverse :: DNSCache -> SockAddr -> IO [Text]
159expiredReverse dns addr = do 178expiredReverse dns addr = do
160 utc <- getCurrentTime 179 utc <- getCurrentTime
@@ -163,6 +182,8 @@ expiredReverse dns addr = do
163 r <- readTVar $ rcache dns 182 r <- readTVar $ rcache dns
164 let ns = maybe [] id $ Map.lookup addr r 183 let ns = maybe [] id $ Map.lookup addr r
165 minute = 60 -- seconds 184 minute = 60 -- seconds
185 -- XXX: Is this right? flip diffUTCTime utc returns the age of the
186 -- cache entry?
166 (es0,ns') = partition ( (>=minute) . flip diffUTCTime utc . fst ) ns 187 (es0,ns') = partition ( (>=minute) . flip diffUTCTime utc . fst ) ns
167 es = map snd es0 188 es = map snd es0
168 modifyTVar' (rcache dns) $ Map.insert addr ns' 189 modifyTVar' (rcache dns) $ Map.insert addr ns'
@@ -190,6 +211,9 @@ cachedReverse dns addr = do
190 -} 211 -}
191 return $ map snd ns 212 return $ map snd ns
192 213
214-- Returns any dns query results for the given name that were observed less
215-- than a minute ago and updates the forward-cache to remove any results older
216-- than that.
193cachedForward :: DNSCache -> Text -> IO [SockAddr] 217cachedForward :: DNSCache -> Text -> IO [SockAddr]
194cachedForward dns n = do 218cachedForward dns n = do
195 utc <- getCurrentTime 219 utc <- getCurrentTime
@@ -201,6 +225,10 @@ cachedForward dns n = do
201 modifyTVar' (fcache dns) $ Map.insert n as' 225 modifyTVar' (fcache dns) $ Map.insert n as'
202 return $ map snd as' 226 return $ map snd as'
203 227
228-- Reverse-resolves an address to a domain name. Returns both the result of a
229-- new query and any freshly cached results. Cache entries older than a minute
230-- will not be returned, but will be refreshed in spawned threads so that they
231-- may be available for the next call.
204reverseResolve :: DNSCache -> SockAddr -> IO [Text] 232reverseResolve :: DNSCache -> SockAddr -> IO [Text]
205reverseResolve dns addr = do 233reverseResolve dns addr = do
206 expired <- expiredReverse dns addr 234 expired <- expiredReverse dns addr
@@ -211,6 +239,8 @@ reverseResolve dns addr = do
211 cs <- cachedReverse dns addr 239 cs <- cachedReverse dns addr
212 return $ xs ++ filter (not . flip elem xs) cs 240 return $ xs ++ filter (not . flip elem xs) cs
213 241
242-- Resolves a name, if there's no result within one second, then any cached
243-- results that are less than a minute old are returned.
214forwardResolve :: DNSCache -> Text -> IO [SockAddr] 244forwardResolve :: DNSCache -> Text -> IO [SockAddr]
215forwardResolve dns n = do 245forwardResolve dns n = do
216 as <- rawForwardResolve dns (const $ return ()) 1000000 n 246 as <- rawForwardResolve dns (const $ return ()) 1000000 n