{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE GeneralisedNewtypeDeriving #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE StandaloneDeriving #-}

module Bcc.CLI.Types
  ( BalanceTxExecUnits (..)
  , CBORObject (..)
  , CertificateFile (..)
  , GenesisFile (..)
  , VestedFile (..)
  , OutputFormat (..)
  , SigningKeyFile (..)
  , SocketPath (..)
  , ScriptFile (..)
  , ScriptDataOrFile (..)
  , ScriptRedeemerOrFile
  , ScriptWitnessFiles (..)
  , ScriptDatumOrFile (..)
  , TransferDirection(..)
  , TxOutAnyEra (..)
  , TxOutChangeAddress (..)
  , UpdateProposalFile (..)
  , VerificationKeyFile (..)
  , Stakes (..)
  , Params (..)
  ) where

import           Bcc.Prelude

import           Data.Aeson (ToJSON (..), object, pairs, (.=))
import qualified Data.Aeson as Aeson
import qualified Data.Text as Text

import qualified Bcc.Chain.Slotting as Cole

import           Bcc.Api

import qualified Bcc.Ledger.Crypto as Crypto

import           Sophie.Spec.Ledger.TxBody (PoolParams (..))

-- | Specify what the CBOR file is
-- i.e a block, a tx, etc
data CBORObject = CBORBlockCole Cole.EpochSlots
                | CBORDelegationCertificateCole
                | CBORTxCole
                | CBORUpdateProposalCole
                | CBORVoteCole
                deriving Int -> CBORObject -> ShowS
[CBORObject] -> ShowS
CBORObject -> String
(Int -> CBORObject -> ShowS)
-> (CBORObject -> String)
-> ([CBORObject] -> ShowS)
-> Show CBORObject
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CBORObject] -> ShowS
$cshowList :: [CBORObject] -> ShowS
show :: CBORObject -> String
$cshow :: CBORObject -> String
showsPrec :: Int -> CBORObject -> ShowS
$cshowsPrec :: Int -> CBORObject -> ShowS
Show

-- Encompasses stake certificates, stake pool certificates,
-- genesis delegate certificates vested delegate certificates and MIR certificates.
newtype CertificateFile = CertificateFile { CertificateFile -> String
unCertificateFile :: FilePath }
                          deriving newtype (CertificateFile -> CertificateFile -> Bool
(CertificateFile -> CertificateFile -> Bool)
-> (CertificateFile -> CertificateFile -> Bool)
-> Eq CertificateFile
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CertificateFile -> CertificateFile -> Bool
$c/= :: CertificateFile -> CertificateFile -> Bool
== :: CertificateFile -> CertificateFile -> Bool
$c== :: CertificateFile -> CertificateFile -> Bool
Eq, Int -> CertificateFile -> ShowS
[CertificateFile] -> ShowS
CertificateFile -> String
(Int -> CertificateFile -> ShowS)
-> (CertificateFile -> String)
-> ([CertificateFile] -> ShowS)
-> Show CertificateFile
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CertificateFile] -> ShowS
$cshowList :: [CertificateFile] -> ShowS
show :: CertificateFile -> String
$cshow :: CertificateFile -> String
showsPrec :: Int -> CertificateFile -> ShowS
$cshowsPrec :: Int -> CertificateFile -> ShowS
Show)

