summaryrefslogtreecommitdiff
path: root/Hosts.hs
blob: 669fd0933f3678d9f0b7af86f5ecc232efa7d826 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE OverloadedStrings   #-}
module Hosts
    ( Hosts
    , assignName
    , assignNewName
    , inet_pton
    , inet_ntop 
    , empty
    , hasName
    , hasAddr
    , encode
    , decode
    , diff
    ) where

import Data.Maybe
import Data.Monoid ( (<>) )
import Data.List (foldl')
import Data.Ord
import Data.Char (isSpace)
import qualified Data.Map as Map
import           Data.Map (Map)
import qualified Data.ByteString.Lazy.Char8 as L
import System.IO.Unsafe (unsafePerformIO)
import Control.Exception as Exception (IOException(..),catch)
import Control.Applicative ( (<$>), (<*>) )
import Control.Monad (mplus)
import Network.Socket

handleIO_ h a = Exception.catch a (\(_ :: IOException) -> h)

inet_pton :: String -> Maybe SockAddr
inet_pton p = n
 where
    n = unsafePerformIO $ do
            handleIO_ (return Nothing) $ do
            info <- getAddrInfo safe_hints (Just p) Nothing
            return $ fmap addrAddress $ listToMaybe info
    safe_hints = Just $ defaultHints { addrFlags=[AI_NUMERICHOST] }

inet_ntop :: SockAddr -> String
inet_ntop n = p
 where
    p = case show n of
            '[':xs ->  fst $ break (==']') xs
            xs     ->  fst $ break (==':') xs


data Hosts = Hosts
    { lineCount :: Int
    , numline :: Map Int L.ByteString
    , namenum :: Map L.ByteString [Int]
    , addrnum :: Map SockAddr Int
    }

instance Show Hosts where
    show = L.unpack . encode

encode = L.unlines . map snd . Map.assocs . numline

parseLine s = (addr,names)
 where
    (addr0,names) = splitAt 1 $ L.words (uncom s)
    addr = do
        a <- fmap L.unpack $ listToMaybe addr0
        n <- inet_pton a
        return $ n -- inet_ntop n
        
    uncom s = fst $ L.break (=='#') s

empty = Hosts { lineCount = 0
              , numline = Map.empty
              , addrnum = Map.empty
              , namenum = Map.empty
              } 

parseHosts fname = do
    input <- L.readFile fname
    decode input

decode input = do
    let ls = L.lines input
        ans = map (\l->(parseLine l,l)) ls
        hosts = foldl' upd empty ans
        upd hosts ((addr,names),line) = hosts
            { lineCount = count
            , numline = Map.insert count line (numline hosts)
            , addrnum = maybeInsert (addrnum hosts) addr
            , namenum = foldl' (\m x->Map.alter (cons count) x m)
                               (namenum hosts)
                               names
            }
          where count = lineCount hosts + 1
                cons v xs = Just $ maybe [v] (v:) xs
                maybeInsert m x = maybe m
                                        (\x->Map.insert x count m)
                                        x
    return hosts


hasName :: L.ByteString -> Hosts -> Bool
hasName name hosts = Map.member name $ namenum hosts

hasAddr :: SockAddr -> Hosts -> Bool
hasAddr addr hosts = Map.member addr $ addrnum hosts

scrubName f line = line'
 where
    (x,ign) = L.break (=='#') line
    ws  = L.groupBy ( (==EQ) `oo` comparing isSpace) x
                        where oo = (.) . (.)
    (a,ws') = splitAt 2 ws
    ws'' = f ws'
    line' = if null ws'' then "# " <> line
                         else L.concat (a ++ ws'') <> ign

assignName addr name hosts = assignName0 False addr name hosts

assignName0 iscannon addr name hosts = hosts'
 where
    ns = Map.lookup name (namenum hosts) 
    a = Map.lookup addr (addrnum hosts)
    hosts' = do
        if (== Just True) $ elem <$> a <*> ns
         then hosts -- address already has name, nothing to do
         else 
            let hosts0 = -- remove name if it's present
                         maybe hosts (removeName hosts) ns
                hosts1 = -- insert name, or add new line
                         maybe (newLine hosts0) (appendName hosts0) a
            in hosts1
    removeName hosts nums = hosts 
        { namenum = Map.delete name (namenum hosts)
        , numline = foldl' scrub (numline hosts) nums
        }
        where scrub m num = Map.adjust (scrubName $ filter (/=name)) num m
    appendName hosts num = hosts
        { numline = Map.adjust (scrubName f) num (numline hosts)
        , namenum = Map.alter (cons num) name (namenum hosts)
        }
        where f ws = if iscannon 
                      then [name, " "] ++ ws
                      else let rs       = reverse ws
                               (sp,rs') = span (L.any isSpace) rs
                           in reverse $ sp ++ [name," "] ++ rs'
              cons v xs = Just $ maybe [v] (v:) xs
    newLine hosts = hosts
        { lineCount = cnt
        , numline = Map.insert cnt line $ numline hosts
        , addrnum = Map.insert addr cnt $ addrnum hosts
        , namenum = Map.alter (cons cnt) name $ namenum hosts
        }
        where cnt = lineCount hosts + 1
              line = L.pack (inet_ntop addr) <> " " <> name
              cons v xs = Just $ maybe [v] (v:) xs

assignNewName addr name hosts = 
    if hasName name hosts then hosts
                          else assignName0 True addr name hosts

-- Returns a list of bytestrings intended to show the
-- differences between the two host databases.  It is
-- assumed that no lines are deleted, only altered or
-- appended.
diff :: Hosts -> Hosts -> [L.ByteString]
diff as bs = cs
 where
    [as',bs'] = map (L.lines . Hosts.encode) [as,bs]
    ext xs = map Just xs ++ repeat Nothing
    ds = takeWhile (isJust . uncurry mplus) $ zip (ext as') (ext bs')
    es = filter (uncurry (/=)) ds
    cs = do
        (a,b) <- es
        [a,b] <- return $ map maybeToList [a,b]
        fmap ("- " <>) a ++ fmap ("+ " <>) b