{-# LANGUAGE GeneralisedNewtypeDeriving #-}
module Bcc.CLI.Cole.Commands
( ColeCommand (..)
, NodeCmd (..)
, VerificationKeyFile (..)
, NewVerificationKeyFile (..)
, CertificateFile (..)
, NewCertificateFile (..)
) where
import Bcc.Prelude
import Bcc.Chain.Update (InstallerHash (..), ProtocolVersion (..),
SoftwareVersion (..), SystemTag (..))
import Bcc.Api (NetworkId, TxIn)
import Bcc.Api.Cole (Address (..), ColeAddr, ColeEra,
ColeProtocolParametersUpdate (..), TxOut)
import Bcc.CLI.Cole.Genesis
import Bcc.CLI.Cole.Key
import Bcc.CLI.Cole.Tx
import Bcc.CLI.Types
import Bcc.CLI.Sophie.Commands (ColeKeyFormat)
data ColeCommand =
NodeCmd NodeCmd
| Genesis
NewDirectory
GenesisParameters
| PrintGenesisHash
GenesisFile
| Keygen
NewSigningKeyFile
| ToVerification
ColeKeyFormat
SigningKeyFile
NewVerificationKeyFile
| PrettySigningKeyPublic
ColeKeyFormat
SigningKeyFile
| MigrateDelegateKeyFrom
SigningKeyFile
NewSigningKeyFile
| PrintSigningKeyAddress
ColeKeyFormat
NetworkId
SigningKeyFile
| GetLocalNodeTip
NetworkId
| SubmitTx
NetworkId
TxFile
| SpendGenesisUTxO
GenesisFile
NetworkId
ColeKeyFormat
NewTxFile
SigningKeyFile
(Address ColeAddr)
[TxOut ColeEra]
| SpendUTxO
NetworkId
ColeKeyFormat
NewTxFile
SigningKeyFile
[TxIn]
[TxOut ColeEra]
| GetTxId TxFile
| ValidateCBOR
CBORObject
FilePath
| PrettyPrintCBOR
FilePath
deriving Int -> ColeCommand -> ShowS
[ColeCommand] -> ShowS
ColeCommand -> String
(Int -> ColeCommand -> ShowS)
-> (ColeCommand -> String)
-> ([ColeCommand] -> ShowS)
-> Show ColeCommand
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ColeCommand] -> ShowS
$cshowList :: [ColeCommand] -> ShowS
show :: ColeCommand -> String
$cshow :: ColeCommand -> String
showsPrec :: Int -> ColeCommand -> ShowS
$cshowsPrec :: Int -> ColeCommand -> ShowS
Show
data NodeCmd = CreateVote
NetworkId
SigningKeyFile
FilePath
Bool
FilePath
| UpdateProposal
NetworkId
SigningKeyFile
ProtocolVersion
SoftwareVersion
SystemTag
InstallerHash
FilePath
ColeProtocolParametersUpdate
| SubmitUpdateProposal
NetworkId
FilePath
| SubmitVote
NetworkId
FilePath
deriving Int -> NodeCmd -> ShowS
[NodeCmd] -> ShowS
NodeCmd -> String
(Int -> NodeCmd -> ShowS)
-> (NodeCmd -> String) -> ([NodeCmd] -> ShowS) -> Show NodeCmd
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NodeCmd] -> ShowS
$cshowList :: [NodeCmd] -> ShowS
show :: NodeCmd -> String
$cshow :: NodeCmd -> String
showsPrec :: Int -> NodeCmd -> ShowS
$cshowsPrec :: Int -> NodeCmd -> ShowS
Show
newtype NewCertificateFile
= NewCertificateFile { NewCertificateFile -> String
nFp :: FilePath }
deriving (NewCertificateFile -> NewCertificateFile -> Bool
(NewCertificateFile -> NewCertificateFile -> Bool)
-> (NewCertificateFile -> NewCertificateFile -> Bool)
-> Eq NewCertificateFile
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NewCertificateFile -> NewCertificateFile -> Bool
$c/= :: NewCertificateFile -> NewCertificateFile -> Bool
== :: NewCertificateFile -> NewCertificateFile -> Bool
$c== :: NewCertificateFile -> NewCertificateFile -> Bool
Eq, Int -> NewCertificateFile -> ShowS
[NewCertificateFile] -> ShowS
NewCertificateFile -> String
(Int -> NewCertificateFile -> ShowS)
-> (NewCertificateFile -> String)
-> ([NewCertificateFile] -> ShowS)
-> Show NewCertificateFile
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NewCertificateFile] -> ShowS
$cshowList :: [NewCertificateFile] -> ShowS
show :: NewCertificateFile -> String
$cshow :: NewCertificateFile -> String
showsPrec :: Int -> NewCertificateFile -> ShowS
$cshowsPrec :: Int -> NewCertificateFile -> ShowS
Show, String -> NewCertificateFile
(String -> NewCertificateFile) -> IsString NewCertificateFile
forall a. (String -> a) -> IsString a
fromString :: String -> NewCertificateFile
$cfromString :: String -> NewCertificateFile
IsString)