newtype GenesisFile = GenesisFile
  { GenesisFile -> String
unGenesisFile :: FilePath }
  deriving stock (GenesisFile -> GenesisFile -> Bool
(GenesisFile -> GenesisFile -> Bool)
-> (GenesisFile -> GenesisFile -> Bool) -> Eq GenesisFile
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GenesisFile -> GenesisFile -> Bool
$c/= :: GenesisFile -> GenesisFile -> Bool
== :: GenesisFile -> GenesisFile -> Bool
$c== :: GenesisFile -> GenesisFile -> Bool
Eq, Eq GenesisFile
Eq GenesisFile
-> (GenesisFile -> GenesisFile -> Ordering)
-> (GenesisFile -> GenesisFile -> Bool)
-> (GenesisFile -> GenesisFile -> Bool)
-> (GenesisFile -> GenesisFile -> Bool)
-> (GenesisFile -> GenesisFile -> Bool)
-> (GenesisFile -> GenesisFile -> GenesisFile)
-> (GenesisFile -> GenesisFile -> GenesisFile)
-> Ord GenesisFile
GenesisFile -> GenesisFile -> Bool
GenesisFile -> GenesisFile -> Ordering
GenesisFile -> GenesisFile -> GenesisFile
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: GenesisFile -> GenesisFile -> GenesisFile
$cmin :: GenesisFile -> GenesisFile -> GenesisFile
max :: GenesisFile -> GenesisFile -> GenesisFile
$cmax :: GenesisFile -> GenesisFile -> GenesisFile
>= :: GenesisFile -> GenesisFile -> Bool
$c>= :: GenesisFile -> GenesisFile -> Bool
> :: GenesisFile -> GenesisFile -> Bool
$c> :: GenesisFile -> GenesisFile -> Bool
<= :: GenesisFile -> GenesisFile -> Bool
$c<= :: GenesisFile -> GenesisFile -> Bool
< :: GenesisFile -> GenesisFile -> Bool
$c< :: GenesisFile -> GenesisFile -> Bool
compare :: GenesisFile -> GenesisFile -> Ordering
$ccompare :: GenesisFile -> GenesisFile -> Ordering
$cp1Ord :: Eq GenesisFile
Ord)
  deriving newtype (String -> GenesisFile
(String -> GenesisFile) -> IsString GenesisFile
forall a. (String -> a) -> IsString a
fromString :: String -> GenesisFile
$cfromString :: String -> GenesisFile
IsString, Int -> GenesisFile -> ShowS
[GenesisFile] -> ShowS
GenesisFile -> String
(Int -> GenesisFile -> ShowS)
-> (GenesisFile -> String)
-> ([GenesisFile] -> ShowS)
-> Show GenesisFile
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GenesisFile] -> ShowS
$cshowList :: [GenesisFile] -> ShowS
show :: GenesisFile -> String
$cshow :: GenesisFile -> String
showsPrec :: Int -> GenesisFile -> ShowS
$cshowsPrec :: Int -> GenesisFile -> ShowS
Show)

instance FromJSON GenesisFile where
  parseJSON :: Value -> Parser GenesisFile
parseJSON (Aeson.String Text
genFp) = GenesisFile -> Parser GenesisFile
forall (f :: * -> *) a. Applicative f => a -> f a
pure (GenesisFile -> Parser GenesisFile)
-> (String -> GenesisFile) -> String -> Parser GenesisFile
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. String -> GenesisFile
GenesisFile (String -> Parser GenesisFile) -> String -> Parser GenesisFile
forall a b. (a -> b) -> a -> b
$ Text -> String
Text.unpack Text
genFp
  parseJSON Value
invalid = Text -> Parser GenesisFile
forall a. HasCallStack => Text -> a
panic (Text -> Parser GenesisFile) -> Text -> Parser GenesisFile
forall a b. (a -> b) -> a -> b
$ Text
"Parsing of GenesisFile failed due to type mismatch. "
                           Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"Encountered: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
Text.pack (Value -> String
forall a b. (Show a, ConvertText String b) => a -> b
show Value
invalid)

