]> www.average.org Git - pdns-pipe-nmc.git/blobdiff - pdns-pipe-nmc.hs
SRV hack part 2
[pdns-pipe-nmc.git] / pdns-pipe-nmc.hs
index 6874bb0d2790886693a54477ca006d60c2a97aa3..1d2563788d0f4fa938ac685322f7d785966ee3f2 100644 (file)
 
 module Main where
 
-import Control.Applicative
+import System.IO
 import Control.Monad
-import Data.ConfigFile
-import Data.Either.Utils
+import Data.ByteString.Lazy hiding (reverse, putStr, putStrLn)
+import qualified Data.ByteString.Char8 as C (pack)
+import qualified Data.ByteString.Lazy.Char8 as L (pack)
+import qualified Data.Text as T (pack)
 import Data.List.Split
-import Data.Aeson (decode)
-import Network.JsonRpc.Client
-import NmcJson
+import Data.Aeson (encode, decode, Value(..))
+import Network.HTTP.Types
+import Data.Conduit
+import Network.HTTP.Conduit
+
+import JsonRpcClient
+import Config
+import PowerDns
+import NmcRpc
+import NmcDom
 
 confFile = "/etc/namecoin.conf"
 
--- Config file handling
-
-data Config = Config { rpcuser       :: String
-                     , rpcpassword   :: String
-                     , rpchost       :: String
-                     , rpcport       :: String
-                     } 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
+-- HTTP/JsonRpc interface
+
+qReq :: Config -> String -> String -> 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"
+                                                     [L.pack q]
+                                                     (String (T.pack id))
+                   , 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
 
-queryNmc :: String -> String -> RRType -> String -> IO (Either String NmcDom)
-queryNmc uri fqdn qtype qid = do
-  case reverse  (splitOn "." fqdn) of
-    "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
-    _           ->
-      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"
+queryNmc :: Manager -> Config -> String -> String
+         -> IO (Either String NmcDom)
+queryNmc mgr cfg qid fqdn =
+  case reverse (splitOn "." fqdn) of
+    "bit":dn:xs -> descendNmcDom queryOp xs $ seedNmcDom dn
+    _           -> return $ Left "Only \".bit\" domain is supported"
+  where
+    queryOp key = do
+      rsp <- runResourceT $ httpLbs (qReq cfg key qid) mgr
+      -- print $ qRsp rsp
+      return $ qRsp rsp
 
 -- Main entry
 
 main = do
+
   cfg <- readConfig confFile
-  let uri = "http://" ++ rpcuser cfg ++ ":" ++ rpcpassword cfg ++
-            "@" ++ rpchost cfg ++ ":" ++ rpcport cfg ++ "/"
+
+  hSetBuffering stdin  LineBuffering
+  hSetBuffering stdout LineBuffering
   ver <- do
     let
       loopErr e = forever $ do
@@ -140,4 +87,23 @@ main = do
       _             -> loopErr $ "bad HELO " ++ (show s)
 
   putStrLn $ "OK\tDnsNmc ready to serve, protocol v." ++ (show ver)
-  forever $ getLine >>= (pdnsOut uri) . (pdnsParse ver)
+
+  mgr <- newManager def
+  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 id qname >>= 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 "askid" str >>= putStr . (pdnsOut 1 "askid" str RRTypeANY)