{-# LANGUAGE RecordWildCards, OverloadedStrings #-} -- | Main module module Main where import Json import Control.Lens import Control.Monad (when) import Network.Wreq (get, responseBody) import Data.Monoid import Data.Aeson (decode, toJSON) import Data.Maybe (fromJust) import Data.HashMap.Strict (delete) import Data.ByteString.Lazy.Char8 (pack) import Options.Applicative import System.Process -- * CLI interface -- | Program arguments record data Options = Options { name :: String , url :: String , dnschain :: Bool , block :: Bool , raw :: Bool } -- | Program arguments parser options :: Parser Options options = Options <$> strArgument ( metavar "NAME" <> help "Namecoin name id" ) <*> strOption ( long "url" <> short 'u' <> value "http://dns.dnschain.net/" <> metavar "URL" <> help "Use custom api url" ) <*> switch ( long "dnschain" <> short 'd' <> help "Use dnschain api" ) <*> switch ( long "block" <> short 'b' <> help "Show blockchain data (require local connection)" ) <*> switch ( long "raw" <> short 'r' <> help "Print raw JSON data" ) -- | Program description description :: ParserInfo Options description = info (helper <*> options) ( fullDesc <> progDesc "Query the namecoin blockchain" <> footer "Stat rosa pristina nomine, nomina nuda tenemus." ) -- * Program -- | Main function main :: IO () main = execParser description >>= exec where exec Options{..} = if dnschain then doDnschain url name raw else doLocal name block -- | Connect to local namecoin node doLocal :: String -> Bool -> IO () doLocal name block = do out <- readProcess "namecoin-cli" ["name_show", name] "" case decode (pack out) of Nothing -> putStrLn "Error parsing data" Just res -> do pprint $ reparse (res |: "value") when block (pprint extra) where reparse = fromJust . decode . pack extra = toJSON (delete "value" res) -- | Connect to dnschain api endpoint doDnschain :: String -> String -> Bool -> IO () doDnschain url name raw = do body <- (^. responseBody) <$> get (url ++ name) if raw then print body else putStrLn $ case decode body of Just res -> repr res Nothing -> "Error parsing data"