newtype VestedFile = VestedFile
  { VestedFile -> String
unVestedFile :: FilePath }
  deriving stock (VestedFile -> VestedFile -> Bool
(VestedFile -> VestedFile -> Bool)
-> (VestedFile -> VestedFile -> Bool) -> Eq VestedFile
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VestedFile -> VestedFile -> Bool
$c/= :: VestedFile -> VestedFile -> Bool
== :: VestedFile -> VestedFile -> Bool
$c== :: VestedFile -> VestedFile -> Bool
Eq, Eq VestedFile
Eq VestedFile
-> (VestedFile -> VestedFile -> Ordering)
-> (VestedFile -> VestedFile -> Bool)
-> (VestedFile -> VestedFile -> Bool)
-> (VestedFile -> VestedFile -> Bool)
-> (VestedFile -> VestedFile -> Bool)
-> (VestedFile -> VestedFile -> VestedFile)
-> (VestedFile -> VestedFile -> VestedFile)
-> Ord VestedFile
VestedFile -> VestedFile -> Bool
VestedFile -> VestedFile -> Ordering
VestedFile -> VestedFile -> VestedFile
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: VestedFile -> VestedFile -> VestedFile
$cmin :: VestedFile -> VestedFile -> VestedFile
max :: VestedFile -> VestedFile -> VestedFile
$cmax :: VestedFile -> VestedFile -> VestedFile
>= :: VestedFile -> VestedFile -> Bool
$c>= :: VestedFile -> VestedFile -> Bool
> :: VestedFile -> VestedFile -> Bool
$c> :: VestedFile -> VestedFile -> Bool
<= :: VestedFile -> VestedFile -> Bool
$c<= :: VestedFile -> VestedFile -> Bool
< :: VestedFile -> VestedFile -> Bool
$c< :: VestedFile -> VestedFile -> Bool
compare :: VestedFile -> VestedFile -> Ordering
$ccompare :: VestedFile -> VestedFile -> Ordering
$cp1Ord :: Eq VestedFile
Ord)
  deriving newtype (String -> VestedFile
(String -> VestedFile) -> IsString VestedFile
forall a. (String -> a) -> IsString a
fromString :: String -> VestedFile
$cfromString :: String -> VestedFile
IsString, Int -> VestedFile -> ShowS
[VestedFile] -> ShowS
VestedFile -> String
(Int -> VestedFile -> ShowS)
-> (VestedFile -> String)
-> ([VestedFile] -> ShowS)
-> Show VestedFile
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VestedFile] -> ShowS
$cshowList :: [VestedFile] -> ShowS
show :: VestedFile -> String
$cshow :: VestedFile -> String
showsPrec :: Int -> VestedFile -> ShowS
$cshowsPrec :: Int -> VestedFile -> ShowS
Show)

instance FromJSON VestedFile where
  parseJSON :: Value -> Parser VestedFile
parseJSON (Aeson.String Text
genFp) = VestedFile -> Parser VestedFile
forall (f :: * -> *) a. Applicative f => a -> f a
pure (VestedFile -> Parser VestedFile)
-> (String -> VestedFile) -> String -> Parser VestedFile
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. String -> VestedFile
VestedFile (String -> Parser VestedFile) -> String -> Parser VestedFile
forall a b. (a -> b) -> a -> b
$ Text -> String
Text.unpack Text
genFp
  parseJSON Value
invalid = Text -> Parser VestedFile
forall a. HasCallStack => Text -> a
panic (Text -> Parser VestedFile) -> Text -> Parser VestedFile
forall a b. (a -> b) -> a -> b
$ Text
"Parsing of VestedFile failed due to type mismatch. "
                           Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"Encountered: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
Text.pack (Value -> String
forall a b. (Show a, ConvertText String b) => a -> b
show Value
invalid)
-- | The desired output format.
data OutputFormat
  = OutputFormatHex
  | OutputFormatBech32
  deriving (OutputFormat -> OutputFormat -> Bool
(OutputFormat -> OutputFormat -> Bool)
-> (OutputFormat -> OutputFormat -> Bool) -> Eq OutputFormat
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OutputFormat -> OutputFormat -> Bool
$c/= :: OutputFormat -> OutputFormat -> Bool
== :: OutputFormat -> OutputFormat -> Bool
$c== :: OutputFormat -> OutputFormat -> Bool
Eq, Int -> OutputFormat -> ShowS
[OutputFormat] -> ShowS
OutputFormat -> String
(Int -> OutputFormat -> ShowS)
-> (OutputFormat -> String)
-> ([OutputFormat] -> ShowS)
-> Show OutputFormat
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OutputFormat] -> ShowS
$cshowList :: [OutputFormat] -> ShowS
show :: OutputFormat -> String
$cshow :: OutputFormat -> String
showsPrec :: Int -> OutputFormat -> ShowS
$cshowsPrec :: Int -> OutputFormat -> ShowS
Show)

