{-# LANGUAGE GeneralisedNewtypeDeriving #-}

module Cardano.CLI.Byron.Commands
  ( ByronCommand (..)
  , NodeCmd (..)
  , VerificationKeyFile (..)
  , NewVerificationKeyFile (..)
  , CertificateFile (..)
  , NewCertificateFile (..)
  ) where

import           Data.String (IsString)

import           Cardano.Chain.Update (InstallerHash (..), ProtocolVersion (..),
                   SoftwareVersion (..), SystemTag (..))

import           Cardano.Api hiding (GenesisParameters)
import           Cardano.Api.Byron hiding (GenesisParameters)

import           Cardano.CLI.Byron.Genesis
import           Cardano.CLI.Byron.Key
import           Cardano.CLI.Byron.Tx
import           Cardano.CLI.Types

import           Cardano.CLI.Shelley.Commands (ByronKeyFormat)

data ByronCommand =

  --- Node Related Commands ---
    NodeCmd NodeCmd

  --- Genesis Related Commands ---
  | Genesis
        NewDirectory
        GenesisParameters

  | PrintGenesisHash
        GenesisFile

  --- Key Related Commands ---
  | Keygen
        NewSigningKeyFile

  | ToVerification
        ByronKeyFormat
        SigningKeyFile
        NewVerificationKeyFile

  | PrettySigningKeyPublic
        ByronKeyFormat
        SigningKeyFile

  | MigrateDelegateKeyFrom
        SigningKeyFile
        -- ^ Old key
        NewSigningKeyFile
        -- ^ New Key

  | PrintSigningKeyAddress
        ByronKeyFormat
        NetworkId
        SigningKeyFile

  | GetLocalNodeTip
        NetworkId

    -----------------------------------

  | SubmitTx
        NetworkId
        TxFile
        -- ^ Filepath of transaction to submit.

  | SpendGenesisUTxO
        GenesisFile
        NetworkId
        ByronKeyFormat
        NewTxFile
        -- ^ Filepath of the newly created transaction.
        SigningKeyFile
        -- ^ Signing key of genesis UTxO owner.
        (Address ByronAddr)
        -- ^ Genesis UTxO address.
        [TxOut CtxTx ByronEra]
        -- ^ Tx output.
  | SpendUTxO
        NetworkId
        ByronKeyFormat
        NewTxFile
        -- ^ Filepath of the newly created transaction.
        SigningKeyFile
        -- ^ Signing key of Tx underwriter.
        [TxIn]
        -- ^ Inputs available for spending to the Tx underwriter's key.
        [TxOut CtxTx ByronEra]
        -- ^ Genesis UTxO output Address.

  | GetTxId TxFile

    --- Misc Commands ---

  | ValidateCBOR
        CBORObject
        -- ^ Type of the CBOR object
        FilePath

  | PrettyPrintCBOR
        FilePath
  deriving Int -> ByronCommand -> ShowS
[ByronCommand] -> ShowS
ByronCommand -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ByronCommand] -> ShowS
$cshowList :: [ByronCommand] -> ShowS
show :: ByronCommand -> String
$cshow :: ByronCommand -> String
showsPrec :: Int -> ByronCommand -> ShowS
$cshowsPrec :: Int -> ByronCommand -> ShowS
Show


data NodeCmd = CreateVote
               NetworkId
               SigningKeyFile
               FilePath -- filepath to update proposal
               Bool
               FilePath
             | UpdateProposal
               NetworkId
               SigningKeyFile
               ProtocolVersion
               SoftwareVersion
               SystemTag
               InstallerHash
               FilePath
               ByronProtocolParametersUpdate
             | SubmitUpdateProposal
               NetworkId
               FilePath
               -- ^ Update proposal filepath.
             | SubmitVote
               NetworkId
               FilePath
               -- ^ Vote filepath.
              deriving Int -> NodeCmd -> ShowS
[NodeCmd] -> ShowS
NodeCmd -> String
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
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
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
forall a. (String -> a) -> IsString a
fromString :: String -> NewCertificateFile
$cfromString :: String -> NewCertificateFile
IsString)