]> www.average.org Git - pdns-pipe-nmc.git/blobdiff - NmcTransform.hs
Revert "wip TLSA"
[pdns-pipe-nmc.git] / NmcTransform.hs
index c753f80165e9d71c7337cd3cd145af5fe772eca7..cf93db38f7793bb7725d51e2b44573cfce7a4197 100644 (file)
@@ -4,9 +4,12 @@ module NmcTransform ( seedNmcDom
 
 import Prelude hiding (lookup)
 import Data.ByteString.Lazy (ByteString)
-import Data.Map (empty, lookup, delete, size, singleton)
+import Data.Text.Lazy (splitOn, pack, unpack)
+import Data.Map.Lazy (empty, lookup, delete, size, singleton
+                     , foldrWithKey, insert, insertWith)
 import Control.Monad (foldM)
 import Data.Aeson (decode)
+import Data.Default.Class (def)
 
 import NmcDom
 
@@ -23,31 +26,34 @@ queryNmcDom queryOp key = do
       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
-mergeImport queryOp depth base = do
+mergeIncl queryOp depth base = do
   let
-    mbase = (expandSrv . mergeSelf) base
-    base' = mbase {domImport = Nothing}
+    mbase = (expandSrv . splitSubdoms . mergeSelf) base
+    base' = mbase {domDelegate = Nothing, domImport = Nothing}
   -- 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' `mergeNmcDom` acc
 
 -- | If there is an element in the map with key "", merge the contents
 --   and remove this element. Do this recursively.
@@ -80,13 +86,13 @@ expandSrv base =
         where
           addSrvMx sr acc = sub1 `mergeNmcDom` acc
             where
-              sub1 = emptyNmcDom { domMap = Just (singleton proto sub2)
+              sub1 = def { domMap = Just (singleton proto sub2)
                                  , domMx = maybemx}
-              sub2 = emptyNmcDom { domMap = Just (singleton srvid sub3) }
-              sub3 = emptyNmcDom { domSrv = Just [srvStr] }
+              sub2 = def { domMap = Just (singleton srvid sub3) }
+              sub3 = def { domSrv = Just [srvStr] }
               proto = "_" ++ (srvProto sr)
               srvid = "_" ++ (srvName sr)
-              srvStr =  (show (srvPrio sr)) ++ " "
+              srvStr =  (show (srvPrio sr)) ++ "\t"
                      ++ (show (srvWeight sr)) ++ " "
                      ++ (show (srvPort sr)) ++ " "
                      ++ (srvHost sr)
@@ -94,8 +100,34 @@ expandSrv base =
                 if srvName sr == "smtp"
                    && srvProto sr == "tcp"
                    && srvPort sr == 25
-                then Just [(show (srvPrio sr)) ++ " " ++ (srvHost sr)]
+                then Just [(show (srvPrio sr)) ++ "\t" ++ (srvHost sr)]
                 else Nothing
+
+-- | Convert map elements of the form "subN...sub2.sub1.dom.bit"
+--   into nested map and merge it
+splitSubdoms :: NmcDom -> NmcDom
+splitSubdoms base =
+  let
+    base' = base { domMap = Nothing }
+  in
+    case domMap base of
+      Nothing -> base'
+      Just sdmap -> (def { domMap = Just sdmap' }) `mergeNmcDom` base'
+        where
+          sdmap' = foldrWithKey stow empty sdmap
+          stow fqdn sdom acc = insertWith mergeNmcDom fqdn' sdom' acc
+            where
+              (fqdn', sdom') =
+                nest (filter (/= "") (splitOnDots fqdn), sdom)
+              splitOnDots s = map unpack (splitOn (pack ".") (pack s))
+              nest ([], v)   = (fqdn, v) -- can split result be empty?
+              nest ([k], v)  = (k, v)
+              nest (k:ks, v) =
+                nest (ks, def { domMap = Just (singleton k v) })
+
+-- | transfer some elements of `base` into `sub`, notably TLSA
+propagate :: NmcDom -> NmcDom -> NmcDom
+propagate base sub = sub -- FIXME implement it
  
 -- | Presence of some elements require removal of some others
 normalizeDom :: NmcDom -> NmcDom
@@ -105,7 +137,7 @@ normalizeDom dom = foldr id dom [ translateNormalizer
   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
       Just tr  -> dom { domMap = Nothing }
@@ -117,7 +149,7 @@ descendNmcDom ::
   -> 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'
     d:ds ->
@@ -125,14 +157,14 @@ descendNmcDom queryOp subdom base = do
         Left err     -> return base'
         Right base'' ->
           case domMap base'' of
-            Nothing  -> return $ Right emptyNmcDom
+            Nothing  -> return $ Right def
             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
-seedNmcDom dn = emptyNmcDom { domImport = Just (["d/" ++ dn])}
+seedNmcDom dn = def { domImport = Just (["d/" ++ dn])}