-- | This data structure is used to allow nicely formatted output within the query stake-snapshot command.
--
-- "markPool", "setPool", "goPool" are the three ledger state stake snapshots (from most recent to least recent)
-- go is the snapshot that is used for the current epoch, set will be used in the next epoch,
-- mark for the epoch after that.  "markTotal", "setTotal", "goTotal" record the total active stake for each snapshot.
--
-- This information can be used by community tools to calculate upcoming leader schedules.
data Stakes =  Stakes
  { Stakes -> Integer
markPool :: Integer
  , Stakes -> Integer
setPool :: Integer
  , Stakes -> Integer
goPool :: Integer
  , Stakes -> Integer
markTotal :: Integer
  , Stakes -> Integer
setTotal :: Integer
  , Stakes -> Integer
goTotal :: Integer
  } deriving Int -> Stakes -> ShowS
[Stakes] -> ShowS
Stakes -> String
(Int -> Stakes -> ShowS)
-> (Stakes -> String) -> ([Stakes] -> ShowS) -> Show Stakes
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Stakes] -> ShowS
$cshowList :: [Stakes] -> ShowS
show :: Stakes -> String
$cshow :: Stakes -> String
showsPrec :: Int -> Stakes -> ShowS
$cshowsPrec :: Int -> Stakes -> ShowS
Show

-- | Pretty printing for stake information
instance ToJSON Stakes where
  toJSON :: Stakes -> Value
toJSON (Stakes Integer
m Integer
s Integer
g Integer
mt Integer
st Integer
gt) = [Pair] -> Value
object
    [ Text
"poolStakeMark" Text -> Integer -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Integer
m
    , Text
"poolStakeSet" Text -> Integer -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Integer
s
    , Text
"poolStakeGo" Text -> Integer -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Integer
g
    , Text
"activeStakeMark" Text -> Integer -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Integer
mt
    , Text
"activeStakeSet" Text -> Integer -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Integer
st
    , Text
"activeStakeGo" Text -> Integer -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Integer
gt
    ]

  toEncoding :: Stakes -> Encoding
toEncoding  (Stakes Integer
m Integer
s Integer
g Integer
mt Integer
st Integer
gt) = Series -> Encoding
pairs (Series -> Encoding) -> Series -> Encoding
forall a b. (a -> b) -> a -> b
$ [Series] -> Series
forall a. Monoid a => [a] -> a
mconcat
    [ Text
"poolStakeMark" Text -> Integer -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Integer
m
    , Text
"poolStakeSet" Text -> Integer -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Integer
s
    , Text
"poolStakeGo" Text -> Integer -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Integer
g
    , Text
"activeStakeMark" Text -> Integer -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Integer
mt
    , Text
"activeStakeSet" Text -> Integer -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Integer
st
    , Text
"activeStakeGo" Text -> Integer -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Integer
gt
    ]

-- | This data structure is used to allow nicely formatted output in the query pool-params command.
-- params are the current pool parameter settings, futureparams are new parameters, retiringEpoch is the
-- epoch that has been set for pool retirement.  Any of these may be Nothing.
data Params crypto = Params
  { Params crypto -> Maybe (PoolParams crypto)
poolParameters :: Maybe (PoolParams crypto)
  , Params crypto -> Maybe (PoolParams crypto)
futurePoolParameters :: Maybe (PoolParams crypto)
  , Params crypto -> Maybe EpochNo
retiringEpoch :: Maybe EpochNo
  } deriving Int -> Params crypto -> ShowS
