{-# LANGUAGE DataKinds #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE ScopedTypeVariables #-} module Cardano.CLI.EraBased.TextView.Option ( pTextViewCmds ) where import Cardano.CLI.EraBased.Common.Option import Cardano.CLI.EraBased.TextView.Command import Cardano.CLI.Option.Flag import Cardano.CLI.Parser import Data.Function ((&)) import Options.Applicative hiding (help, str) import Options.Applicative qualified as Opt pTextViewCmds :: Maybe (Parser (TextViewCmds era)) pTextViewCmds :: forall era. Maybe (Parser (TextViewCmds era)) pTextViewCmds = String -> InfoMod (TextViewCmds era) -> [Maybe (Parser (TextViewCmds era))] -> Maybe (Parser (TextViewCmds era)) forall a. String -> InfoMod a -> [Maybe (Parser a)] -> Maybe (Parser a) subInfoParser String "text-view" ( String -> InfoMod (TextViewCmds era) forall a. String -> InfoMod a Opt.progDesc (String -> InfoMod (TextViewCmds era)) -> String -> InfoMod (TextViewCmds era) forall a b. (a -> b) -> a -> b $ [String] -> String forall a. Monoid a => [a] -> a mconcat [ String "Commands for dealing with Shelley TextView files. Transactions, addresses etc " , String "are stored on disk as TextView files." ] ) [ Parser (TextViewCmds era) -> Maybe (Parser (TextViewCmds era)) forall a. a -> Maybe a Just (Parser (TextViewCmds era) -> Maybe (Parser (TextViewCmds era))) -> (ParserInfo (TextViewCmds era) -> Parser (TextViewCmds era)) -> ParserInfo (TextViewCmds era) -> Maybe (Parser (TextViewCmds era)) forall b c a. (b -> c) -> (a -> b) -> a -> c . Mod CommandFields (TextViewCmds era) -> Parser (TextViewCmds era) forall a. Mod CommandFields a -> Parser a Opt.hsubparser (Mod CommandFields (TextViewCmds era) -> Parser (TextViewCmds era)) -> (ParserInfo (TextViewCmds era) -> Mod CommandFields (TextViewCmds era)) -> ParserInfo (TextViewCmds era) -> Parser (TextViewCmds era) forall b c a. (b -> c) -> (a -> b) -> a -> c . String -> ParserInfo (TextViewCmds era) -> Mod CommandFields (TextViewCmds era) forall a. String -> ParserInfo a -> Mod CommandFields a commandWithMetavar String "decode-cbor" (ParserInfo (TextViewCmds era) -> Maybe (Parser (TextViewCmds era))) -> ParserInfo (TextViewCmds era) -> Maybe (Parser (TextViewCmds era)) forall a b. (a -> b) -> a -> b $ Parser (TextViewCmds era) -> InfoMod (TextViewCmds era) -> ParserInfo (TextViewCmds era) forall a. Parser a -> InfoMod a -> ParserInfo a Opt.info ( (TextViewDecodeCborCmdArgs -> TextViewCmds era) -> Parser TextViewDecodeCborCmdArgs -> Parser (TextViewCmds era) forall a b. (a -> b) -> Parser a -> Parser b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap TextViewDecodeCborCmdArgs -> TextViewCmds era forall era. TextViewDecodeCborCmdArgs -> TextViewCmds era TextViewDecodeCborCmd (Parser TextViewDecodeCborCmdArgs -> Parser (TextViewCmds era)) -> Parser TextViewDecodeCborCmdArgs -> Parser (TextViewCmds era) forall a b. (a -> b) -> a -> b $ String -> Vary '[FormatCborHex, FormatJson, FormatText, FormatYaml] -> Maybe (File () 'Out) -> TextViewDecodeCborCmdArgs TextViewDecodeCborCmdArgs (String -> Vary '[FormatCborHex, FormatJson, FormatText, FormatYaml] -> Maybe (File () 'Out) -> TextViewDecodeCborCmdArgs) -> Parser String -> Parser (Vary '[FormatCborHex, FormatJson, FormatText, FormatYaml] -> Maybe (File () 'Out) -> TextViewDecodeCborCmdArgs) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Parser String pCBORInFile Parser (Vary '[FormatCborHex, FormatJson, FormatText, FormatYaml] -> Maybe (File () 'Out) -> TextViewDecodeCborCmdArgs) -> Parser (Vary '[FormatCborHex, FormatJson, FormatText, FormatYaml]) -> Parser (Maybe (File () 'Out) -> TextViewDecodeCborCmdArgs) forall a b. Parser (a -> b) -> Parser a -> Parser b forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> String -> [Flag (Vary '[FormatCborHex, FormatJson, FormatText, FormatYaml])] -> Parser (Vary '[FormatCborHex, FormatJson, FormatText, FormatYaml]) forall (fs :: [*]). String -> [Flag (Vary fs)] -> Parser (Vary fs) pFormatFlags String "text view info output format" [ Flag (Vary '[FormatCborHex, FormatJson, FormatText, FormatYaml]) forall (fs :: [*]). (FormatCborHex :| fs) => Flag (Vary fs) flagFormatCborHex , Flag (Vary '[FormatCborHex, FormatJson, FormatText, FormatYaml]) forall (fs :: [*]). (FormatJson :| fs) => Flag (Vary fs) flagFormatJson , Flag (Vary '[FormatCborHex, FormatJson, FormatText, FormatYaml]) forall (fs :: [*]). (FormatText :| fs) => Flag (Vary fs) flagFormatText Flag (Vary '[FormatCborHex, FormatJson, FormatText, FormatYaml]) -> (Flag (Vary '[FormatCborHex, FormatJson, FormatText, FormatYaml]) -> Flag (Vary '[FormatCborHex, FormatJson, FormatText, FormatYaml])) -> Flag (Vary '[FormatCborHex, FormatJson, FormatText, FormatYaml]) forall a b. a -> (a -> b) -> b & Flag (Vary '[FormatCborHex, FormatJson, FormatText, FormatYaml]) -> Flag (Vary '[FormatCborHex, FormatJson, FormatText, FormatYaml]) forall a. Flag a -> Flag a setDefault , Flag (Vary '[FormatCborHex, FormatJson, FormatText, FormatYaml]) forall (fs :: [*]). (FormatYaml :| fs) => Flag (Vary fs) flagFormatYaml ] Parser (Maybe (File () 'Out) -> TextViewDecodeCborCmdArgs) -> Parser (Maybe (File () 'Out)) -> Parser TextViewDecodeCborCmdArgs forall a b. Parser (a -> b) -> Parser a -> Parser b forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Parser (Maybe (File () 'Out)) forall content. Parser (Maybe (File content 'Out)) pMaybeOutputFile ) (InfoMod (TextViewCmds era) -> ParserInfo (TextViewCmds era)) -> InfoMod (TextViewCmds era) -> ParserInfo (TextViewCmds era) forall a b. (a -> b) -> a -> b $ String -> InfoMod (TextViewCmds era) forall a. String -> InfoMod a Opt.progDesc String "Print a TextView file as decoded CBOR." ]