--- /dev/null
+{-# LANGUAGE DeriveDataTypeable #-}
+
+module CommandLine (
+ Args(..),
+ Delegates(..),
+ get_args
+ )
+where
+
+import System.Console.CmdArgs
+
+-- Get the version from Cabal.
+import Paths_haeres (version)
+import Data.Version (showVersion)
+
+ns_description :: String
+ns_description =
+ "Confirm delegation of NS records. " ++
+ "This is the default mode."
+
+mx_description :: String
+mx_description = "Confirm delegation of MX records."
+
+program_name :: String
+program_name = "haeres"
+
+my_summary :: String
+my_summary = program_name ++ "-" ++ (showVersion version)
+
+server_help :: String
+server_help =
+ "IP address of server to query " ++
+ "(will use resolv.conf if not specified)"
+
+newtype Delegates =
+ Delegates { get_delegates :: [String] }
+ deriving (Data, Show, Typeable)
+
+instance Default Delegates where
+ def = Delegates []
+
+data Args =
+ NS { server :: Maybe String, delegates :: Delegates } |
+ MX { server :: Maybe String, delegates :: Delegates }
+ deriving (Data, Show, Typeable)
+
+arg_spec :: Args
+arg_spec =
+ modes [ns &= auto, mx]
+ &= program program_name
+ &= summary my_summary
+ &= helpArg [explicit,
+ name "help",
+ name "h",
+ groupname "Common flags"]
+ &= versionArg [explicit,
+ name "version",
+ name "v",
+ groupname "Common flags"]
+ where
+ -- The repetition here is necessary, some Template Haskell magic
+ -- going on.
+ ns :: Args
+ ns = NS {
+ server = def
+ &= groupname "Common flags"
+ &= typ "IP"
+ &= help server_help,
+
+ delegates = def
+ &= args
+ &= typ "DELEGATES" }
+
+ &= details [ns_description]
+
+ mx :: Args
+ mx = MX {
+ server = def
+ &= groupname "Common flags"
+ &= typ "IP"
+ &= help server_help,
+
+ delegates = def
+ &= args
+ &= typ "DELEGATES" }
+
+ &= details [mx_description]
+
+get_args :: IO Args
+get_args = cmdArgs arg_spec
module Main
where
+import qualified Data.ByteString.Char8 as BS (pack)
+import Data.List ((\\))
+import Data.String.Utils (join, splitWs)
+
+import Network.DNS (
+ Domain,
+ FileOrNumericHost(RCHostName),
+ ResolvConf(resolvInfo),
+ defaultResolvConf,
+ lookupNS,
+ makeResolvSeed,
+ withResolver
+ )
+
+import System.IO (hGetContents, stdin)
+
+import CommandLine (Args(..), Delegates(..), get_args)
+
+report :: (Domain, Maybe [Domain]) -> IO ()
+report (d, Nothing) =
+ putStrLn $ "Domain " ++ (show d) ++ " not delegated."
+report (d, Just leftovers) =
+ if null leftovers
+ then return ()
+ else putStrLn $ "Domain " ++
+ (show d) ++
+ " delegates somewhere else: " ++
+ (join " " (map show leftovers))
+
+clean :: Delegates -> (Domain, Maybe [Domain]) -> (Domain, Maybe [Domain])
+clean _ p@(_, Nothing) = p
+clean (Delegates ds') (d, Just targets) =
+ (d, Just $ targets \\ ds)
+ where
+ ds = map BS.pack ds'
+
main :: IO ()
main = do
- putStrLn "Hello, World."
+ cfg <- get_args
+ print cfg
+ input <- hGetContents stdin
+
+ -- Split the input on any whitespace characters.
+ let domains' = splitWs input
+
+ -- Convert those Strings to ByteStrings
+ let domains = map BS.pack domains'
+
+ let rc = case (server cfg) of
+ Nothing -> defaultResolvConf
+ Just s -> defaultResolvConf { resolvInfo = RCHostName s }
+
+ rs <- makeResolvSeed rc
+ withResolver rs $ \resolver -> do
+ -- This function keeps the domain matches with its NS records.
+ let lookupNS' = \d -> (lookupNS resolver d) >>= (return . ((,) d))
+ domains_ns <- mapM lookupNS' domains
+ let cdns = map (clean (delegates cfg)) domains_ns
+
+ case cfg of
+ (NS _ _) ->
+ -- We're only checking NS records, so report what we found.
+ mapM_ report cdns
+ (MX _ _) ->
+ print "Hello, world."