[Params crypto] -> ShowS
Params crypto -> String
(Int -> Params crypto -> ShowS)
-> (Params crypto -> String)
-> ([Params crypto] -> ShowS)
-> Show (Params crypto)
forall crypto. Int -> Params crypto -> ShowS
forall crypto. [Params crypto] -> ShowS
forall crypto. Params crypto -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Params crypto] -> ShowS
$cshowList :: forall crypto. [Params crypto] -> ShowS
show :: Params crypto -> String
$cshow :: forall crypto. Params crypto -> String
showsPrec :: Int -> Params crypto -> ShowS
$cshowsPrec :: forall crypto. Int -> Params crypto -> ShowS
Show

-- | Pretty printing for pool parameters
instance Crypto.Crypto crypto =>  ToJSON (Params crypto) where
  toJSON :: Params crypto -> Value
toJSON (Params Maybe (PoolParams crypto)
p Maybe (PoolParams crypto)
fp Maybe EpochNo
r) = [Pair] -> Value
object
    [ Text
"poolParams" Text -> Maybe (PoolParams crypto) -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Maybe (PoolParams crypto)
p
    , Text
"futurePoolParams" Text -> Maybe (PoolParams crypto) -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Maybe (PoolParams crypto)
fp
    , Text
"retiring" Text -> Maybe EpochNo -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Maybe EpochNo
r
    ]

  toEncoding :: Params crypto -> Encoding
toEncoding (Params Maybe (PoolParams crypto)
p Maybe (PoolParams crypto)
fp Maybe EpochNo
r) = Series -> Encoding
pairs (Series -> Encoding) -> Series -> Encoding
forall a b. (a -> b) -> a -> b
$ [Series] -> Series
forall a. Monoid a => [a] -> a
mconcat
    [ Text
"poolParams" Text -> Maybe (PoolParams crypto) -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Maybe (PoolParams crypto)
p
    , Text
"futurePoolParams" Text -> Maybe (PoolParams crypto) -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Maybe (PoolParams crypto)
fp
    , Text
"retiring" Text -> Maybe EpochNo -> Series
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Maybe EpochNo
r
    ]

newtype SigningKeyFile = SigningKeyFile
  { SigningKeyFile -> String
unSigningKeyFile :: FilePath }
  deriving stock (SigningKeyFile -> SigningKeyFile -> Bool
(SigningKeyFile -> SigningKeyFile -> Bool)
-> (SigningKeyFile -> SigningKeyFile -> Bool) -> Eq SigningKeyFile
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SigningKeyFile -> SigningKeyFile -> Bool
$c/= :: SigningKeyFile -> SigningKeyFile -> Bool
== :: SigningKeyFile -> SigningKeyFile -> Bool
$c== :: SigningKeyFile -> SigningKeyFile -> Bool
Eq, Eq SigningKeyFile
Eq SigningKeyFile
-> (SigningKeyFile -> SigningKeyFile -> Ordering)
-> (SigningKeyFile -> SigningKeyFile -> Bool)
-> (SigningKeyFile -> SigningKeyFile -> Bool)
-> (SigningKeyFile -> SigningKeyFile -> Bool)
-> (SigningKeyFile -> SigningKeyFile -> Bool)
-> (SigningKeyFile -> SigningKeyFile -> SigningKeyFile)
-> (SigningKeyFile -> SigningKeyFile -> SigningKeyFile)
-> Ord SigningKeyFile
SigningKeyFile -> SigningKeyFile -> Bool
SigningKeyFile -> SigningKeyFile -> Ordering
SigningKeyFile -> SigningKeyFile -> SigningKeyFile
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: SigningKeyFile -> SigningKeyFile -> SigningKeyFile
$cmin :: SigningKeyFile -> SigningKeyFile -> SigningKeyFile
max :: SigningKeyFile -> SigningKeyFile -> SigningKeyFile
$cmax :: SigningKeyFile -> SigningKeyFile -> SigningKeyFile
>= :: SigningKeyFile -> SigningKeyFile -> Bool
$c>= :: SigningKeyFile -> SigningKeyFile -> Bool
> :: SigningKeyFile -> SigningKeyFile -> Bool
$c> :: SigningKeyFile -> SigningKeyFile -> Bool
<= :: SigningKeyFile -> SigningKeyFile -> Bool
$c<= :: SigningKeyFile -> SigningKeyFile -> Bool
< :: SigningKeyFile -> SigningKeyFile -> Bool
$c< :: SigningKeyFile -> SigningKeyFile -> Bool
compare :: SigningKeyFile -> SigningKeyFile -> Ordering
$ccompare :: SigningKeyFile -> SigningKeyFile -> Ordering
$cp1Ord :: Eq SigningKeyFile
Ord)
  deriving newtype (String -> SigningKeyFile
(String -> SigningKeyFile) -> IsString SigningKeyFile
forall a. (String -> a) -> IsString a
fromString :: String -> SigningKeyFile
$cfromString :: String -> SigningKeyFile
IsString, Int -> SigningKeyFile -> ShowS
[SigningKeyFile] -> ShowS
SigningKeyFile -> String
(Int -> SigningKeyFile -> ShowS)
-> (SigningKeyFile -> String)
-> ([SigningKeyFile] -> ShowS)
-> Show SigningKeyFile
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SigningKeyFile] -> ShowS
$cshowList :: [SigningKeyFile] -> ShowS
show :: SigningKeyFile -> String
$cshow :: SigningKeyFile -> String
showsPrec :: Int -> SigningKeyFile -> ShowS
$cshowsPrec :: Int -> SigningKeyFile -> ShowS
Show)

