{-# LANGUAGE OverloadedStrings #-}
module Config
( Config (..)
, mkConfig
) where
import Control.Monad ( MonadPlus (mzero) )
import Data.Aeson ( FromJSON (parseJSON), (.!=), (.:) )
import qualified Data.Yaml as Y
data Config
= Config {
Config -> String
configHost :: String
, Config -> Int
configPort :: Int
, Config -> String
configUser :: String
, Config -> String
configPassword :: String
, Config -> String
configKnownHosts :: FilePath
}
deriving (Int -> Config -> ShowS
[Config] -> ShowS
Config -> String
(Int -> Config -> ShowS)
-> (Config -> String) -> ([Config] -> ShowS) -> Show Config
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Config -> ShowS
showsPrec :: Int -> Config -> ShowS
$cshow :: Config -> String
show :: Config -> String
$cshowList :: [Config] -> ShowS
showList :: [Config] -> ShowS
Show)
newtype YamlConfig
= YamlConfig { YamlConfig -> Remote
yamlRemote :: Remote }
deriving (Int -> YamlConfig -> ShowS
[YamlConfig] -> ShowS
YamlConfig -> String
(Int -> YamlConfig -> ShowS)
-> (YamlConfig -> String)
-> ([YamlConfig] -> ShowS)
-> Show YamlConfig
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> YamlConfig -> ShowS
showsPrec :: Int -> YamlConfig -> ShowS
$cshow :: YamlConfig -> String
show :: YamlConfig -> String
$cshowList :: [YamlConfig] -> ShowS
showList :: [YamlConfig] -> ShowS
Show)
data Remote
= Remote { Remote -> String
remoteHost :: String
, Remote -> Int
remotePort :: Int
, Remote -> String
remoteUser :: String
, Remote -> String
remotePassword :: String
, Remote -> String
remoteKnownHosts :: FilePath
}
deriving (Int -> Remote -> ShowS
[Remote] -> ShowS
Remote -> String
(Int -> Remote -> ShowS)
-> (Remote -> String) -> ([Remote] -> ShowS) -> Show Remote
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Remote -> ShowS
showsPrec :: Int -> Remote -> ShowS
$cshow :: Remote -> String
show :: Remote -> String
$cshowList :: [Remote] -> ShowS
showList :: [Remote] -> ShowS
Show)
mkConfig :: YamlConfig -> IO Config
mkConfig :: YamlConfig -> IO Config
mkConfig YamlConfig{Remote
yamlRemote :: YamlConfig -> Remote
yamlRemote :: Remote
..} = do
let Remote {Int
String
remoteHost :: Remote -> String
remotePort :: Remote -> Int
remoteUser :: Remote -> String
remotePassword :: Remote -> String
remoteKnownHosts :: Remote -> String
remoteHost :: String
remotePort :: Int
remoteUser :: String
remotePassword :: String
remoteKnownHosts :: String
..} = Remote
yamlRemote
Config -> IO Config
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Config -> IO Config) -> Config -> IO Config
forall a b. (a -> b) -> a -> b
$
Config { configHost :: String
configHost = String
remoteHost
, configPort :: Int
configPort = Int
remotePort
, configUser :: String
configUser = String
remoteUser
, configPassword :: String
configPassword = String
remotePassword
, configKnownHosts :: String
configKnownHosts = String
remoteKnownHosts
}
instance FromJSON YamlConfig where
parseJSON :: Value -> Parser YamlConfig
parseJSON (Y.Object Object
v) =
Remote -> YamlConfig
YamlConfig (Remote -> YamlConfig) -> Parser Remote -> Parser YamlConfig
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Key -> Parser Remote
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"remote"
parseJSON Value
_ = Parser YamlConfig
forall a. Parser a
forall (m :: * -> *) a. MonadPlus m => m a
mzero
instance FromJSON Remote where
parseJSON :: Value -> Parser Remote
parseJSON (Y.Object Object
v) =
String -> Int -> String -> String -> String -> Remote
Remote (String -> Int -> String -> String -> String -> Remote)
-> Parser String
-> Parser (Int -> String -> String -> String -> Remote)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Key -> Parser String
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"hostname"
Parser (Int -> String -> String -> String -> Remote)
-> Parser Int -> Parser (String -> String -> String -> Remote)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser (Maybe Int)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"port" Parser (Maybe Int) -> Int -> Parser Int
forall a. Parser (Maybe a) -> a -> Parser a
.!= Int
22
Parser (String -> String -> String -> Remote)
-> Parser String -> Parser (String -> String -> Remote)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser String
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"username"
Parser (String -> String -> Remote)
-> Parser String -> Parser (String -> Remote)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser String
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"password"
Parser (String -> Remote) -> Parser String -> Parser Remote
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v Object -> Key -> Parser String
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"known_hosts"
parseJSON Value
_ = Parser Remote
forall a. Parser a
forall (m :: * -> *) a. MonadPlus m => m a
mzero