]> www.average.org Git - pdns-pipe-nmc.git/blobdiff - PowerDns.hs
wip AXFR support
[pdns-pipe-nmc.git] / PowerDns.hs
index 7ed76e8a24bc046dcb42a96382d932f20c4210cb..61fdc21b307a1ef8c8af959c95ae58d0d64d3fb2 100644 (file)
@@ -1,25 +1,36 @@
-module PowerDns where
+module PowerDns ( RRType(..)
+                , PdnsRequest(..)
+                , pdnsParse
+                , pdnsReport
+                , pdnsOut
+                , pdnsOutXfr
+                ) where
+
+import NmcDom
 
 data RRType = RRTypeSRV   | RRTypeA   | RRTypeAAAA | RRTypeCNAME
             | RRTypeDNAME | RRTypeSOA | RRTypeRP   | RRTypeLOC
-            | RRTypeNS    | RRTypeDS
+            | RRTypeNS    | RRTypeDS  | RRTypeMX
             | RRTypeANY   | RRTypeError String 
         deriving (Show)
 
 data PdnsRequest = PdnsRequestQ
                    { qName              :: String
                    , qType              :: RRType
-                   , iD                 :: String
+                   , iD                 :: Int
                    , remoteIpAddress    :: String
                    , localIpAddress     :: Maybe String
                    , ednsSubnetAddress  :: Maybe String
                    }
-                 | PdnsRequestAXFR String
+                 | PdnsRequestAXFR Int
                  | PdnsRequestPing
         deriving (Show)
 
 pdnsParse ver s =
   let
+    getInt s = case reads s :: [(Int, String)] of
+      [(x, _)] -> x
+      _        -> -1
     getQt qt = case qt of
       "SRV"     -> RRTypeSRV   
       "A"       -> RRTypeA
@@ -31,6 +42,7 @@ pdnsParse ver s =
       "LOC"     -> RRTypeLOC
       "NS"      -> RRTypeNS    
       "DS"      -> RRTypeDS
+      "MX"      -> RRTypeMX
       "ANY"     -> RRTypeANY
       _         -> RRTypeError qt
     getLIp ver xs
@@ -46,27 +58,81 @@ pdnsParse ver s =
   in
     case words s of
       "PING":[]                 -> Right PdnsRequestPing
-      "AXFR":x:[]               -> Right (PdnsRequestAXFR x)
+      "AXFR":x:[]               -> Right (PdnsRequestAXFR (getInt x))
       "Q":qn:"IN":qt:id:rip:xs  -> Right (PdnsRequestQ
                                             { qName = qn
                                             , qType = getQt qt
-                                            , iD = id
+                                            , iD = getInt id
                                             , remoteIpAddress = rip
                                             , 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 -> Int -> 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" $ n2p rrtype
+    where
+      addLine (nm, ty, dt) accum =
+        "DATA\t" ++ v3ext ++ nm ++ "\tIN\t" ++ ty ++ "\t" ++ ttl ++
+            "\t" ++ (show id) ++ "\t" ++ dt ++ "\n" ++ accum
+      v3ext = case ver of
+        3 -> "0\t1\t"
+        _ -> ""
+      ttl = show 3600
+
+      n2p RRTypeANY   =
+        foldr (\r accum -> (n2p r) ++ accum) []
+          [RRTypeSRV, RRTypeA, RRTypeAAAA, RRTypeCNAME, RRTypeDNAME,
+           RRTypeRP, RRTypeLOC, RRTypeNS, RRTypeDS, RRTypeMX]
+      n2p RRTypeSRV   = mapto    "SRV"   $ domSrv dom
+      n2p RRTypeMX    = mapto    "MX"    $ domMx dom
+      n2p RRTypeA     = mapto    "A"     $ domIp dom
+      n2p RRTypeAAAA  = mapto    "AAAA"  $ domIp6 dom
+      n2p RRTypeCNAME = takejust "CNAME" $ domAlias dom
+      n2p RRTypeDNAME = takejust "DNAME" $ domTranslate dom
+      n2p RRTypeSOA   = -- FIXME generate only for top domain
+                        -- FIXME make realistic version field
+                        -- FIXME make realistic nameserver field
+        if dom == emptyNmcDom then []
+        else [(name, "SOA", "ns " ++ email ++ " 99999 10800 3600 604800 86400")]
+          where
+            email = case domEmail dom of
+              Nothing   -> "hostmaster." ++ name
+              Just addr -> dotmail addr
+      n2p RRTypeRP    = case domEmail dom of
+        Nothing   -> []
+        Just addr -> [(name, "RP", (dotmail addr) ++ " .")]
+      n2p RRTypeLOC   = takejust "LOC"  $ domLoc dom
+      n2p RRTypeNS    = mapto    "NS"   $ domNs dom
+      n2p RRTypeDS    = case domDs dom of
+        Nothing  -> []
+        Just dss -> map (\x -> (name, "DS", dsStr x)) dss
+          where
+            dsStr x = (show (dsKeyTag x)) ++ " "
+                   ++ (show (dsAlgo x)) ++ " "
+                   ++ (show (dsHashType x)) ++ " "
+                   ++ (dsHashValue x)
+
+      dotmail addr = 
+        let (aname, adom) = break (== '@') addr
+        in case adom of
+          "" -> aname
+          _  -> aname ++ "." ++ (tail adom)
+      
+      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)]
 
-{-
-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"
--}
+pdnsOutXfr :: Int -> Int -> String -> Either String NmcDom -> String
+pdnsOutXfr ver id name edom = case edom of
+  Left  err -> pdnsReport $ err ++ " in a query for " ++ name
+  Right dom -> pdnsReport $ "AXFR unsupported in a query for " ++ name