newtype SocketPath = SocketPath { SocketPath -> String
unSocketPath :: FilePath }

newtype UpdateProposalFile = UpdateProposalFile { UpdateProposalFile -> String
unUpdateProposalFile :: FilePath }
                             deriving newtype (UpdateProposalFile -> UpdateProposalFile -> Bool
(UpdateProposalFile -> UpdateProposalFile -> Bool)
-> (UpdateProposalFile -> UpdateProposalFile -> Bool)
-> Eq UpdateProposalFile
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateProposalFile -> UpdateProposalFile -> Bool
$c/= :: UpdateProposalFile -> UpdateProposalFile -> Bool
== :: UpdateProposalFile -> UpdateProposalFile -> Bool
$c== :: UpdateProposalFile -> UpdateProposalFile -> Bool
Eq, Int -> UpdateProposalFile -> ShowS
[UpdateProposalFile] -> ShowS
UpdateProposalFile -> String
(Int -> UpdateProposalFile -> ShowS)
-> (UpdateProposalFile -> String)
-> ([UpdateProposalFile] -> ShowS)
-> Show UpdateProposalFile
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateProposalFile] -> ShowS
$cshowList :: [UpdateProposalFile] -> ShowS
show :: UpdateProposalFile -> String
$cshow :: UpdateProposalFile -> String
showsPrec :: Int -> UpdateProposalFile -> ShowS
$cshowsPrec :: Int -> UpdateProposalFile -> ShowS
Show)

newtype VerificationKeyFile
  = VerificationKeyFile { VerificationKeyFile -> String
unVerificationKeyFile :: FilePath }
  deriving (VerificationKeyFile -> VerificationKeyFile -> Bool
(VerificationKeyFile -> VerificationKeyFile -> Bool)
-> (VerificationKeyFile -> VerificationKeyFile -> Bool)
-> Eq VerificationKeyFile
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VerificationKeyFile -> VerificationKeyFile -> Bool
$c/= :: VerificationKeyFile -> VerificationKeyFile -> Bool
== :: VerificationKeyFile -> VerificationKeyFile -> Bool
$c== :: VerificationKeyFile -> VerificationKeyFile -> Bool
Eq, Int -> VerificationKeyFile -> ShowS
[VerificationKeyFile] -> ShowS
VerificationKeyFile -> String
(Int -> VerificationKeyFile -> ShowS)
-> (VerificationKeyFile -> String)
-> ([VerificationKeyFile] -> ShowS)
-> Show VerificationKeyFile
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VerificationKeyFile] -> ShowS
$cshowList :: [VerificationKeyFile] -> ShowS
show :: VerificationKeyFile -> String
$cshow :: VerificationKeyFile -> String
showsPrec :: Int -> VerificationKeyFile -> ShowS
$cshowsPrec :: Int -> VerificationKeyFile -> ShowS
Show)

