]> www.average.org Git - pdns-pipe-nmc.git/blobdiff - pdns-pipe-nmc.hs
wip merging imports
[pdns-pipe-nmc.git] / pdns-pipe-nmc.hs
index 079e3b9cd9ab4014cb85016cc4d2892f78a94b3f..d9ced8f3318629029611f1f5aff08e998dfebb73 100644 (file)
 
 module Main where
 
 
 module Main where
 
---import Control.Applicative
+import System.IO
 import Control.Monad
 import Control.Monad
-import Data.ByteString.Char8 (pack, unpack)
-import Data.ByteString.Lazy hiding (pack, unpack, putStrLn)
-import Data.ConfigFile
-import Data.Either.Utils
+import qualified Data.ByteString.Char8 as C (pack, unpack)
+import qualified Data.ByteString.Lazy.Char8 as L (pack, unpack)
+import Data.ByteString.Lazy as BS hiding (reverse, putStr, putStrLn)
 import Data.List.Split
 import Data.Aeson (encode, decode, Value(..))
 import Network.HTTP.Types
 import Data.Conduit
 import Network.HTTP.Conduit
 import Data.List.Split
 import Data.Aeson (encode, decode, Value(..))
 import Network.HTTP.Types
 import Data.Conduit
 import Network.HTTP.Conduit
-import Data.JsonRpcClient
-import NmcJson
 
 
-confFile = "/etc/namecoin.conf"
+import JsonRpcClient
+import Config
+import PowerDns
+import NmcRpc
+import NmcDom
 
 
--- Config file handling
-
-data Config = Config { rpcuser       :: String
-                     , rpcpassword   :: String
-                     , rpchost       :: String
-                     , rpcport       :: Int
-                     } deriving (Show)
-
-readConfig :: String -> IO Config
-readConfig f = do
-  cp <- return . forceEither =<< readfile emptyCP f
-  return (Config { rpcuser       = getSetting cp "rpcuser"     ""
-                 , rpcpassword   = getSetting cp "rpcpassword" ""
-                 , rpchost       = getSetting cp "rpchost"     "localhost"
-                 , rpcport       = getSetting cp "rpcport"     8336
-                 })
-    where
-      getSetting cp x dfl = case get cp "DEFAULT" x of
-                              Left  _ -> dfl
-                              Right x -> x
+confFile = "/etc/namecoin.conf"
 
 -- HTTP/JsonRpc interface
 
 
 -- HTTP/JsonRpc interface
 
-qReq cf q = applyBasicAuth (pack (rpcuser cf)) (pack (rpcpassword cf))
-          $ def { host           = (pack (rpchost cf))
-                , port           = (rpcport cf)
-                , method         = "PUT"
-                , requestHeaders = [ (hAccept,      "application/json")
-                                   , (hContentType, "application/json")
-                                   , (hConnection,  "Keep-Alive")
-                                   ]
-                , requestBody    = RequestBodyLBS $ encode $
-                                   JsonRpcRequest JsonRpcV1
-                                                  "name_show"
-                                                  [q]
-                                                  (String "pdns-nmc")
-                , checkStatus    = \_ _ _ -> Nothing
-                }
+qReq :: Config -> ByteString -> ByteString -> Request m
+qReq cf q id = applyBasicAuth (C.pack (rpcuser cf)) (C.pack (rpcpassword cf))
+             $ def { host           = (C.pack (rpchost cf))
+                   , port           = (rpcport cf)
+                   , method         = "PUT"
+                   , requestHeaders = [ (hAccept,      "application/json")
+                                      , (hContentType, "application/json")
+                                      , (hConnection,  "Keep-Alive")
+                                      ]
+                   , requestBody    = RequestBodyLBS $ encode $
+                                      JsonRpcRequest JsonRpcV1
+                                                     "name_show"
+                                                     [q]
+                                                     (String "pdns-nmc")
+                   , checkStatus    = \_ _ _ -> Nothing
+                   }
+
+qRsp :: Response ByteString -> Either String ByteString
+qRsp rsp =
+    case parseJsonRpc (responseBody rsp) :: Either JsonRpcError NmcRes of
+      Left  jerr -> 
+        case (jrpcErrCode jerr) of
+          -4 -> Right "{}"      -- this is how non-existent entry is returned
+          _  -> Left $ "JsonRpc error response: " ++ (show jerr)
+      Right jrsp -> Right $ resValue jrsp
 
 -- NMC interface
 
 
 -- NMC interface
 
