module Hydra.TUI.Options where
import Hydra.Prelude
import Data.Version (Version (Version), showVersion)
import Hydra.Cardano.Api (NetworkId, SocketPath)
import Hydra.Network (Host (Host))
import Hydra.Options (networkIdParser)
import Hydra.Version (embeddedRevision, gitRevision, unknownVersion)
import Options.Applicative (
Parser,
auto,
help,
infoOption,
long,
metavar,
option,
short,
showDefault,
strOption,
value,
)
import Paths_hydra_tui (version)
data Options = Options
{ Options -> Host
hydraNodeHost :: Host
, Options -> SocketPath
cardanoNodeSocket :: SocketPath
, Options -> NetworkId
cardanoNetworkId :: NetworkId
, Options -> FilePath
cardanoSigningKey :: FilePath
}
deriving stock (Options -> Options -> Bool
(Options -> Options -> Bool)
-> (Options -> Options -> Bool) -> Eq Options
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Options -> Options -> Bool
== :: Options -> Options -> Bool
$c/= :: Options -> Options -> Bool
/= :: Options -> Options -> Bool
Eq, Int -> Options -> ShowS
[Options] -> ShowS
Options -> FilePath
(Int -> Options -> ShowS)
-> (Options -> FilePath) -> ([Options] -> ShowS) -> Show Options
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Options -> ShowS
showsPrec :: Int -> Options -> ShowS
$cshow :: Options -> FilePath
show :: Options -> FilePath
$cshowList :: [Options] -> ShowS
showList :: [Options] -> ShowS
Show)
parseOptions :: Parser Options
parseOptions :: Parser Options
parseOptions =
( Host -> SocketPath -> NetworkId -> FilePath -> Options
Options
(Host -> SocketPath -> NetworkId -> FilePath -> Options)
-> Parser Host
-> Parser (SocketPath -> NetworkId -> FilePath -> Options)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Host
parseNodeHost
Parser (SocketPath -> NetworkId -> FilePath -> Options)
-> Parser SocketPath -> Parser (NetworkId -> FilePath -> Options)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser SocketPath
parseCardanoNodeSocket
Parser (NetworkId -> FilePath -> Options)
-> Parser NetworkId -> Parser (FilePath -> Options)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser NetworkId
networkIdParser
Parser (FilePath -> Options) -> Parser FilePath -> Parser Options
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser FilePath
parseCardanoSigningKey
)
Parser Options -> Parser (Options -> Options) -> Parser Options
forall (f :: * -> *) a b. Applicative f => f a -> f (a -> b) -> f b
<**> Parser (Options -> Options)
versionInfo
where
versionInfo :: Parser (Options -> Options)
versionInfo :: Parser (Options -> Options)
versionInfo =
FilePath
-> Mod OptionFields (Options -> Options)
-> Parser (Options -> Options)
forall a. FilePath -> Mod OptionFields (a -> a) -> Parser (a -> a)
infoOption
(Version -> FilePath
showVersion Version
ourVersion)
(FilePath -> Mod OptionFields (Options -> Options)
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
long FilePath
"version" Mod OptionFields (Options -> Options)
-> Mod OptionFields (Options -> Options)
-> Mod OptionFields (Options -> Options)
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod OptionFields (Options -> Options)
forall (f :: * -> *) a. FilePath -> Mod f a
help FilePath
"Show version")
ourVersion :: Version
ourVersion =
Version
version Version -> (Version -> Version) -> Version
forall a b. a -> (a -> b) -> b
& \(Version [Int]
semver [FilePath]
_) -> [Int] -> [FilePath] -> Version
Version [Int]
semver [FilePath]
revision
revision :: [FilePath]
revision =
Maybe FilePath -> [FilePath]
forall a. Maybe a -> [a]
maybeToList (Maybe FilePath -> [FilePath]) -> Maybe FilePath -> [FilePath]
forall a b. (a -> b) -> a -> b
$
Maybe FilePath
embeddedRevision
Maybe FilePath -> Maybe FilePath -> Maybe FilePath
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe FilePath
gitRevision
Maybe FilePath -> Maybe FilePath -> Maybe FilePath
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> FilePath -> Maybe FilePath
forall a. a -> Maybe a
Just FilePath
unknownVersion
parseCardanoNodeSocket :: Parser SocketPath
parseCardanoNodeSocket :: Parser SocketPath
parseCardanoNodeSocket =
Mod OptionFields SocketPath -> Parser SocketPath
forall s. IsString s => Mod OptionFields s -> Parser s
strOption
( FilePath -> Mod OptionFields SocketPath
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
long FilePath
"node-socket"
Mod OptionFields SocketPath
-> Mod OptionFields SocketPath -> Mod OptionFields SocketPath
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod OptionFields SocketPath
forall (f :: * -> *) a. HasMetavar f => FilePath -> Mod f a
metavar FilePath
"FILE"
Mod OptionFields SocketPath
-> Mod OptionFields SocketPath -> Mod OptionFields SocketPath
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod OptionFields SocketPath
forall (f :: * -> *) a. FilePath -> Mod f a
help FilePath
"The path to the Cardano node domain socket for client communication."
Mod OptionFields SocketPath
-> Mod OptionFields SocketPath -> Mod OptionFields SocketPath
forall a. Semigroup a => a -> a -> a
<> SocketPath -> Mod OptionFields SocketPath
forall (f :: * -> *) a. HasValue f => a -> Mod f a
value SocketPath
"node.socket"
Mod OptionFields SocketPath
-> Mod OptionFields SocketPath -> Mod OptionFields SocketPath
forall a. Semigroup a => a -> a -> a
<> Mod OptionFields SocketPath
forall a (f :: * -> *). Show a => Mod f a
showDefault
)
parseNodeHost :: Parser Host
parseNodeHost :: Parser Host
parseNodeHost =
ReadM Host -> Mod OptionFields Host -> Parser Host
forall a. ReadM a -> Mod OptionFields a -> Parser a
option
ReadM Host
forall a. Read a => ReadM a
auto
( FilePath -> Mod OptionFields Host
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
long FilePath
"connect"
Mod OptionFields Host
-> Mod OptionFields Host -> Mod OptionFields Host
forall a. Semigroup a => a -> a -> a
<> Char -> Mod OptionFields Host
forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
'c'
Mod OptionFields Host
-> Mod OptionFields Host -> Mod OptionFields Host
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod OptionFields Host
forall (f :: * -> *) a. FilePath -> Mod f a
help FilePath
"Hydra-node to connect to in the form of <host>:<port>"
Mod OptionFields Host
-> Mod OptionFields Host -> Mod OptionFields Host
forall a. Semigroup a => a -> a -> a
<> Host -> Mod OptionFields Host
forall (f :: * -> *) a. HasValue f => a -> Mod f a
value (Text -> PortNumber -> Host
Host Text
"127.0.0.1" PortNumber
4001)
Mod OptionFields Host
-> Mod OptionFields Host -> Mod OptionFields Host
forall a. Semigroup a => a -> a -> a
<> Mod OptionFields Host
forall a (f :: * -> *). Show a => Mod f a
showDefault
)
parseCardanoSigningKey :: Parser FilePath
parseCardanoSigningKey :: Parser FilePath
parseCardanoSigningKey =
Mod OptionFields FilePath -> Parser FilePath
forall s. IsString s => Mod OptionFields s -> Parser s
strOption
( FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
long FilePath
"cardano-signing-key"
Mod OptionFields FilePath
-> Mod OptionFields FilePath -> Mod OptionFields FilePath
forall a. Semigroup a => a -> a -> a
<> Char -> Mod OptionFields FilePath
forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
'k'
Mod OptionFields FilePath
-> Mod OptionFields FilePath -> Mod OptionFields FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. HasMetavar f => FilePath -> Mod f a
metavar FilePath
"FILE"
Mod OptionFields FilePath
-> Mod OptionFields FilePath -> Mod OptionFields FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. FilePath -> Mod f a
help FilePath
"The path to the user signing key file used for selecting UTxO and signing a commit transaction. This file uses the same 'TextEnvelope' format as cardano-cli."
Mod OptionFields FilePath
-> Mod OptionFields FilePath -> Mod OptionFields FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. HasValue f => a -> Mod f a
value FilePath
"me.sk"
Mod OptionFields FilePath
-> Mod OptionFields FilePath -> Mod OptionFields FilePath
forall a. Semigroup a => a -> a -> a
<> Mod OptionFields FilePath
forall a (f :: * -> *). Show a => Mod f a
showDefault
)