]> www.average.org Git - pdns-pipe-nmc.git/blobdiff - NmcTransform.hs
publish binary 0.9.0.1
[pdns-pipe-nmc.git] / NmcTransform.hs
index 29c00087904d0228dccf42992a3676063f57f89c..4a3e66714777d5cfebb81e80a67949e190050753 100644 (file)
@@ -2,11 +2,14 @@ module NmcTransform ( seedNmcDom
                     , descendNmcDom
                     ) where
 
                     , descendNmcDom
                     ) where
 
-import Prelude hiding (lookup)
+import Prelude hiding (lookup, null)
 import Data.ByteString.Lazy (ByteString)
 import Data.ByteString.Lazy (ByteString)
-import Data.Map (lookup, delete, size)
+import Data.Map.Lazy (Map, empty, lookup, delete, null, singleton
+                     , foldrWithKey, insert, insertWith)
 import Control.Monad (foldM)
 import Control.Monad (foldM)
+import Data.Maybe (fromMaybe)
 import Data.Aeson (decode)
 import Data.Aeson (decode)
+import Data.Default.Class (def)
 
 import NmcDom
 
 
 import NmcDom
 
@@ -23,41 +26,44 @@ queryNmcDom queryOp key = do
       Nothing  -> return $ Left $ "Unparseable value: " ++ (show str)
       Just dom -> return $ Right dom
 
       Nothing  -> return $ Left $ "Unparseable value: " ++ (show str)
       Just dom -> return $ Right dom
 
--- | Try to fetch "import" object and merge it into the base domain
---   Original "import" element is removed, but new imports from the
---   imported objects are processed recursively until there are none.
-mergeImport ::
+-- | Try to fetch "delegate" or "import" object and merge them into the
+--   base domain. Original "import" element is removed, but newly
+--   merged data may contain new "import" or "delegate", so the objects
+--   that are about to be merged are processed recursively until there
+--   are no more "import" and "deletage" attributes (or the depth gauge
+--   reaches zero).
+mergeIncl ::
   (String -> IO (Either String ByteString)) -- ^ query operation action
   -> Int                                    -- ^ recursion counter
   -> NmcDom                                 -- ^ base domain
   -> IO (Either String NmcDom)              -- ^ result with merged import
   (String -> IO (Either String ByteString)) -- ^ query operation action
   -> Int                                    -- ^ recursion counter
   -> NmcDom                                 -- ^ base domain
   -> IO (Either String NmcDom)              -- ^ result with merged import
-mergeImport queryOp depth base = do
+mergeIncl queryOp depth base = do
   let
     mbase = mergeSelf base
   let
     mbase = mergeSelf base
-    base' = mbase {domImport = Nothing}
+    base' = mbase {domDelegate = Nothing, domImport = Nothing}
   -- print base
   if depth <= 0 then return $ Left "Nesting of imports is too deep"
   -- print base
   if depth <= 0 then return $ Left "Nesting of imports is too deep"
-  else case domImport mbase of
-    Nothing  -> return $ Right base'
-    Just keys -> foldM mergeImport1 (Right base') keys
-      where
-        mergeImport1 (Left  err) _   = return $ Left err
-        mergeImport1 (Right acc) key = do
-          sub <- queryNmcDom queryOp key
-          case sub of
-            Left  err  -> return $ Left err
-            Right sub' -> mergeImport queryOp (depth - 1) $
-                                sub' `mergeNmcDom` acc
+    else case ((domDelegate mbase), (domImport mbase)) of
+      (Nothing,  Nothing  ) -> return $ Right base'
+      (Nothing,  Just keys) -> foldM mergeIncl1 (Right base') keys
+      (Just key, _        ) -> mergeIncl1 (Right def) key
+  where
+    mergeIncl1 (Left  err) _   = return $ Left err -- can never happen
+    mergeIncl1 (Right acc) key = do
+      sub <- queryNmcDom queryOp key
+      case sub of
+        Left  err  -> return $ Left err
+        Right sub' -> mergeIncl queryOp (depth - 1) $ sub' `merge` acc
 
 -- | If there is an element in the map with key "", merge the contents
 --   and remove this element. Do this recursively.
 mergeSelf :: NmcDom -> NmcDom
 mergeSelf base =
   let
 
 -- | If there is an element in the map with key "", merge the contents
 --   and remove this element. Do this recursively.
 mergeSelf :: NmcDom -> NmcDom
 mergeSelf base =
   let
-    map   = domMap base
-    base' = base {domMap = removeSelf map}
+    map   = domSubmap base
+    base' = base {domSubmap = removeSelf map}
     removeSelf Nothing    = Nothing
     removeSelf Nothing    = Nothing
-    removeSelf (Just map) = if size map' == 0 then Nothing else Just map'
+    removeSelf (Just map) = if null map' then Nothing else Just map'
       where map' = delete "" map
   in
     case map of
       where map' = delete "" map
   in
     case map of
@@ -65,39 +71,41 @@ mergeSelf base =
       Just map' ->
         case lookup "" map' of
           Nothing  -> base'
       Just map' ->
         case lookup "" map' of
           Nothing  -> base'
-          Just sub -> (mergeSelf sub) `mergeNmcDom` base'
+          Just sub -> (mergeSelf sub) `merge` base'
         -- recursion depth limited by the size of the record
 
         -- recursion depth limited by the size of the record
 
--- | SRV case - remove everyting and filter SRV records
-normalizeSrv :: String -> String -> NmcDom -> NmcDom
-normalizeSrv serv proto dom =
-  emptyNmcDom {domService = fmap (filter needed) (domService dom)}
-    where
-      needed r = srvName r == serv && srvProto r == proto
+-- | transfer some elements of `base` into `sub`, notably TLSA
+propagate :: NmcDom -> NmcDom -> NmcDom
+propagate base sub = sub `merge` (pickglobals base)
+  where
+    pickglobals dom = fromMaybe def (siftsubmap (siftsubmap taketlsa) dom)
+    siftsubmap f dom =
+      let
+        sdmap = fromMaybe empty (domSubmap dom)
+        sdmap' = foldrWithKey (\k x -> addifjust k (f x)) empty sdmap
+        addifjust k mdom acc = case mdom of
+          Nothing  -> acc
+          Just dom -> insert k dom acc -- dups are impossible here
+      in
+        if null sdmap' then Nothing else Just $ def { domSubmap = Just sdmap'}
+    taketlsa dom = case domTlsa dom of
+      Nothing   -> Nothing
+      Just tlsa -> case filter (\x -> tlsIncSubdoms x) tlsa of
+        []    -> Nothing
+        tlsa' -> Just $ def { domTlsa = Just tlsa' }
 
 -- | Presence of some elements require removal of some others
 normalizeDom :: NmcDom -> NmcDom
 
 -- | Presence of some elements require removal of some others
 normalizeDom :: NmcDom -> NmcDom
