]> www.average.org Git - pdns-pipe-nmc.git/blobdiff - pdns-pipe-nmc.hs
wip move 'synthetic' parsing into NmcDom
[pdns-pipe-nmc.git] / pdns-pipe-nmc.hs
index 079e3b9cd9ab4014cb85016cc4d2892f78a94b3f..5fc64fa1c940c96bff85b47f80ec7bc65943b307 100644 (file)
 
 module Main where
 
---import Control.Applicative
+import Prelude hiding (lookup, readFile)
+import System.Environment
+import System.Console.GetOpt
+import System.IO hiding (readFile)
+import System.IO.Error
+import Data.Time.Clock.POSIX
+import Control.Exception
+import Text.Show.Pretty hiding (String)
 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 Control.Monad.State
+import Data.ByteString.Lazy hiding (reverse, putStr, putStrLn, head, empty)
+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.Map.Lazy (Map, empty, lookup, insert, delete, size)
 import Data.Aeson (encode, decode, Value(..))
 import Network.HTTP.Types
-import Data.Conduit
-import Network.HTTP.Conduit
-import Data.JsonRpcClient
-import NmcJson
+import Network.HTTP.Client
+import Data.Default.Class (def)
+-- if you have data-default-0.5.1 import this instead of Data.Default.Class:
+-- import Data.Default (def)
+
+import JsonRpcClient
+import Config
+import PowerDns
+import NmcRpc
+import NmcDom
+import NmcTransform
 
 confFile = "/etc/namecoin.conf"
 
--- 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
-
 -- 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 -> String -> Int -> Request
+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 (show 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)
+queryOpNmc cfg mgr qid key =
+  httpLbs (qReq cfg key qid) mgr >>= return . qRsp
 
-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
+queryOpFile key = catch (readFile key >>= return . Right)
+                        (\e -> return (Left (show (e :: IOException))))
 
-main = do
+queryDom queryOp fqdn =
+  case reverse (splitOn "." fqdn) of
+    "bit":dn:xs -> descendNmcDom queryOp xs $ seedNmcDom dn
+    _           -> return $ Left "Only \".bit\" domain is supported"
+
+-- Number of ten minute intervals elapsed since creation of Namecoin
+-- on April 18, 2011. Another option would be to use blockcount
+-- but that would require another lookup, and we are cheap.
+-- Yet another - to use (const - expires_in) from the lookup.
+nmcAge = fmap (\x -> floor ((x - 1303070400) / 600)) getPOSIXTime
+
+-- run a PowerDNS coprocess. Negotiate ABI version and execute requests.
+
+mainPdnsNmc = do
 
   cfg <- readConfig confFile
 
+  hSetBuffering stdin  LineBuffering
+  hSetBuffering stdout LineBuffering
+
   ver <- do
     let
       loopErr e = forever $ do
@@ -167,19 +106,86 @@ main = do
 
   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)
+  mgr <- newManager defaultManagerSettings
+
+  let
+    fetch = lookup
+    -- Save the name under current count, increment count for the next run
+    -- so the name is saved under the count that was put into the response.
+    stow name (count, cache) =
+      (if count >= 99 then 0 else count + 1
+      , insert count name
+          $ delete (if count >= 10 then count - 10 else count + 90) cache
+      )
+    io = liftIO
+
+    mainloop = forever $ do
+      l <- io getLine
+      gen <- io $ nmcAge
+      (count, cache) <- get
+      case pdnsParse ver l of
+        Left e -> io $ putStr $ pdnsReport e
+        Right preq -> do
+          case preq of
+            PdnsRequestQ qname qtype id _ _ _ -> do
+              io $ queryDom (queryOpNmc cfg mgr id) qname
+                     >>= putStr . (pdnsOutQ ver count gen qname qtype)
+  {-
+  -- debug
+              io $ putStrLn $ "LOG\tRequest number " ++ (show count)
+                           ++ " id: " ++ (show id)
+                           ++ " qname: " ++ qname
+                           ++ " qtype: " ++ (show qtype)
+                           ++ " cache size: " ++ (show (size cache))
+  -- end debug
+  -}
+              put $ stow qname (count, cache)
+            PdnsRequestAXFR xrq ->
+              case fetch xrq cache of
+                Nothing ->
+                  io $ putStr $
+                    pdnsReport ("AXFR for unknown id: " ++ (show xrq))
+                Just qname ->
+                  io $ queryDom (queryOpNmc cfg mgr xrq) qname
+                    >>= putStr . (pdnsOutXfr ver count gen qname)
+            PdnsRequestPing -> io $ putStrLn "END"
+
+  runStateT mainloop (0, empty) >> return ()
+
+-- helper for command-line tools
+
+pdnsOut gen key qt dom =
+  case qt of
+    "AXFR" -> pdnsOutXfr 1 (-1) gen key dom
+    _      -> pdnsOutQ 1 (-1) gen key (rrType qt) dom
+
+-- run one query by key from Namecoin, print domain object and answer
+
+mainOne gen key qt = do
+  cfg <- readConfig confFile
+  mgr <- newManager defaultManagerSettings
+  dom <- queryDom (queryOpNmc cfg mgr (-1)) key
+  putStrLn $ ppShow dom
+  putStr $ pdnsOut gen key qt dom
+
+-- get data from the file, print domain object and answer
+
+mainFile gen key qt = do
+  dom <- queryDom queryOpFile key
+  putStrLn $ ppShow dom
+  putStr $ pdnsOut gen key qt dom
+
+-- Entry point
+
+main = do
+  args <- getArgs
+  gen <- nmcAge
+  let
+    with f xs = case xs of
+      [qfqdn, qtype]       -> f gen qfqdn qtype
+      _ -> error $ "usage: empty args, or \"[-f] <fqdn> {<TYPE>|ANY|AXFR}\""
+                ++ " (type in caps)"
+  case args of
+    []      -> mainPdnsNmc
+    "-f":xs -> with mainFile xs
+    _       -> with mainOne args