newtype ScriptFile = ScriptFile { ScriptFile -> String
unScriptFile :: FilePath }
                     deriving (ScriptFile -> ScriptFile -> Bool
(ScriptFile -> ScriptFile -> Bool)
-> (ScriptFile -> ScriptFile -> Bool) -> Eq ScriptFile
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ScriptFile -> ScriptFile -> Bool
$c/= :: ScriptFile -> ScriptFile -> Bool
== :: ScriptFile -> ScriptFile -> Bool
$c== :: ScriptFile -> ScriptFile -> Bool
Eq, Int -> ScriptFile -> ShowS
[ScriptFile] -> ShowS
ScriptFile -> String
(Int -> ScriptFile -> ShowS)
-> (ScriptFile -> String)
-> ([ScriptFile] -> ShowS)
-> Show ScriptFile
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ScriptFile] -> ShowS
$cshowList :: [ScriptFile] -> ShowS
show :: ScriptFile -> String
$cshow :: ScriptFile -> String
showsPrec :: Int -> ScriptFile -> ShowS
$cshowsPrec :: Int -> ScriptFile -> ShowS
Show)

data ScriptDataOrFile = ScriptDataFile  FilePath   -- ^ By reference to a file
                      | ScriptDataValue ScriptData -- ^ By value
  deriving (ScriptDataOrFile -> ScriptDataOrFile -> Bool
(ScriptDataOrFile -> ScriptDataOrFile -> Bool)
-> (ScriptDataOrFile -> ScriptDataOrFile -> Bool)
-> Eq ScriptDataOrFile
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ScriptDataOrFile -> ScriptDataOrFile -> Bool
$c/= :: ScriptDataOrFile -> ScriptDataOrFile -> Bool
== :: ScriptDataOrFile -> ScriptDataOrFile -> Bool
$c== :: ScriptDataOrFile -> ScriptDataOrFile -> Bool
Eq, Int -> ScriptDataOrFile -> ShowS
[ScriptDataOrFile] -> ShowS
ScriptDataOrFile -> String
(Int -> ScriptDataOrFile -> ShowS)
-> (ScriptDataOrFile -> String)
-> ([ScriptDataOrFile] -> ShowS)
-> Show ScriptDataOrFile
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ScriptDataOrFile] -> ShowS
$cshowList :: [ScriptDataOrFile] -> ShowS
show :: ScriptDataOrFile -> String
$cshow :: ScriptDataOrFile -> String
showsPrec :: Int -> ScriptDataOrFile -> ShowS
$cshowsPrec :: Int -> ScriptDataOrFile -> ShowS
Show)

type ScriptRedeemerOrFile = ScriptDataOrFile

-- | This type is like 'ScriptWitness', but the file paths from which to load
-- the script witness data representation.
--
-- It is era-independent, but witness context-dependent.
--
data ScriptWitnessFiles witctx where
     SimpleScriptWitnessFile  :: ScriptFile
                              -> ScriptWitnessFiles witctx

     ZerepochScriptWitnessFiles :: ScriptFile
                              -> ScriptDatumOrFile witctx
                              -> ScriptRedeemerOrFile
                              -> ExecutionUnits
                              -> ScriptWitnessFiles witctx

deriving instance Show (ScriptWitnessFiles witctx)

data ScriptDatumOrFile witctx where
     ScriptDatumOrFileForTxIn    :: ScriptDataOrFile
                                 -> ScriptDatumOrFile WitCtxTxIn

     NoScriptDatumOrFileForMint  :: ScriptDatumOrFile WitCtxMint
     NoScriptDatumOrFileForStake :: ScriptDatumOrFile WitCtxStake

deriving instance Show (ScriptDatumOrFile witctx)


