]> www.average.org Git - pdns-pipe-nmc.git/blob - NmcTransform.hs
cc89abeda14e60ffab546c029d2636a9f4973f96
[pdns-pipe-nmc.git] / NmcTransform.hs
1 module NmcTransform ( seedNmcDom
2                     , descendNmcDom
3                     ) where
4
5 import Prelude hiding (lookup)
6 import Data.ByteString.Lazy (ByteString)
7 import Data.Text.Lazy (splitOn, pack, unpack)
8 import Data.Map.Lazy (empty, lookup, delete, size, singleton
9                      , foldrWithKey, insert, insertWith)
10 import Control.Monad (foldM)
11 import Data.Aeson (decode)
12 import Data.Default.Class (def)
13
14 import NmcDom
15
16 -- | Perform query and return error string or parsed domain object
17 queryNmcDom ::
18   (String -> IO (Either String ByteString)) -- ^ query operation action
19   -> String                                 -- ^ key
20   -> IO (Either String NmcDom)              -- ^ error string or domain
21 queryNmcDom queryOp key = do
22   l <- queryOp key
23   case l of
24     Left estr -> return $ Left estr
25     Right str -> case decode str :: Maybe NmcDom of
26       Nothing  -> return $ Left $ "Unparseable value: " ++ (show str)
27       Just dom -> return $ Right dom
28
29 -- | Try to fetch "delegate" or "import" object and merge them into the
30 --   base domain. Original "import" element is removed, but newly
31 --   merged data may contain new "import" or "delegate", so the objects
32 --   that are about to be merged are processed recursively until there
33 --   are no more "import" and "deletage" attributes (or the depth gauge
34 --   reaches zero).
35 mergeIncl ::
36   (String -> IO (Either String ByteString)) -- ^ query operation action
37   -> Int                                    -- ^ recursion counter
38   -> NmcDom                                 -- ^ base domain
39   -> IO (Either String NmcDom)              -- ^ result with merged import
40 mergeIncl queryOp depth base = do
41   let
42     mbase = (expandSrv . splitSubdoms . mergeSelf) base
43     base' = mbase {domDelegate = Nothing, domImport = Nothing}
44   -- print base
45   if depth <= 0 then return $ Left "Nesting of imports is too deep"
46     else case ((domDelegate mbase), (domImport mbase)) of
47       (Nothing,  Nothing  ) -> return $ Right base'
48       (Nothing,  Just keys) -> foldM mergeIncl1 (Right base') keys
49       (Just key, _        ) -> mergeIncl1 (Right def) key
50   where
51     mergeIncl1 (Left  err) _   = return $ Left err -- can never happen
52     mergeIncl1 (Right acc) key = do
53       sub <- queryNmcDom queryOp key
54       case sub of
55         Left  err  -> return $ Left err
56         Right sub' -> mergeIncl queryOp (depth - 1) $ sub' `mergeNmcDom` acc
57
58 -- | If there is an element in the map with key "", merge the contents
59 --   and remove this element. Do this recursively.
60 mergeSelf :: NmcDom -> NmcDom
61 mergeSelf base =
62   let
63     map   = domMap base
64     base' = base {domMap = removeSelf map}
65     removeSelf Nothing    = Nothing
66     removeSelf (Just map) = if size map' == 0 then Nothing else Just map'
67       where map' = delete "" map
68   in
69     case map of
70       Nothing   -> base'
71       Just map' ->
72         case lookup "" map' of
73           Nothing  -> base'
74           Just sub -> (mergeSelf sub) `mergeNmcDom` base'
75         -- recursion depth limited by the size of the record
76
77 -- | replace Service with Srv down in the Map
78 expandSrv :: NmcDom -> NmcDom
79 expandSrv base =
80   let
81     base' = base { domService = Nothing }
82   in
83     case domService base of
84       Nothing -> base'
85       Just sl -> foldr addSrvMx base' sl
86         where
87           addSrvMx sr acc = sub1 `mergeNmcDom` acc
88             where
89               sub1 = def { domMap = Just (singleton proto sub2)
90                                  , domMx = maybemx}
91               sub2 = def { domMap = Just (singleton srvid sub3) }
92               sub3 = def { domSrv = Just [srvStr] }
93               proto = "_" ++ (srvProto sr)
94               srvid = "_" ++ (srvName sr)
95               srvStr =  (show (srvPrio sr)) ++ "\t"
96                      ++ (show (srvWeight sr)) ++ " "
97                      ++ (show (srvPort sr)) ++ " "
98                      ++ (srvHost sr)
99               maybemx =
100                 if srvName sr == "smtp"
101                    && srvProto sr == "tcp"
102                    && srvPort sr == 25
103                 then Just [(show (srvPrio sr)) ++ "\t" ++ (srvHost sr)]
104                 else Nothing
105 {-
106 -- | replace Tls with Tlsa down in the Map
107 --   This function is almost, but not quite, entirely unlike expandSrv.
108 expandTls :: NmcDom -> NmcDom
109 expandTls base =
110   let
111     base' = base { domTls = Nothing }
112   in
113     case domTls base of
114       Nothing -> base'
115       Just sl -> foldr addTlsa base' sl
116         where
117           addTlsa sr acc = sub1 `mergeNmcDom` acc
118             where
119               sub1 = def { domMap = Just (singleton proto sub2) }
120               sub2 = def { domMap = Just (singleton port sub3) }
121               sub3 = def { domTlsa = Just [tlsStr] }
122               proto = "_" ++ (tlsProto sr)
123               port = "_" ++ (tlsName sr)
124               tlsStr =  (show (tlsPrio sr)) ++ "\t"
125                      ++ (show (tlsWeight sr)) ++ " "
126                      ++ (show (tlsPort sr)) ++ " "
127                      ++ (tlsHost sr)
128 -}
129
130 -- | Convert map elements of the form "subN...sub2.sub1.dom.bit"
131 --   into nested map and merge it
132 splitSubdoms :: NmcDom -> NmcDom
133 splitSubdoms base =
134   let
135     base' = base { domMap = Nothing }
136   in
137     case domMap base of
138       Nothing -> base'
139       Just sdmap -> (def { domMap = Just sdmap' }) `mergeNmcDom` base'
140         where
141           sdmap' = foldrWithKey stow empty sdmap
142           stow fqdn sdom acc = insertWith mergeNmcDom fqdn' sdom' acc
143             where
144               (fqdn', sdom') =
145                 nest (filter (/= "") (splitOnDots fqdn), sdom)
146               splitOnDots s = map unpack (splitOn (pack ".") (pack s))
147               nest ([], v)   = (fqdn, v) -- can split result be empty?
148               nest ([k], v)  = (k, v)
149               nest (k:ks, v) =
150                 nest (ks, def { domMap = Just (singleton k v) })
151  
152 -- | Presence of some elements require removal of some others
153 normalizeDom :: NmcDom -> NmcDom
154 normalizeDom dom = foldr id dom [ translateNormalizer
155                                 , nsNormalizer
156                                 ]
157   where
158     nsNormalizer dom = case domNs dom of
159       Nothing  -> dom
160       Just ns  -> def { domNs = domNs dom, domEmail = domEmail dom }
161     translateNormalizer dom = case domTranslate dom of
162       Nothing  -> dom
163       Just tr  -> dom { domMap = Nothing }
164
165 -- | Merge imports and Selfs and follow the maps tree to get dom
166 descendNmcDom ::
167   (String -> IO (Either String ByteString)) -- ^ query operation action
168   -> [String]                               -- ^ subdomain chain
169   -> NmcDom                                 -- ^ base domain
170   -> IO (Either String NmcDom)              -- ^ fully processed result
171 descendNmcDom queryOp subdom base = do
172   base' <- mergeIncl queryOp 10 base
173   case subdom of
174     []   -> return $ fmap normalizeDom base'
175     d:ds ->
176       case base' of
177         Left err     -> return base'
178         Right base'' ->
179           case domMap base'' of
180             Nothing  -> return $ Right def
181             Just map ->
182               case lookup d map of
183                 Nothing  -> return $ Right def
184                 Just sub -> descendNmcDom queryOp ds sub
185
186 -- | Initial NmcDom populated with "import" only, suitable for "descend"
187 seedNmcDom ::
188   String        -- ^ domain key (without namespace prefix)
189   -> NmcDom     -- ^ resulting seed domain
190 seedNmcDom dn = def { domImport = Just (["d/" ++ dn])}