-{-
-queryNmc :: String -> String -> RRType -> String -> IO (Either String NmcDom)
-queryNmc uri fqdn qtype qid = do
-  case reverse  (splitOn "." fqdn) of
+queryOp :: Manager -> Config -> String -> String
+        -> IO (Either String ByteString)
+queryOp mgr cfg qid key = do
+  rsp <- runResourceT $
+    httpLbs (qReq cfg (L.pack key) (L.pack qid)) mgr
+  return $ qRsp rsp
+
+queryNmc :: Manager -> Config -> String -> String
+         -> IO (Either String NmcDom)
+queryNmc mgr cfg fqdn qid = do
+  case reverse (splitOn "." fqdn) of
     "bit":dn:xs -> do
     "bit":dn:xs -> do
-      ans <- detailledRemote Version1 [] uri "name_show" $ "d/" ++ dn
-      let mdom = decode (resValue ans) :: Maybe NmcDom
-      case mdom of
-        Nothing  -> return $ Left ("Unparseable: " ++ (show (resValue ans)))
-        Just dom -> return $ Right dom
+      dom <- mergeImport (queryOp mgr cfg qid) $
+                emptyNmcDom { domImport = Just ("d/" ++ dn)}
+      return $ Right $ descendNmcDom xs dom
     _           ->
       return $ Left "Only \".bit\" domain is supported"
     _           ->
       return $ Left "Only \".bit\" domain is supported"
--}
--- PowerDNS ABI
-
-data RRType = RRTypeSRV   | RRTypeA   | RRTypeAAAA | RRTypeCNAME
-            | RRTypeDNAME | RRTypeSOA | RRTypeRP   | RRTypeLOC
-            | RRTypeNS    | RRTypeDS
-            | RRTypeANY   | RRTypeError String 
-        deriving (Show)
-
-data PdnsRequest = PdnsRequestQ
-                   { qName              :: String
-                   , qType              :: RRType
-                   , iD                 :: String
-                   , remoteIpAddress    :: String
-                   , localIpAddress     :: Maybe String
-                   , ednsSubnetAddress  :: Maybe String
-                   }
-                 | PdnsRequestAXFR String
-                 | PdnsRequestPing
-        deriving (Show)
-
-pdnsParse ver s =
-  let
-    getQt qt = case qt of
-      "SRV"     -> RRTypeSRV   
-      "A"       -> RRTypeA
-      "AAAA"    -> RRTypeAAAA
-      "CNAME"   -> RRTypeCNAME
-      "DNAME"   -> RRTypeDNAME 
-      "SOA"     -> RRTypeSOA 
-      "RP"      -> RRTypeRP   
-      "LOC"     -> RRTypeLOC
-      "NS"      -> RRTypeNS    
-      "DS"      -> RRTypeDS
-      "ANY"     -> RRTypeANY
-      _         -> RRTypeError qt
-    getLIp ver xs
-      | ver >= 2  = case xs of
-                      x:_       -> Just x
-                      _         -> Nothing
-      | otherwise = Nothing
-    getRIp ver xs
-      | ver >= 3  = case xs of
-                      _:x:_     -> Just x
-                      _         -> Nothing
-      | otherwise = Nothing
-  in
-    case words s of
-      "PING":[]                 -> Right PdnsRequestPing
-      "AXFR":x:[]               -> Right (PdnsRequestAXFR x)
-      "Q":qn:"IN":qt:id:rip:xs  -> Right (PdnsRequestQ
-                                            { qName = qn
-                                            , qType = getQt qt
-                                            , iD = id
-                                            , remoteIpAddress = rip
-                                            , localIpAddress = getLIp ver xs
-                                            , ednsSubnetAddress = getRIp ver xs
-                                            })
-      _                         -> Left s
-
-{-
-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"
--}
 
 -- Main entry
 
 
 -- Main entry
 
@@ -151,6 +75,8 @@ main = do
 
   cfg <- readConfig confFile
 
 
   cfg <- readConfig confFile
 
+  hSetBuffering stdin  LineBuffering
+  hSetBuffering stdout LineBuffering
   ver <- do
     let
       loopErr e = forever $ do
   ver <- do
     let
       loopErr e = forever $ do
@@ -168,18 +94,21 @@ main = do
   putStrLn $ "OK\tDnsNmc ready to serve, protocol v." ++ (show ver)
 
   mgr <- newManager def
   putStrLn $ "OK\tDnsNmc ready to serve, protocol v." ++ (show ver)
 
   mgr <- newManager def
-
-  print $ qReq cfg "d/nosuchdomain"
-  rsp <- runResourceT $ httpLbs (qReq cfg "d/nosuchdomain") mgr
-  print $ (statusCode . responseStatus) rsp
-  putStrLn "===== complete response is:"
-  print rsp
-  let rbody = responseBody rsp
-  putStrLn "===== response body is:"
-  print rbody
-  let result = parseJsonRpc rbody :: Either JsonRpcError NmcRes
-  putStrLn "===== parsed response is:"
-  print result
---  print $ parseJsonRpc (responseBody rsp)
-
-  --forever $ getLine >>= (pdnsOut uri) . (pdnsParse ver)
+  forever $ do
+    l <- getLine
+    case pdnsParse ver l of
+      Left e -> putStr $ pdnsReport e
+      Right preq -> do
+        case preq of
+          PdnsRequestQ qname qtype id _ _ _ ->
+            queryNmc mgr cfg qname id >>= putStr . (pdnsOut ver id qname qtype)
+          PdnsRequestAXFR xfrreq ->
+            putStr $ pdnsReport ("No support for AXFR " ++ xfrreq)
+          PdnsRequestPing -> putStrLn "END"
+
+-- for testing
+
+ask str = do
+  cfg <- readConfig confFile
+  mgr <- newManager def
+  queryNmc mgr cfg str "askid" >>= putStr . (pdnsOut 1 "askid" str RRTypeANY)