]> www.average.org Git - pdns-pipe-nmc.git/blobdiff - PowerDns.hs
cleanup pdns response generator
[pdns-pipe-nmc.git] / PowerDns.hs
index 7ed76e8a24bc046dcb42a96382d932f20c4210cb..796d97c5fa15a74445a05c600335098caa3f29c7 100644 (file)
@@ -1,8 +1,15 @@
-module PowerDns where
+module PowerDns ( RRType(..)
+                , PdnsRequest(..)
+                , pdnsParse
+                , pdnsReport
+                , pdnsOut
+                ) where
+
+import NmcDom
 
 data RRType = RRTypeSRV   | RRTypeA   | RRTypeAAAA | RRTypeCNAME
             | RRTypeDNAME | RRTypeSOA | RRTypeRP   | RRTypeLOC
-            | RRTypeNS    | RRTypeDS
+            | RRTypeNS    | RRTypeDS  | RRTypeMX
             | RRTypeANY   | RRTypeError String 
         deriving (Show)
 
@@ -31,6 +38,7 @@ pdnsParse ver s =
       "LOC"     -> RRTypeLOC
       "NS"      -> RRTypeNS    
       "DS"      -> RRTypeDS
+      "MX"      -> RRTypeMX
       "ANY"     -> RRTypeANY
       _         -> RRTypeError qt
     getLIp ver xs
@@ -55,18 +63,68 @@ pdnsParse ver s =
                                             , localIpAddress = getLIp ver xs
                                             , ednsSubnetAddress = getRIp ver xs
                                             })
-      _                         -> Left s
+      _                         -> Left $ "Unparseable PDNS Request: " ++ s
+
+pdnsReport :: String -> String
+pdnsReport err =
+  "LOG\tError: " ++ err ++ "\nFAIL\n"
+
+pdnsOut :: Int -> String -> String -> RRType -> Either String NmcDom -> String
+pdnsOut ver id name rrtype edom =
+  case edom of
+    Left  err -> pdnsReport $ err ++ " in a query for " ++ name
+    Right dom -> foldr addLine "END\n" $ nmc2pdns name rrtype dom
+      where
+        addLine (nm, ty, dt) accum =
+          "DATA\t" ++ v3ext ++ nm ++ "\tIN\t" ++ ty ++ "\t" ++ ttl ++
+              "\t" ++ id ++ "\t" ++ dt ++ "\n" ++ accum
+        v3ext = case ver of
+          3 -> "0\t1\t"
+          _ -> ""
+        ttl = show 3600
 
-{-
-pdnsOut :: String -> Either String PdnsRequest -> IO ()
-pdnsOut _   (Left e)   = putStrLn ("ERROR\tUnparseable request: " ++ e)
-pdnsOut uri (Right rq) = case rq of
-    PdnsRequestQ qn qt id lip rip eip -> do
-      dom <- queryNmc uri qn qt id
-      case dom of
-        Left  e      -> putStrLn ("ERROR\tNmc query error: " ++ e)
-        Right result -> print result
-    PdnsRequestAXFR xfrreq ->
-      putStrLn ("ERROR\t No support for AXFR " ++ xfrreq)
-    PdnsRequestPing -> putStrLn "OK"
--}
+nmc2pdns :: String -> RRType -> NmcDom -> [(String, String, String)]
+nmc2pdns name RRTypeANY   dom =
+  foldr (\r accum -> (nmc2pdns r) ++ accum) []
+    [RRTypeSRV, RRTypeA, RRTypeAAAA, RRTypeCNAME, RRTypeDNAME,
+     RRTypeSOA, RRTypeRP, RRTypeLOC, RRTypeNS, RRTypeDS, RRTypeMX]
+  where
+    nmc2pdns RRTypeSRV   = makesrv  "SRV"   $ domService dom
+    nmc2pdns RRTypeMX    = mapto    "MX"    $ domMx dom
+    nmc2pdns RRTypeA     = mapto    "A"     $ domIp dom
+    nmc2pdns RRTypeAAAA  = mapto    "AAAA"  $ domIp6 dom
+    nmc2pdns RRTypeCNAME = takejust "CNAME" $ domAlias dom
+    nmc2pdns RRTypeDNAME = takejust "DNAME" $ domTranslate dom
+    nmc2pdns RRTypeSOA   = -- FIXME generate only for top domain
+      if dom == emptyNmcDom then []
+      else
+        let
+          email = case domEmail dom of
+            Nothing   -> "hostmaster." ++ name
+            Just addr ->
+              let (aname, adom) = break (== '@') addr
+              in case adom of
+                "" -> aname
+                _  -> aname ++ "." ++ (tail adom)
+        in [(name, "SOA", email ++ " 99999999 10800 3600 604800 86400")]
+    nmc2pdns RRTypeRP    = [] --FIXME
+    nmc2pdns RRTypeLOC   = takejust "LOC"  $ domLoc dom
+    nmc2pdns RRTypeNS    = mapto    "NS"   $ domNs dom
+    nmc2pdns RRTypeDS    = [] --FIXME
+    
+    mapto rrstr maybel = case maybel of
+      Nothing  -> []
+      Just l   -> map (\x -> (name, rrstr, x)) l
+    
+    takejust rrstr maybestr = case maybestr of
+      Nothing  -> []
+      Just str -> [(name, rrstr, str)]
+    
+    makesrv rrstr mayberl = case mayberl of
+      Nothing  -> []
+      Just srl  -> map (\x -> (name, rrstr, fmtsrv x)) srl
+        where
+          fmtsrv rl = (show (srvPrio rl)) ++ " "
+                    ++ (show (srvWeight rl)) ++ " "
+                    ++ (show (srvPort rl)) ++ " "
+                    ++ (srvHost rl)