-normalizeDom dom = foldr id dom [ srvNormalizer
-                                , translateNormalizer
+normalizeDom dom = foldr id dom [ translateNormalizer
                                 , nsNormalizer
                                 ]
   where
     nsNormalizer dom = case domNs dom of
       Nothing  -> dom
                                 , nsNormalizer
                                 ]
   where
     nsNormalizer dom = case domNs dom of
       Nothing  -> dom
-      Just ns  -> emptyNmcDom { domNs = domNs dom, domEmail = domEmail dom }
+      Just ns  -> def { domNs = domNs dom, domEmail = domEmail dom }
     translateNormalizer dom = case domTranslate dom of
       Nothing  -> dom
     translateNormalizer dom = case domTranslate dom of
       Nothing  -> dom
-      Just tr  -> dom { domMap = Nothing }
-    srvNormalizer dom = dom { domService = Nothing, domMx = makemx }
-      where
-        makemx = case domService dom of
-          Nothing  -> Nothing
-          Just svl -> Just $ map makerec (filter needed svl)
-            where
-              needed sr = srvName sr == "smtp"
-                        && srvProto sr == "tcp"
-                        && srvPort sr == 25
-              makerec sr = (show (srvPrio sr)) ++ " " ++ (srvHost sr)
+      Just tr  -> dom { domSubmap = Nothing }
 
 -- | Merge imports and Selfs and follow the maps tree to get dom
 descendNmcDom ::
 
 -- | Merge imports and Selfs and follow the maps tree to get dom
 descendNmcDom ::
@@ -106,24 +114,22 @@ descendNmcDom ::
   -> NmcDom                                 -- ^ base domain
   -> IO (Either String NmcDom)              -- ^ fully processed result
 descendNmcDom queryOp subdom base = do
   -> NmcDom                                 -- ^ base domain
   -> IO (Either String NmcDom)              -- ^ fully processed result
 descendNmcDom queryOp subdom base = do
-  base' <- mergeImport queryOp 10 base
+  base' <- mergeIncl queryOp 10 base
   case subdom of
     []   -> return $ fmap normalizeDom base'
   case subdom of
     []   -> return $ fmap normalizeDom base'
-    -- A hack to handle SRV records: don't descend if ["_prot","_serv"]
-    [('_':p),('_':s)] -> return $ fmap (normalizeSrv s p) base'
     d:ds ->
       case base' of
         Left err     -> return base'
         Right base'' ->
     d:ds ->
       case base' of
         Left err     -> return base'
         Right base'' ->
-          case domMap base'' of
-            Nothing  -> return $ Right emptyNmcDom
+          case domSubmap base'' of
+            Nothing  -> return $ Right def
             Just map ->
               case lookup d map of
             Just map ->
               case lookup d map of
-                Nothing  -> return $ Right emptyNmcDom
-                Just sub -> descendNmcDom queryOp ds sub
+                Nothing  -> return $ Right def
+                Just sub -> descendNmcDom queryOp ds $ propagate base'' sub
 
 -- | Initial NmcDom populated with "import" only, suitable for "descend"
 seedNmcDom ::
   String        -- ^ domain key (without namespace prefix)
   -> NmcDom     -- ^ resulting seed domain
 
 -- | Initial NmcDom populated with "import" only, suitable for "descend"
 seedNmcDom ::
   String        -- ^ domain key (without namespace prefix)
   -> NmcDom     -- ^ resulting seed domain
-seedNmcDom dn = emptyNmcDom { domImport = Just (["d/" ++ dn])}
+seedNmcDom dn = def { domImport = Just (["d/" ++ dn])}