-- | Determines the direction in which the MIR certificate will transfer BCC.
data TransferDirection = TransferToReserves | TransferToTreasury
                         deriving Int -> TransferDirection -> ShowS
[TransferDirection] -> ShowS
TransferDirection -> String
(Int -> TransferDirection -> ShowS)
-> (TransferDirection -> String)
-> ([TransferDirection] -> ShowS)
-> Show TransferDirection
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TransferDirection] -> ShowS
$cshowList :: [TransferDirection] -> ShowS
show :: TransferDirection -> String
$cshow :: TransferDirection -> String
showsPrec :: Int -> TransferDirection -> ShowS
$cshowsPrec :: Int -> TransferDirection -> ShowS
Show

-- | A TxOut value that is the superset of possibilities for any era: any
-- address type and allowing multi-asset values. This is used as the type for
-- values passed on the command line. It can be converted into the
-- era-dependent 'TxOutValue' type.
--
data TxOutAnyEra = TxOutAnyEra
                     AddressAny
                     Value
                     (Maybe (Hash ScriptData))
  deriving (TxOutAnyEra -> TxOutAnyEra -> Bool
(TxOutAnyEra -> TxOutAnyEra -> Bool)
-> (TxOutAnyEra -> TxOutAnyEra -> Bool) -> Eq TxOutAnyEra
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TxOutAnyEra -> TxOutAnyEra -> Bool
$c/= :: TxOutAnyEra -> TxOutAnyEra -> Bool
== :: TxOutAnyEra -> TxOutAnyEra -> Bool
$c== :: TxOutAnyEra -> TxOutAnyEra -> Bool
Eq, Int -> TxOutAnyEra -> ShowS
[TxOutAnyEra] -> ShowS
TxOutAnyEra -> String
(Int -> TxOutAnyEra -> ShowS)
-> (TxOutAnyEra -> String)
-> ([TxOutAnyEra] -> ShowS)
-> Show TxOutAnyEra
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TxOutAnyEra] -> ShowS
$cshowList :: [TxOutAnyEra] -> ShowS
show :: TxOutAnyEra -> String
$cshow :: TxOutAnyEra -> String
showsPrec :: Int -> TxOutAnyEra -> ShowS
$cshowsPrec :: Int -> TxOutAnyEra -> ShowS
Show)

-- | A partially-specified transaction output indented to use as a change
-- output.
--
-- It does not specify a value, since this will be worked out automatically.
--
-- It does not use any script data hash, since that's generally not used for
-- change outputs.
--
newtype TxOutChangeAddress = TxOutChangeAddress AddressAny
  deriving (TxOutChangeAddress -> TxOutChangeAddress -> Bool
(TxOutChangeAddress -> TxOutChangeAddress -> Bool)
-> (TxOutChangeAddress -> TxOutChangeAddress -> Bool)
-> Eq TxOutChangeAddress
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TxOutChangeAddress -> TxOutChangeAddress -> Bool
$c/= :: TxOutChangeAddress -> TxOutChangeAddress -> Bool
== :: TxOutChangeAddress -> TxOutChangeAddress -> Bool
$c== :: TxOutChangeAddress -> TxOutChangeAddress -> Bool
Eq, Int -> TxOutChangeAddress -> ShowS
[TxOutChangeAddress] -> ShowS
TxOutChangeAddress -> String
(Int -> TxOutChangeAddress -> ShowS)
-> (TxOutChangeAddress -> String)
-> ([TxOutChangeAddress] -> ShowS)
-> Show TxOutChangeAddress
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TxOutChangeAddress] -> ShowS
$cshowList :: [TxOutChangeAddress] -> ShowS
show :: TxOutChangeAddress -> String
$cshow :: TxOutChangeAddress -> String
showsPrec :: Int -> TxOutChangeAddress -> ShowS
$cshowsPrec :: Int -> TxOutChangeAddress -> ShowS
Show)

-- | A flag that differentiates between automatically
-- and manually balancing a tx.
data BalanceTxExecUnits = AutoBalance | ManualBalance