{-# LANGUAGE PolyKinds #-}
module Marconi.CLI
(chainPointParser
, multiString
, parseCardanoAddresses
, pNetworkId
, Options (..)
, optionsParser
, parseOptions
, utxoDbPath
, datumDbPath
, scriptTxDbPath
) where
import Control.Applicative (optional, some)
import Data.ByteString.Char8 qualified as C8
import Data.List (nub)
import Data.List.NonEmpty (fromList)
import Data.Maybe (fromMaybe)
import Data.Proxy (Proxy (Proxy))
import Data.Text (pack)
import Options.Applicative qualified as Opt
import System.Environment (lookupEnv)
import System.FilePath ((</>))
import Cardano.Api (ChainPoint, NetworkId)
import Cardano.Api qualified as C
import Marconi.Types (TargetAddresses)
chainPointParser :: Opt.Parser C.ChainPoint
chainPointParser :: Parser ChainPoint
chainPointParser =
ChainPoint -> Parser ChainPoint
forall (f :: * -> *) a. Applicative f => a -> f a
pure ChainPoint
C.ChainPointAtGenesis
Parser ChainPoint -> Parser ChainPoint -> Parser ChainPoint
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
Opt.<|> ( SlotNo -> Hash BlockHeader -> ChainPoint
C.ChainPoint
(SlotNo -> Hash BlockHeader -> ChainPoint)
-> Parser SlotNo -> Parser (Hash BlockHeader -> ChainPoint)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadM SlotNo -> Mod OptionFields SlotNo -> Parser SlotNo
forall a. ReadM a -> Mod OptionFields a -> Parser a
Opt.option (Word64 -> SlotNo
C.SlotNo (Word64 -> SlotNo) -> ReadM Word64 -> ReadM SlotNo
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadM Word64
forall a. Read a => ReadM a
Opt.auto) (String -> Mod OptionFields SlotNo
forall (f :: * -> *) a. HasName f => String -> Mod f a
Opt.long String
"slot-no"
Mod OptionFields SlotNo
-> Mod OptionFields SlotNo -> Mod OptionFields SlotNo
forall a. Semigroup a => a -> a -> a
<> Char -> Mod OptionFields SlotNo
forall (f :: * -> *) a. HasName f => Char -> Mod f a
Opt.short Char
'n'
Mod OptionFields SlotNo
-> Mod OptionFields SlotNo -> Mod OptionFields SlotNo
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields SlotNo
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
Opt.metavar String
"SLOT-NO")
Parser (Hash BlockHeader -> ChainPoint)
-> Parser (Hash BlockHeader) -> Parser ChainPoint
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ReadM (Hash BlockHeader)
-> Mod OptionFields (Hash BlockHeader) -> Parser (Hash BlockHeader)
forall a. ReadM a -> Mod OptionFields a -> Parser a
Opt.option
((String -> Maybe (Hash BlockHeader)) -> ReadM (Hash BlockHeader)
forall a. (String -> Maybe a) -> ReadM a
Opt.maybeReader String -> Maybe (Hash BlockHeader)
maybeParseHashBlockHeader ReadM (Hash BlockHeader)
-> ReadM (Hash BlockHeader) -> ReadM (Hash BlockHeader)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
Opt.<|> String -> ReadM (Hash BlockHeader)
forall a. String -> ReadM a
Opt.readerError String
"Malformed block hash")
(String -> Mod OptionFields (Hash BlockHeader)
forall (f :: * -> *) a. HasName f => String -> Mod f a
Opt.long String
"block-hash"
Mod OptionFields (Hash BlockHeader)
-> Mod OptionFields (Hash BlockHeader)
-> Mod OptionFields (Hash BlockHeader)
forall a. Semigroup a => a -> a -> a
<> Char -> Mod OptionFields (Hash BlockHeader)
forall (f :: * -> *) a. HasName f => Char -> Mod f a
Opt.short Char
'b'
Mod OptionFields (Hash BlockHeader)
-> Mod OptionFields (Hash BlockHeader)
-> Mod OptionFields (Hash BlockHeader)
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields (Hash BlockHeader)
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
Opt.metavar String
"BLOCK-HASH")
)
where
maybeParseHashBlockHeader :: String -> Maybe (C.Hash C.BlockHeader)
maybeParseHashBlockHeader :: String -> Maybe (Hash BlockHeader)
maybeParseHashBlockHeader =
(RawBytesHexError -> Maybe (Hash BlockHeader))
-> (Hash BlockHeader -> Maybe (Hash BlockHeader))
-> Either RawBytesHexError (Hash BlockHeader)
-> Maybe (Hash BlockHeader)
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (Maybe (Hash BlockHeader)
-> RawBytesHexError -> Maybe (Hash BlockHeader)
forall a b. a -> b -> a
const Maybe (Hash BlockHeader)
forall a. Maybe a
Nothing) Hash BlockHeader -> Maybe (Hash BlockHeader)
forall a. a -> Maybe a
Just
(Either RawBytesHexError (Hash BlockHeader)
-> Maybe (Hash BlockHeader))
-> (String -> Either RawBytesHexError (Hash BlockHeader))
-> String
-> Maybe (Hash BlockHeader)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AsType (Hash BlockHeader)
-> ByteString -> Either RawBytesHexError (Hash BlockHeader)
forall a.
SerialiseAsRawBytes a =>
AsType a -> ByteString -> Either RawBytesHexError a
C.deserialiseFromRawBytesHex (Proxy (Hash BlockHeader) -> AsType (Hash BlockHeader)
forall t. HasTypeProxy t => Proxy t -> AsType t
C.proxyToAsType Proxy (Hash BlockHeader)
forall k (t :: k). Proxy t
Proxy)
(ByteString -> Either RawBytesHexError (Hash BlockHeader))
-> (String -> ByteString)
-> String
-> Either RawBytesHexError (Hash BlockHeader)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ByteString
C8.pack
fromJustWithError :: (Show e) => Either e a -> a
fromJustWithError :: Either e a -> a
fromJustWithError Either e a
v = case Either e a
v of
Left e
e ->
String -> a
forall a. HasCallStack => String -> a
error (String -> a) -> String -> a
forall a b. (a -> b) -> a -> b
$ String
"\n!!!\n Abnormal Termination with Error: " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> e -> String
forall a. Show a => a -> String
show e
e String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
"\n!!!\n"
Right a
accounts -> a
accounts
pNetworkId :: Opt.Parser C.NetworkId
pNetworkId :: Parser NetworkId
pNetworkId = Parser NetworkId
pMainnet Parser NetworkId -> Parser NetworkId -> Parser NetworkId
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
Opt.<|> (NetworkMagic -> NetworkId)
-> Parser NetworkMagic -> Parser NetworkId
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap NetworkMagic -> NetworkId
C.Testnet Parser NetworkMagic
pTestnetMagic
pMainnet :: Opt.Parser C.NetworkId
pMainnet :: Parser NetworkId
pMainnet = NetworkId -> Mod FlagFields NetworkId -> Parser NetworkId
forall a. a -> Mod FlagFields a -> Parser a
Opt.flag' NetworkId
C.Mainnet (String -> Mod FlagFields NetworkId
forall (f :: * -> *) a. HasName f => String -> Mod f a
Opt.long String
"mainnet" Mod FlagFields NetworkId
-> Mod FlagFields NetworkId -> Mod FlagFields NetworkId
forall a. Semigroup a => a -> a -> a
<> String -> Mod FlagFields NetworkId
forall (f :: * -> *) a. String -> Mod f a
Opt.help String
"Use the mainnet magic id.")
pTestnetMagic :: Opt.Parser C.NetworkMagic
pTestnetMagic :: Parser NetworkMagic
pTestnetMagic = Word32 -> NetworkMagic
C.NetworkMagic (Word32 -> NetworkMagic) -> Parser Word32 -> Parser NetworkMagic
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadM Word32 -> Mod OptionFields Word32 -> Parser Word32
forall a. ReadM a -> Mod OptionFields a -> Parser a
Opt.option ReadM Word32
forall a. Read a => ReadM a
Opt.auto
(String -> Mod OptionFields Word32
forall (f :: * -> *) a. HasName f => String -> Mod f a
Opt.long String
"testnet-magic"
Mod OptionFields Word32
-> Mod OptionFields Word32 -> Mod OptionFields Word32
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields Word32
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
Opt.metavar String
"NATURAL"
Mod OptionFields Word32
-> Mod OptionFields Word32 -> Mod OptionFields Word32
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields Word32
forall (f :: * -> *) a. String -> Mod f a
Opt.help String
"Specify a testnet magic id.")
multiString :: Opt.Mod Opt.OptionFields [C.Address C.ShelleyAddr] -> Opt.Parser TargetAddresses
multiString :: Mod OptionFields [Address ShelleyAddr] -> Parser TargetAddresses
multiString Mod OptionFields [Address ShelleyAddr]
desc = [Address ShelleyAddr] -> TargetAddresses
forall a. [a] -> NonEmpty a
fromList ([Address ShelleyAddr] -> TargetAddresses)
-> ([[Address ShelleyAddr]] -> [Address ShelleyAddr])
-> [[Address ShelleyAddr]]
-> TargetAddresses
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[Address ShelleyAddr]] -> [Address ShelleyAddr]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[Address ShelleyAddr]] -> TargetAddresses)
-> Parser [[Address ShelleyAddr]] -> Parser TargetAddresses
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser [Address ShelleyAddr] -> Parser [[Address ShelleyAddr]]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
some Parser [Address ShelleyAddr]
single
where
single :: Parser [Address ShelleyAddr]
single = ReadM [Address ShelleyAddr]
-> Mod OptionFields [Address ShelleyAddr]
-> Parser [Address ShelleyAddr]
forall a. ReadM a -> Mod OptionFields a -> Parser a
Opt.option (ReadM String
forall s. IsString s => ReadM s
Opt.str ReadM String
-> (String -> ReadM [Address ShelleyAddr])
-> ReadM [Address ShelleyAddr]
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ([Address ShelleyAddr] -> ReadM [Address ShelleyAddr]
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([Address ShelleyAddr] -> ReadM [Address ShelleyAddr])
-> (String -> [Address ShelleyAddr])
-> String
-> ReadM [Address ShelleyAddr]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [Address ShelleyAddr]
parseCardanoAddresses)) Mod OptionFields [Address ShelleyAddr]
desc
parseCardanoAddresses :: String -> [C.Address C.ShelleyAddr]
parseCardanoAddresses :: String -> [Address ShelleyAddr]
parseCardanoAddresses = [Address ShelleyAddr] -> [Address ShelleyAddr]
forall a. Eq a => [a] -> [a]
nub
([Address ShelleyAddr] -> [Address ShelleyAddr])
-> (String -> [Address ShelleyAddr])
-> String
-> [Address ShelleyAddr]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either Bech32DecodeError [Address ShelleyAddr]
-> [Address ShelleyAddr]
forall e a. Show e => Either e a -> a
fromJustWithError
(Either Bech32DecodeError [Address ShelleyAddr]
-> [Address ShelleyAddr])
-> (String -> Either Bech32DecodeError [Address ShelleyAddr])
-> String
-> [Address ShelleyAddr]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> Either Bech32DecodeError (Address ShelleyAddr))
-> [String] -> Either Bech32DecodeError [Address ShelleyAddr]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (Text -> Either Bech32DecodeError (Address ShelleyAddr)
deserializeToCardano (Text -> Either Bech32DecodeError (Address ShelleyAddr))
-> (String -> Text)
-> String
-> Either Bech32DecodeError (Address ShelleyAddr)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
pack)
([String] -> Either Bech32DecodeError [Address ShelleyAddr])
-> (String -> [String])
-> String
-> Either Bech32DecodeError [Address ShelleyAddr]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String]
words
where
deserializeToCardano :: Text -> Either Bech32DecodeError (Address ShelleyAddr)
deserializeToCardano = AsType (Address ShelleyAddr)
-> Text -> Either Bech32DecodeError (Address ShelleyAddr)
forall a.
SerialiseAsBech32 a =>
AsType a -> Text -> Either Bech32DecodeError a
C.deserialiseFromBech32 (Proxy (Address ShelleyAddr) -> AsType (Address ShelleyAddr)
forall t. HasTypeProxy t => Proxy t -> AsType t
C.proxyToAsType Proxy (Address ShelleyAddr)
forall k (t :: k). Proxy t
Proxy)
data Options = Options
{ Options -> String
optionsSocketPath :: String,
Options -> NetworkId
optionsNetworkId :: NetworkId,
Options -> ChainPoint
optionsChainPoint :: ChainPoint,
Options -> String
optionsDbPath :: FilePath,
Options -> Bool
optionsDisableUtxo :: Bool,
Options -> Bool
optionsDisableDatum :: Bool,
Options -> Bool
optionsDisableScript :: Bool,
Options -> Maybe TargetAddresses
optionsTargetAddresses :: Maybe TargetAddresses
}
deriving (Int -> Options -> String -> String
[Options] -> String -> String
Options -> String
(Int -> Options -> String -> String)
-> (Options -> String)
-> ([Options] -> String -> String)
-> Show Options
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Options] -> String -> String
$cshowList :: [Options] -> String -> String
show :: Options -> String
$cshow :: Options -> String
showsPrec :: Int -> Options -> String -> String
$cshowsPrec :: Int -> Options -> String -> String
Show)
parseOptions :: IO Options
parseOptions :: IO Options
parseOptions = do
Maybe String
maybeSha <- String -> IO (Maybe String)
lookupEnv String
"GITHUB_SHA"
let sha :: String
sha = String -> Maybe String -> String
forall a. a -> Maybe a -> a
fromMaybe String
"GIHUB_SHA environment variable not set!" Maybe String
maybeSha
ParserInfo Options -> IO Options
forall a. ParserInfo a -> IO a
Opt.execParser (String -> ParserInfo Options
programParser String
sha)
where
programParser :: String -> ParserInfo Options
programParser String
sha =
Parser Options -> InfoMod Options -> ParserInfo Options
forall a. Parser a -> InfoMod a -> ParserInfo a
Opt.info (Parser ((Options -> Options) -> Options -> Options)
forall a. Parser (a -> a)
Opt.helper
Parser ((Options -> Options) -> Options -> Options)
-> Parser (Options -> Options) -> Parser (Options -> Options)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (String -> Parser (Options -> Options)
forall a. String -> Parser (a -> a)
versionOption String
sha)
Parser (Options -> Options) -> Parser Options -> Parser Options
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Options
optionsParser)
(InfoMod Options
forall a. InfoMod a
Opt.fullDesc
InfoMod Options -> InfoMod Options -> InfoMod Options
forall a. Semigroup a => a -> a -> a
<> String -> InfoMod Options
forall a. String -> InfoMod a
Opt.progDesc String
"marconi"
InfoMod Options -> InfoMod Options -> InfoMod Options
forall a. Semigroup a => a -> a -> a
<> String -> InfoMod Options
forall a. String -> InfoMod a
Opt.header
String
"marconi - a lightweight customizable solution for indexing and querying the Cardano blockchain"
)
versionOption :: String -> Parser (a -> a)
versionOption String
sha = String -> Mod OptionFields (a -> a) -> Parser (a -> a)
forall a. String -> Mod OptionFields (a -> a) -> Parser (a -> a)
Opt.infoOption String
sha (String -> Mod OptionFields (a -> a)
forall (f :: * -> *) a. HasName f => String -> Mod f a
Opt.long String
"version" Mod OptionFields (a -> a)
-> Mod OptionFields (a -> a) -> Mod OptionFields (a -> a)
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields (a -> a)
forall (f :: * -> *) a. String -> Mod f a
Opt.help String
"Show git SHA")
optionsParser :: Opt.Parser Options
optionsParser :: Parser Options
optionsParser =
String
-> NetworkId
-> ChainPoint
-> String
-> Bool
-> Bool
-> Bool
-> Maybe TargetAddresses
-> Options
Options
(String
-> NetworkId
-> ChainPoint
-> String
-> Bool
-> Bool
-> Bool
-> Maybe TargetAddresses
-> Options)
-> Parser String
-> Parser
(NetworkId
-> ChainPoint
-> String
-> Bool
-> Bool
-> Bool
-> Maybe TargetAddresses
-> Options)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Mod OptionFields String -> Parser String
forall s. IsString s => Mod OptionFields s -> Parser s
Opt.strOption (String -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => String -> Mod f a
Opt.long String
"socket-path"
Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> Char -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => Char -> Mod f a
Opt.short Char
's'
Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. String -> Mod f a
Opt.help String
"Path to node socket.")
Parser
(NetworkId
-> ChainPoint
-> String
-> Bool
-> Bool
-> Bool
-> Maybe TargetAddresses
-> Options)
-> Parser NetworkId
-> Parser
(ChainPoint
-> String
-> Bool
-> Bool
-> Bool
-> Maybe TargetAddresses
-> Options)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser NetworkId
pNetworkId
Parser
(ChainPoint
-> String
-> Bool
-> Bool
-> Bool
-> Maybe TargetAddresses
-> Options)
-> Parser ChainPoint
-> Parser
(String
-> Bool -> Bool -> Bool -> Maybe TargetAddresses -> Options)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser ChainPoint
chainPointParser
Parser
(String
-> Bool -> Bool -> Bool -> Maybe TargetAddresses -> Options)
-> Parser String
-> Parser
(Bool -> Bool -> Bool -> Maybe TargetAddresses -> Options)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Mod OptionFields String -> Parser String
forall s. IsString s => Mod OptionFields s -> Parser s
Opt.strOption (String -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => String -> Mod f a
Opt.long String
"database-directory-path"
Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> Char -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => Char -> Mod f a
Opt.short Char
'd'
Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields String
forall (f :: * -> *) a. String -> Mod f a
Opt.help String
"Dirctory Path for SQLite database.")
Parser (Bool -> Bool -> Bool -> Maybe TargetAddresses -> Options)
-> Parser Bool
-> Parser (Bool -> Bool -> Maybe TargetAddresses -> Options)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Mod FlagFields Bool -> Parser Bool
Opt.switch (String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
Opt.long String
"disable-utxo"
Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> String -> Mod FlagFields Bool
forall (f :: * -> *) a. String -> Mod f a
Opt.help String
"disable utxo indexers."
Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> Mod FlagFields Bool
forall a (f :: * -> *). Show a => Mod f a
Opt.showDefault
)
Parser (Bool -> Bool -> Maybe TargetAddresses -> Options)
-> Parser Bool -> Parser (Bool -> Maybe TargetAddresses -> Options)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Mod FlagFields Bool -> Parser Bool
Opt.switch (String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
Opt.long String
"disable-datum"
Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> String -> Mod FlagFields Bool
forall (f :: * -> *) a. String -> Mod f a
Opt.help String
"disable datum indexers."
Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> Mod FlagFields Bool
forall a (f :: * -> *). Show a => Mod f a
Opt.showDefault
)
Parser (Bool -> Maybe TargetAddresses -> Options)
-> Parser Bool -> Parser (Maybe TargetAddresses -> Options)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Mod FlagFields Bool -> Parser Bool
Opt.switch (String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
Opt.long String
"disable-script-tx"
Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> String -> Mod FlagFields Bool
forall (f :: * -> *) a. String -> Mod f a
Opt.help String
"disable script-tx indexers."
Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> Mod FlagFields Bool
forall a (f :: * -> *). Show a => Mod f a
Opt.showDefault
)
Parser (Maybe TargetAddresses -> Options)
-> Parser (Maybe TargetAddresses) -> Parser Options
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Mod OptionFields [Address ShelleyAddr]
-> Parser (Maybe TargetAddresses)
optAddressesParser (String -> Mod OptionFields [Address ShelleyAddr]
forall (f :: * -> *) a. HasName f => String -> Mod f a
Opt.long String
"addresses-to-index"
Mod OptionFields [Address ShelleyAddr]
-> Mod OptionFields [Address ShelleyAddr]
-> Mod OptionFields [Address ShelleyAddr]
forall a. Semigroup a => a -> a -> a
<> Char -> Mod OptionFields [Address ShelleyAddr]
forall (f :: * -> *) a. HasName f => Char -> Mod f a
Opt.short Char
'a'
Mod OptionFields [Address ShelleyAddr]
-> Mod OptionFields [Address ShelleyAddr]
-> Mod OptionFields [Address ShelleyAddr]
forall a. Semigroup a => a -> a -> a
<> String -> Mod OptionFields [Address ShelleyAddr]
forall (f :: * -> *) a. String -> Mod f a
Opt.help (String
"Becch32 Shelley addresses to index."
String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
" i.e \"--address-to-index address-1 --address-to-index address-2 ...\"" ) )
optAddressesParser :: Opt.Mod Opt.OptionFields [C.Address C.ShelleyAddr] -> Opt.Parser (Maybe TargetAddresses)
optAddressesParser :: Mod OptionFields [Address ShelleyAddr]
-> Parser (Maybe TargetAddresses)
optAddressesParser = Parser TargetAddresses -> Parser (Maybe TargetAddresses)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Parser TargetAddresses -> Parser (Maybe TargetAddresses))
-> (Mod OptionFields [Address ShelleyAddr]
-> Parser TargetAddresses)
-> Mod OptionFields [Address ShelleyAddr]
-> Parser (Maybe TargetAddresses)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Mod OptionFields [Address ShelleyAddr] -> Parser TargetAddresses
multiString
utxoDbName :: FilePath
utxoDbName :: String
utxoDbName = String
"utxodb"
datumDbName :: FilePath
datumDbName :: String
datumDbName = String
"datumdb"
scriptTxDbName :: FilePath
scriptTxDbName :: String
scriptTxDbName = String
"scripttxdb"
utxoDbPath :: Options -> Maybe FilePath
utxoDbPath :: Options -> Maybe String
utxoDbPath Options
o = if Options -> Bool
optionsDisableUtxo Options
o then Maybe String
forall a. Maybe a
Nothing; else String -> Maybe String
forall a. a -> Maybe a
Just (Options -> String
optionsDbPath Options
o String -> String -> String
</> String
utxoDbName)
datumDbPath :: Options -> Maybe FilePath
datumDbPath :: Options -> Maybe String
datumDbPath Options
o = if Options -> Bool
optionsDisableDatum Options
o then Maybe String
forall a. Maybe a
Nothing; else String -> Maybe String
forall a. a -> Maybe a
Just (Options -> String
optionsDbPath Options
o String -> String -> String
</> String
datumDbName)
scriptTxDbPath :: Options -> Maybe FilePath
scriptTxDbPath :: Options -> Maybe String
scriptTxDbPath Options
o = if Options -> Bool
optionsDisableScript Options
o then Maybe String
forall a. Maybe a
Nothing; else String -> Maybe String
forall a. a -> Maybe a
Just (Options -> String
optionsDbPath Options
o String -> String -> String
</> String
scriptTxDbName)