module Morley.Client.Parser
( clientParser
, clientConfigParser
, argsRawParser
, mbContractFileOption
, contractNameOption
, feeOption
, baseUrlReader
, OriginateArgs(..)
, originateArgsOption
, parserInfo
) where
import Control.Exception.Safe (throwString)
import Data.Aeson qualified as Aeson
import Data.Default (def)
import Data.Singletons (demote, fromSing)
import Data.Type.Equality (pattern Refl)
import Fmt (blockListF, build, nameF, pretty, (+|), (|+))
import Options.Applicative
(ReadM, eitherReader, help, long, metavar, option, short, strOption, subparser, value)
import Options.Applicative qualified as Opt
import Servant.Client (BaseUrl(..), parseBaseUrl)
import Morley.App.CLI qualified as Morley
import Morley.CLI
(addressOrAliasOption, keyHashOption, mutezOption, parserInfo, someAddressOrAliasOption,
valueOption)
import Morley.Client.Action
import Morley.Client.Full
import Morley.Client.RPC
import Morley.Client.TezosClient
import Morley.Client.Util (extractAddressesFromValue)
import Morley.Micheline (fromExpression, toExpression, unStringEncode)
import Morley.Michelson.Runtime (prepareContract)
import Morley.Michelson.TypeCheck qualified as TC
import Morley.Michelson.Typed (Contract, Contract'(..), SomeContract(..))
import Morley.Michelson.Typed qualified as T
import Morley.Michelson.Typed.Value (Value'(..))
import Morley.Michelson.Untyped qualified as U
import Morley.Tezos.Address
import Morley.Tezos.Address.Alias
import Morley.Tezos.Address.Kinds
import Morley.Tezos.Core
import Morley.Tezos.Crypto
import Morley.Util.CLI (mkCLOptionParser, mkCommandParser)
import Morley.Util.Constrained
import Morley.Util.Exception (throwLeft)
import Morley.Util.Named
mkCommandParser' :: String -> String -> Opt.Parser a -> Opt.Mod Opt.CommandFields a
mkCommandParser' :: forall a. FilePath -> FilePath -> Parser a -> Mod CommandFields a
mkCommandParser' = (Parser a -> FilePath -> Mod CommandFields a)
-> FilePath -> Parser a -> Mod CommandFields a
forall a b c. (a -> b -> c) -> b -> a -> c
flip ((Parser a -> FilePath -> Mod CommandFields a)
-> FilePath -> Parser a -> Mod CommandFields a)
-> (FilePath -> Parser a -> FilePath -> Mod CommandFields a)
-> FilePath
-> FilePath
-> Parser a
-> Mod CommandFields a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> Parser a -> FilePath -> Mod CommandFields a
forall a. FilePath -> Parser a -> FilePath -> Mod CommandFields a
mkCommandParser
type ClientMCmd = Opt.Mod Opt.CommandFields (MorleyClientM ())
originateCmd :: ClientMCmd
originateCmd :: Mod CommandFields (MorleyClientM ())
originateCmd = FilePath
-> FilePath
-> Parser (MorleyClientM ())
-> Mod CommandFields (MorleyClientM ())
forall a. FilePath -> FilePath -> Parser a -> Mod CommandFields a
mkCommandParser' FilePath
"originate" FilePath
"Originate passed contract on real network." do
OriginateArgs
oas <- Parser OriginateArgs
originateArgsOption
pure let OriginateArgs{Maybe FilePath
Maybe Mutez
Maybe KeyHash
Mutez
AddressOrAlias 'AddressKindImplicit
ContractAlias
Value
oaMbContractFile :: Maybe FilePath
oaContractName :: ContractAlias
oaInitialBalance :: Mutez
oaInitialStorage :: Value
oaOriginateFrom :: AddressOrAlias 'AddressKindImplicit
oaMbFee :: Maybe Mutez
oaDelegate :: Maybe KeyHash
oaMbContractFile :: OriginateArgs -> Maybe FilePath
oaContractName :: OriginateArgs -> ContractAlias
oaInitialBalance :: OriginateArgs -> Mutez
oaInitialStorage :: OriginateArgs -> Value
oaOriginateFrom :: OriginateArgs -> AddressOrAlias 'AddressKindImplicit
oaMbFee :: OriginateArgs -> Maybe Mutez
oaDelegate :: OriginateArgs -> Maybe KeyHash
..} = OriginateArgs
oas in do
Contract
contract <- IO Contract -> MorleyClientM Contract
forall a. IO a -> MorleyClientM a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Contract -> MorleyClientM Contract)
-> IO Contract -> MorleyClientM Contract
forall a b. (a -> b) -> a -> b
$ Maybe FilePath -> IO Contract
prepareContract Maybe FilePath
oaMbContractFile
let originator :: AddressOrAlias 'AddressKindImplicit
originator = AddressOrAlias 'AddressKindImplicit
oaOriginateFrom
AddressWithAlias 'AddressKindImplicit
originatorAA <- AddressOrAlias 'AddressKindImplicit
-> MorleyClientM
(ResolvedAddressAndAlias (AddressOrAlias 'AddressKindImplicit))
forall addressOrAlias (m :: * -> *).
(HasTezosClient m, MonadThrow m, Resolve addressOrAlias) =>
addressOrAlias -> m (ResolvedAddressAndAlias addressOrAlias)
resolveAddressWithAlias AddressOrAlias 'AddressKindImplicit
originator
(OperationHash
operationHash, KindedAddress 'AddressKindContract
contractAddr) <-
AliasBehavior
-> ContractAlias
-> AddressWithAlias 'AddressKindImplicit
-> Mutez
-> Contract
-> Value
-> Maybe Mutez
-> Maybe KeyHash
-> MorleyClientM
(OperationHash, KindedAddress 'AddressKindContract)
forall (m :: * -> *) env.
(HasTezosRpc m, HasTezosClient m, WithClientLog env m) =>
AliasBehavior
-> ContractAlias
-> AddressWithAlias 'AddressKindImplicit
-> Mutez
-> Contract
-> Value
-> Maybe Mutez
-> Maybe KeyHash
-> m (OperationHash, KindedAddress 'AddressKindContract)
originateUntypedContract AliasBehavior
OverwriteDuplicateAlias ContractAlias
oaContractName AddressWithAlias 'AddressKindImplicit
originatorAA Mutez
oaInitialBalance
Contract
contract Value
oaInitialStorage Maybe Mutez
oaMbFee Maybe KeyHash
oaDelegate
Text -> MorleyClientM ()
forall (m :: * -> *). MonadIO m => Text -> m ()
putTextLn Text
"Contract was successfully deployed."
Text -> MorleyClientM ()
forall (m :: * -> *). MonadIO m => Text -> m ()
putTextLn (Text -> MorleyClientM ()) -> Text -> MorleyClientM ()
forall a b. (a -> b) -> a -> b
$ Text
"Operation hash: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> OperationHash -> Text
forall a b. (Buildable a, FromDoc b) => a -> b
pretty OperationHash
operationHash
Text -> MorleyClientM ()
forall (m :: * -> *). MonadIO m => Text -> m ()
putTextLn (Text -> MorleyClientM ()) -> Text -> MorleyClientM ()
forall a b. (a -> b) -> a -> b
$ Text
"Contract address: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> KindedAddress 'AddressKindContract -> Text
forall (kind :: AddressKind). KindedAddress kind -> Text
formatAddress KindedAddress 'AddressKindContract
contractAddr
transferCmd :: ClientMCmd
transferCmd :: Mod CommandFields (MorleyClientM ())
transferCmd = FilePath
-> FilePath
-> Parser (MorleyClientM ())
-> Mod CommandFields (MorleyClientM ())
forall a. FilePath -> FilePath -> Parser a -> Mod CommandFields a
mkCommandParser' FilePath
"transfer"
FilePath
"Perform a transfer to the given contract with given amount and parameter." do
AddressOrAlias 'AddressKindImplicit
taSender <- forall (kind :: AddressKind).
(SingI kind, L1AddressKind kind) =>
Maybe (AddressOrAlias kind)
-> NamedF Identity FilePath "name"
-> NamedF Identity FilePath "help"
-> Parser (AddressOrAlias kind)
addressOrAliasOption @'AddressKindImplicit Maybe (AddressOrAlias 'AddressKindImplicit)
forall a. Maybe a
Nothing
(NamedF Identity FilePath "name"
-> NamedF Identity FilePath "help"
-> Parser (AddressOrAlias 'AddressKindImplicit))
-> Param (NamedF Identity FilePath "name")
-> NamedF Identity FilePath "help"
-> Parser (AddressOrAlias 'AddressKindImplicit)
forall p fn fn'. WithParam p fn fn' => fn -> Param p -> fn'
! FilePath -> Param (NamedF Identity FilePath "name")
forall (x :: Symbol) a. IsLabel x a => a
#name FilePath
"from"
(NamedF Identity FilePath "help"
-> Parser (AddressOrAlias 'AddressKindImplicit))
-> Param (NamedF Identity FilePath "help")
-> Parser (AddressOrAlias 'AddressKindImplicit)
forall p fn fn'. WithParam p fn fn' => fn -> Param p -> fn'
! FilePath -> Param (NamedF Identity FilePath "help")
forall (x :: Symbol) a. IsLabel x a => a
#help FilePath
"Address or alias from which transfer is performed."
SomeAddressOrAlias
taDestination <- Maybe SomeAddressOrAlias
-> NamedF Identity FilePath "name"
-> NamedF Identity FilePath "help"
-> Parser SomeAddressOrAlias
someAddressOrAliasOption Maybe SomeAddressOrAlias
forall a. Maybe a
Nothing
(NamedF Identity FilePath "name"
-> NamedF Identity FilePath "help" -> Parser SomeAddressOrAlias)
-> Param (NamedF Identity FilePath "name")
-> NamedF Identity FilePath "help"
-> Parser SomeAddressOrAlias
forall p fn fn'. WithParam p fn fn' => fn -> Param p -> fn'
! FilePath -> Param (NamedF Identity FilePath "name")
forall (x :: Symbol) a. IsLabel x a => a
#name FilePath
"to"
(NamedF Identity FilePath "help" -> Parser SomeAddressOrAlias)
-> Param (NamedF Identity FilePath "help")
-> Parser SomeAddressOrAlias
forall p fn fn'. WithParam p fn fn' => fn -> Param p -> fn'
! FilePath -> Param (NamedF Identity FilePath "help")
forall (x :: Symbol) a. IsLabel x a => a
#help FilePath
"Address or alias of the transfer's destination."
Mutez
taAmount <- Maybe Mutez
-> NamedF Identity FilePath "name"
-> NamedF Identity FilePath "help"
-> Parser Mutez
mutezOption (Mutez -> Maybe Mutez
forall a. a -> Maybe a
Just Mutez
zeroMutez)
(NamedF Identity FilePath "name"
-> NamedF Identity FilePath "help" -> Parser Mutez)
-> Param (NamedF Identity FilePath "name")
-> NamedF Identity FilePath "help"
-> Parser Mutez
forall p fn fn'. WithParam p fn fn' => fn -> Param p -> fn'
! FilePath -> Param (NamedF Identity FilePath "name")
forall (x :: Symbol) a. IsLabel x a => a
#name FilePath
"amount"
(NamedF Identity FilePath "help" -> Parser Mutez)
-> Param (NamedF Identity FilePath "help") -> Parser Mutez
forall p fn fn'. WithParam p fn fn' => fn -> Param p -> fn'
! FilePath -> Param (NamedF Identity FilePath "help")
forall (x :: Symbol) a. IsLabel x a => a
#help FilePath
"Transfer amount."
Value
taParameter <- Maybe Value
-> NamedF Identity FilePath "name"
-> NamedF Identity FilePath "help"
-> Parser Value
valueOption Maybe Value
forall a. Maybe a
Nothing
(NamedF Identity FilePath "name"
-> NamedF Identity FilePath "help" -> Parser Value)
-> Param (NamedF Identity FilePath "name")
-> NamedF Identity FilePath "help"
-> Parser Value
forall p fn fn'. WithParam p fn fn' => fn -> Param p -> fn'
! FilePath -> Param (NamedF Identity FilePath "name")
forall (x :: Symbol) a. IsLabel x a => a
#name FilePath
"parameter"
(NamedF Identity FilePath "help" -> Parser Value)
-> Param (NamedF Identity FilePath "help") -> Parser Value
forall p fn fn'. WithParam p fn fn' => fn -> Param p -> fn'
! FilePath -> Param (NamedF Identity FilePath "help")
forall (x :: Symbol) a. IsLabel x a => a
#help FilePath
"Transfer parameter."
Maybe Mutez
taMbFee <- Parser (Maybe Mutez)
feeOption
pure do
ResolvedAddressAndAlias (AddressOrAlias 'AddressKindImplicit)
sendAddress <- AddressOrAlias 'AddressKindImplicit
-> MorleyClientM
(ResolvedAddressAndAlias (AddressOrAlias 'AddressKindImplicit))
forall addressOrAlias (m :: * -> *).
(HasTezosClient m, MonadThrow m, Resolve addressOrAlias) =>
addressOrAlias -> m (ResolvedAddressAndAlias addressOrAlias)
resolveAddressWithAlias AddressOrAlias 'AddressKindImplicit
taSender
Constrained
(ConstrainAddressKind
'[ 'AddressKindImplicit, 'AddressKindContract])
KindedAddress
destAddress <- SomeAddressOrAlias
-> MorleyClientM (ResolvedAddress SomeAddressOrAlias)
forall addressOrAlias (m :: * -> *).
(HasTezosClient m, MonadThrow m, Resolve addressOrAlias) =>
addressOrAlias -> m (ResolvedAddress addressOrAlias)
resolveAddress SomeAddressOrAlias
taDestination
(OperationHash
operationHash, [WithSource EventOperation]
contractEvents) :: (OperationHash, [WithSource EventOperation]) <-
Constrained
(ConstrainAddressKind
'[ 'AddressKindImplicit, 'AddressKindContract])
KindedAddress
-> (forall (t :: AddressKind).
ConstrainAddressKind
'[ 'AddressKindImplicit, 'AddressKindContract] t =>
KindedAddress t
-> MorleyClientM (OperationHash, [WithSource EventOperation]))
-> MorleyClientM (OperationHash, [WithSource EventOperation])
forall {k} (c :: k -> Constraint) (f :: k -> *) r.
Constrained c f -> (forall (t :: k). c t => f t -> r) -> r
withConstrained Constrained
(ConstrainAddressKind
'[ 'AddressKindImplicit, 'AddressKindContract])
KindedAddress
destAddress \case
destContract :: KindedAddress t
destContract@ContractAddress{} -> do
Contract
contract <- KindedAddress 'AddressKindContract -> MorleyClientM Contract
forall (m :: * -> *).
HasTezosRpc m =>
KindedAddress 'AddressKindContract -> m Contract
getContract KindedAddress t
KindedAddress 'AddressKindContract
destContract
SomeContract (Contract{} :: Contract cp st) <-
MorleyClientM (Either (TcError' ExpandedOp) SomeContract)
-> MorleyClientM SomeContract
forall (m :: * -> *) e a.
(MonadThrow m, Exception e) =>
m (Either e a) -> m a
throwLeft (MorleyClientM (Either (TcError' ExpandedOp) SomeContract)
-> MorleyClientM SomeContract)
-> MorleyClientM (Either (TcError' ExpandedOp) SomeContract)
-> MorleyClientM SomeContract
forall a b. (a -> b) -> a -> b
$ Either (TcError' ExpandedOp) SomeContract
-> MorleyClientM (Either (TcError' ExpandedOp) SomeContract)
forall a. a -> MorleyClientM a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either (TcError' ExpandedOp) SomeContract
-> MorleyClientM (Either (TcError' ExpandedOp) SomeContract))
-> Either (TcError' ExpandedOp) SomeContract
-> MorleyClientM (Either (TcError' ExpandedOp) SomeContract)
forall a b. (a -> b) -> a -> b
$ TypeCheckOptions
-> TypeCheckResult ExpandedOp SomeContract
-> Either (TcError' ExpandedOp) SomeContract
forall op a.
TypeCheckOptions -> TypeCheckResult op a -> Either (TcError' op) a
TC.typeCheckingWith TypeCheckOptions
forall a. Default a => a
def (TypeCheckResult ExpandedOp SomeContract
-> Either (TcError' ExpandedOp) SomeContract)
-> TypeCheckResult ExpandedOp SomeContract
-> Either (TcError' ExpandedOp) SomeContract
forall a b. (a -> b) -> a -> b
$ Contract -> TypeCheckResult ExpandedOp SomeContract
TC.typeCheckContract Contract
contract
let addrs :: [KindedAddress 'AddressKindContract]
addrs = Value -> [Address]
extractAddressesFromValue Value
taParameter [Address]
-> ([Address] -> [KindedAddress 'AddressKindContract])
-> [KindedAddress 'AddressKindContract]
forall a b. a -> (a -> b) -> b
& (Address -> Maybe (KindedAddress 'AddressKindContract))
-> [Address] -> [KindedAddress 'AddressKindContract]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe \case
MkAddress x :: KindedAddress kind
x@ContractAddress{} -> KindedAddress 'AddressKindContract
-> Maybe (KindedAddress 'AddressKindContract)
forall a. a -> Maybe a
Just KindedAddress kind
KindedAddress 'AddressKindContract
x
Address
_ -> Maybe (KindedAddress 'AddressKindContract)
forall a. Maybe a
Nothing
TcOriginatedContracts
tcOriginatedContracts <- [KindedAddress 'AddressKindContract]
-> MorleyClientM TcOriginatedContracts
forall (m :: * -> *).
HasTezosRpc m =>
[KindedAddress 'AddressKindContract] -> m TcOriginatedContracts
getContractsParameterTypes [KindedAddress 'AddressKindContract]
addrs
Value cp
parameter <- MorleyClientM (Either (TcError' ExpandedOp) (Value cp))
-> MorleyClientM (Value cp)
forall (m :: * -> *) e a.
(MonadThrow m, Exception e) =>
m (Either e a) -> m a
throwLeft (MorleyClientM (Either (TcError' ExpandedOp) (Value cp))
-> MorleyClientM (Value cp))
-> MorleyClientM (Either (TcError' ExpandedOp) (Value cp))
-> MorleyClientM (Value cp)
forall a b. (a -> b) -> a -> b
$ Either (TcError' ExpandedOp) (Value cp)
-> MorleyClientM (Either (TcError' ExpandedOp) (Value cp))
forall a. a -> MorleyClientM a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either (TcError' ExpandedOp) (Value cp)
-> MorleyClientM (Either (TcError' ExpandedOp) (Value cp)))
-> Either (TcError' ExpandedOp) (Value cp)
-> MorleyClientM (Either (TcError' ExpandedOp) (Value cp))
forall a b. (a -> b) -> a -> b
$ TypeCheckOptions
-> TypeCheckResult ExpandedOp (Value cp)
-> Either (TcError' ExpandedOp) (Value cp)
forall op a.
TypeCheckOptions -> TypeCheckResult op a -> Either (TcError' op) a
TC.typeCheckingWith TypeCheckOptions
forall a. Default a => a
def (TypeCheckResult ExpandedOp (Value cp)
-> Either (TcError' ExpandedOp) (Value cp))
-> TypeCheckResult ExpandedOp (Value cp)
-> Either (TcError' ExpandedOp) (Value cp)
forall a b. (a -> b) -> a -> b
$
forall (t :: T).
SingI t =>
TcOriginatedContracts
-> Value -> TypeCheckResult ExpandedOp (Value t)
TC.typeVerifyParameter @cp TcOriginatedContracts
tcOriginatedContracts Value
taParameter
AddressWithAlias 'AddressKindImplicit
-> KindedAddress 'AddressKindContract
-> Mutez
-> EpName
-> Value cp
-> Maybe Mutez
-> MorleyClientM (OperationHash, [WithSource EventOperation])
forall (m :: * -> *) (t :: T) env (kind :: AddressKind).
(HasTezosRpc m, HasTezosClient m, WithClientLog env m,
ParameterScope t, L1AddressKind kind) =>
AddressWithAlias 'AddressKindImplicit
-> KindedAddress kind
-> Mutez
-> EpName
-> Value t
-> Maybe Mutez
-> m (OperationHash, [WithSource EventOperation])
transfer AddressWithAlias 'AddressKindImplicit
ResolvedAddressAndAlias (AddressOrAlias 'AddressKindImplicit)
sendAddress KindedAddress t
KindedAddress 'AddressKindContract
destContract Mutez
taAmount EpName
U.DefEpName Value cp
parameter Maybe Mutez
taMbFee
destImplicit :: KindedAddress t
destImplicit@ImplicitAddress {} -> case Value
taParameter of
Value
U.ValueUnit -> AddressWithAlias 'AddressKindImplicit
-> KindedAddress 'AddressKindImplicit
-> Mutez
-> EpName
-> Value 'TUnit
-> Maybe Mutez
-> MorleyClientM (OperationHash, [WithSource EventOperation])
forall (m :: * -> *) (t :: T) env (kind :: AddressKind).
(HasTezosRpc m, HasTezosClient m, WithClientLog env m,
ParameterScope t, L1AddressKind kind) =>
AddressWithAlias 'AddressKindImplicit
-> KindedAddress kind
-> Mutez
-> EpName
-> Value t
-> Maybe Mutez
-> m (OperationHash, [WithSource EventOperation])
transfer AddressWithAlias 'AddressKindImplicit
ResolvedAddressAndAlias (AddressOrAlias 'AddressKindImplicit)
sendAddress KindedAddress t
KindedAddress 'AddressKindImplicit
destImplicit Mutez
taAmount EpName
U.DefEpName Value 'TUnit
forall (instr :: [T] -> [T] -> *). Value' instr 'TUnit
VUnit Maybe Mutez
forall a. Maybe a
Nothing
Value
_ -> FilePath
-> MorleyClientM (OperationHash, [WithSource EventOperation])
forall (m :: * -> *) a.
(MonadThrow m, HasCallStack) =>
FilePath -> m a
throwString (FilePath
"The transaction parameter must be 'Unit' "
FilePath -> FilePath -> FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath
"when transferring to an implicit account")
Text -> MorleyClientM ()
forall (m :: * -> *). MonadIO m => Text -> m ()
putTextLn (Text -> MorleyClientM ()) -> Text -> MorleyClientM ()
forall a b. (a -> b) -> a -> b
$ Text
"Transaction was successfully sent.\nOperation hash " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> OperationHash -> Text
forall a b. (Buildable a, FromDoc b) => a -> b
pretty OperationHash
operationHash Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"."
Bool -> MorleyClientM () -> MorleyClientM ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ([WithSource EventOperation] -> Bool
forall t. Container t => t -> Bool
null [WithSource EventOperation]
contractEvents) do
Text -> MorleyClientM ()
forall (m :: * -> *). MonadIO m => Text -> m ()
putTextLn (Text -> MorleyClientM ()) -> Text -> MorleyClientM ()
forall a b. (a -> b) -> a -> b
$ Text
"Additionally, the following contract events were emitted:"
Text -> MorleyClientM ()
forall (m :: * -> *). MonadIO m => Text -> m ()
putTextLn (Text -> MorleyClientM ()) -> Text -> MorleyClientM ()
forall a b. (a -> b) -> a -> b
$ Doc -> Text
forall a b. (Buildable a, FromDoc b) => a -> b
pretty (Doc -> Text) -> Doc -> Text
forall a b. (a -> b) -> a -> b
$ [WithSource EventOperation] -> Doc
forall a (f :: * -> *). (Buildable a, Foldable f) => f a -> Doc
blockListF [WithSource EventOperation]
contractEvents
getBalanceCmd :: ClientMCmd
getBalanceCmd :: Mod CommandFields (MorleyClientM ())
getBalanceCmd = FilePath
-> FilePath
-> Parser (MorleyClientM ())
-> Mod CommandFields (MorleyClientM ())
forall a. FilePath -> FilePath -> Parser a -> Mod CommandFields a
mkCommandParser' FilePath
"get-balance" FilePath
"Get balance for given address" do
SomeAddressOrAlias
addrOrAlias <- Maybe SomeAddressOrAlias
-> NamedF Identity FilePath "name"
-> NamedF Identity FilePath "help"
-> Parser SomeAddressOrAlias
someAddressOrAliasOption Maybe SomeAddressOrAlias
forall a. Maybe a
Nothing
(NamedF Identity FilePath "name"
-> NamedF Identity FilePath "help" -> Parser SomeAddressOrAlias)
-> Param (NamedF Identity FilePath "name")
-> NamedF Identity FilePath "help"
-> Parser SomeAddressOrAlias
forall p fn fn'. WithParam p fn fn' => fn -> Param p -> fn'
! FilePath -> Param (NamedF Identity FilePath "name")
forall (x :: Symbol) a. IsLabel x a => a
#name FilePath
"addr"
(NamedF Identity FilePath "help" -> Parser SomeAddressOrAlias)
-> Param (NamedF Identity FilePath "help")
-> Parser SomeAddressOrAlias
forall p fn fn'. WithParam p fn fn' => fn -> Param p -> fn'
! FilePath -> Param (NamedF Identity FilePath "help")
forall (x :: Symbol) a. IsLabel x a => a
#help FilePath
"Contract or implicit address or alias to get balance for."
pure do
Constrained KindedAddress a
addr <- SomeAddressOrAlias
-> MorleyClientM (ResolvedAddress SomeAddressOrAlias)
forall addressOrAlias (m :: * -> *).
(HasTezosClient m, MonadThrow m, Resolve addressOrAlias) =>
addressOrAlias -> m (ResolvedAddress addressOrAlias)
resolveAddress SomeAddressOrAlias
addrOrAlias
Mutez
balance <- KindedAddress a -> MorleyClientM Mutez
forall (kind :: AddressKind) (m :: * -> *).
(HasTezosRpc m, L1AddressKind kind) =>
KindedAddress kind -> m Mutez
getBalance KindedAddress a
addr
Text -> MorleyClientM ()
forall (m :: * -> *). MonadIO m => Text -> m ()
putTextLn (Text -> MorleyClientM ()) -> Text -> MorleyClientM ()
forall a b. (a -> b) -> a -> b
$ Mutez -> Text
prettyTez Mutez
balance
getBlockHeaderCmd :: ClientMCmd
= FilePath
-> FilePath
-> Parser (MorleyClientM ())
-> Mod CommandFields (MorleyClientM ())
forall a. FilePath -> FilePath -> Parser a -> Mod CommandFields a
mkCommandParser' FilePath
"get-block-header" FilePath
"Get header of a block" do
BlockId
blockId <- Parser BlockId
blockIdOption
pure do
BlockHeader
blockHeader <- BlockId -> MorleyClientM BlockHeader
forall (m :: * -> *). HasTezosRpc m => BlockId -> m BlockHeader
getBlockHeader BlockId
blockId
ByteString -> MorleyClientM ()
forall a (m :: * -> *). (Print a, MonadIO m) => a -> m ()
putStrLn (ByteString -> MorleyClientM ()) -> ByteString -> MorleyClientM ()
forall a b. (a -> b) -> a -> b
$ BlockHeader -> ByteString
forall a. ToJSON a => a -> ByteString
Aeson.encode BlockHeader
blockHeader
getScriptSizeCmd :: ClientMCmd
getScriptSizeCmd :: Mod CommandFields (MorleyClientM ())
getScriptSizeCmd = FilePath
-> FilePath
-> Parser (MorleyClientM ())
-> Mod CommandFields (MorleyClientM ())
forall a. FilePath -> FilePath -> Parser a -> Mod CommandFields a
mkCommandParser' FilePath
"compute-script-size" FilePath
"Compute script size" do
FilePath
ssScriptFile <- Parser FilePath
scriptFileOption
Value
ssStorage <- Maybe Value
-> NamedF Identity FilePath "name"
-> NamedF Identity FilePath "help"
-> Parser Value
valueOption Maybe Value
forall a. Maybe a
Nothing
(NamedF Identity FilePath "name"
-> NamedF Identity FilePath "help" -> Parser Value)
-> Param (NamedF Identity FilePath "name")
-> NamedF Identity FilePath "help"
-> Parser Value
forall p fn fn'. WithParam p fn fn' => fn -> Param p -> fn'
! FilePath -> Param (NamedF Identity FilePath "name")
forall (x :: Symbol) a. IsLabel x a => a
#name FilePath
"storage"
(NamedF Identity FilePath "help" -> Parser Value)
-> Param (NamedF Identity FilePath "help") -> Parser Value
forall p fn fn'. WithParam p fn fn' => fn -> Param p -> fn'
! FilePath -> Param (NamedF Identity FilePath "help")
forall (x :: Symbol) a. IsLabel x a => a
#help FilePath
"Contract storage value."
pure do
Contract
contract <- IO Contract -> MorleyClientM Contract
forall a. IO a -> MorleyClientM a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Contract -> MorleyClientM Contract)
-> IO Contract -> MorleyClientM Contract
forall a b. (a -> b) -> a -> b
$ Maybe FilePath -> IO Contract
prepareContract (FilePath -> Maybe FilePath
forall a. a -> Maybe a
Just FilePath
ssScriptFile)
MorleyClientM SomeContractAndStorage -> MorleyClientM ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (MorleyClientM SomeContractAndStorage -> MorleyClientM ())
-> (TypeCheckResult ExpandedOp SomeContractAndStorage
-> MorleyClientM SomeContractAndStorage)
-> TypeCheckResult ExpandedOp SomeContractAndStorage
-> MorleyClientM ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MorleyClientM (Either (TcError' ExpandedOp) SomeContractAndStorage)
-> MorleyClientM SomeContractAndStorage
forall (m :: * -> *) e a.
(MonadThrow m, Exception e) =>
m (Either e a) -> m a
throwLeft (MorleyClientM
(Either (TcError' ExpandedOp) SomeContractAndStorage)
-> MorleyClientM SomeContractAndStorage)
-> (TypeCheckResult ExpandedOp SomeContractAndStorage
-> MorleyClientM
(Either (TcError' ExpandedOp) SomeContractAndStorage))
-> TypeCheckResult ExpandedOp SomeContractAndStorage
-> MorleyClientM SomeContractAndStorage
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either (TcError' ExpandedOp) SomeContractAndStorage
-> MorleyClientM
(Either (TcError' ExpandedOp) SomeContractAndStorage)
forall a. a -> MorleyClientM a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either (TcError' ExpandedOp) SomeContractAndStorage
-> MorleyClientM
(Either (TcError' ExpandedOp) SomeContractAndStorage))
-> (TypeCheckResult ExpandedOp SomeContractAndStorage
-> Either (TcError' ExpandedOp) SomeContractAndStorage)
-> TypeCheckResult ExpandedOp SomeContractAndStorage
-> MorleyClientM
(Either (TcError' ExpandedOp) SomeContractAndStorage)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TypeCheckOptions
-> TypeCheckResult ExpandedOp SomeContractAndStorage
-> Either (TcError' ExpandedOp) SomeContractAndStorage
forall op a.
TypeCheckOptions -> TypeCheckResult op a -> Either (TcError' op) a
TC.typeCheckingWith TypeCheckOptions
forall a. Default a => a
def (TypeCheckResult ExpandedOp SomeContractAndStorage
-> MorleyClientM ())
-> TypeCheckResult ExpandedOp SomeContractAndStorage
-> MorleyClientM ()
forall a b. (a -> b) -> a -> b
$
Contract
-> Value -> TypeCheckResult ExpandedOp SomeContractAndStorage
TC.typeCheckContractAndStorage Contract
contract Value
ssStorage
Natural
size <- Contract -> Value -> MorleyClientM Natural
forall (m :: * -> *).
HasTezosRpc m =>
Contract -> Value -> m Natural
computeUntypedContractSize Contract
contract Value
ssStorage
Natural -> MorleyClientM ()
forall a (m :: * -> *). (MonadIO m, Show a) => a -> m ()
print Natural
size
getBlockOperationsCmd :: ClientMCmd
getBlockOperationsCmd :: Mod CommandFields (MorleyClientM ())
getBlockOperationsCmd = FilePath
-> FilePath
-> Parser (MorleyClientM ())
-> Mod CommandFields (MorleyClientM ())
forall a. FilePath -> FilePath -> Parser a -> Mod CommandFields a
mkCommandParser' FilePath
"get-block-operations"
FilePath
"Get operations contained in a block" do
BlockId
blockId <- Parser BlockId
blockIdOption
pure do
[[BlockOperation]]
operationLists <- BlockId -> MorleyClientM [[BlockOperation]]
forall (m :: * -> *).
HasTezosRpc m =>
BlockId -> m [[BlockOperation]]
getBlockOperations BlockId
blockId
[[BlockOperation]]
-> (Element [[BlockOperation]] -> MorleyClientM ())
-> MorleyClientM ()
forall t (m :: * -> *) b.
(Container t, Monad m) =>
t -> (Element t -> m b) -> m ()
forM_ [[BlockOperation]]
operationLists ((Element [[BlockOperation]] -> MorleyClientM ())
-> MorleyClientM ())
-> (Element [[BlockOperation]] -> MorleyClientM ())
-> MorleyClientM ()
forall a b. (a -> b) -> a -> b
$ \Element [[BlockOperation]]
operations -> do
[BlockOperation]
-> (Element [BlockOperation] -> MorleyClientM ())
-> MorleyClientM ()
forall t (m :: * -> *) b.
(Container t, Monad m) =>
t -> (Element t -> m b) -> m ()
forM_ [BlockOperation]
Element [[BlockOperation]]
operations ((Element [BlockOperation] -> MorleyClientM ())
-> MorleyClientM ())
-> (Element [BlockOperation] -> MorleyClientM ())
-> MorleyClientM ()
forall a b. (a -> b) -> a -> b
$ \BlockOperation {[OperationRespWithMeta]
Text
boHash :: Text
boContents :: [OperationRespWithMeta]
boHash :: BlockOperation -> Text
boContents :: BlockOperation -> [OperationRespWithMeta]
..} -> do
Text -> MorleyClientM ()
forall (m :: * -> *). MonadIO m => Text -> m ()
putTextLn (Text -> MorleyClientM ()) -> Text -> MorleyClientM ()
forall a b. (a -> b) -> a -> b
$ Text
"Hash: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
boHash
Text -> MorleyClientM ()
forall (m :: * -> *). MonadIO m => Text -> m ()
putTextLn (Text -> MorleyClientM ()) -> Text -> MorleyClientM ()
forall a b. (a -> b) -> a -> b
$ Text
"Contents: "
[OperationResp WithCommonOperationData]
-> (Element [OperationResp WithCommonOperationData]
-> MorleyClientM ())
-> MorleyClientM ()
forall t (m :: * -> *) b.
(Container t, Monad m) =>
t -> (Element t -> m b) -> m ()
forM_ (OperationRespWithMeta -> OperationResp WithCommonOperationData
orwmResponse (OperationRespWithMeta -> OperationResp WithCommonOperationData)
-> [OperationRespWithMeta]
-> [OperationResp WithCommonOperationData]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [OperationRespWithMeta]
boContents) \case
TransactionOpResp WithCommonOperationData TransactionOperation
op -> ByteString -> MorleyClientM ()
forall a (m :: * -> *). (Print a, MonadIO m) => a -> m ()
putStrLn (ByteString -> MorleyClientM ()) -> ByteString -> MorleyClientM ()
forall a b. (a -> b) -> a -> b
$ WithCommonOperationData TransactionOperation -> ByteString
forall a. ToJSON a => a -> ByteString
Aeson.encode WithCommonOperationData TransactionOperation
op
TransferTicketOpResp WithCommonOperationData TransferTicketOperation
op -> ByteString -> MorleyClientM ()
forall a (m :: * -> *). (Print a, MonadIO m) => a -> m ()
putStrLn (ByteString -> MorleyClientM ()) -> ByteString -> MorleyClientM ()
forall a b. (a -> b) -> a -> b
$ WithCommonOperationData TransferTicketOperation -> ByteString
forall a. ToJSON a => a -> ByteString
Aeson.encode WithCommonOperationData TransferTicketOperation
op
OriginationOpResp WithCommonOperationData OriginationOperation
op -> ByteString -> MorleyClientM ()
forall a (m :: * -> *). (Print a, MonadIO m) => a -> m ()
putStrLn (ByteString -> MorleyClientM ()) -> ByteString -> MorleyClientM ()
forall a b. (a -> b) -> a -> b
$ WithCommonOperationData OriginationOperation -> ByteString
forall a. ToJSON a => a -> ByteString
Aeson.encode WithCommonOperationData OriginationOperation
op
DelegationOpResp WithCommonOperationData DelegationOperation
op -> ByteString -> MorleyClientM ()
forall a (m :: * -> *). (Print a, MonadIO m) => a -> m ()
putStrLn (ByteString -> MorleyClientM ()) -> ByteString -> MorleyClientM ()
forall a b. (a -> b) -> a -> b
$ WithCommonOperationData DelegationOperation -> ByteString
forall a. ToJSON a => a -> ByteString
Aeson.encode WithCommonOperationData DelegationOperation
op
RevealOpResp WithCommonOperationData RevealOperation
op -> ByteString -> MorleyClientM ()
forall a (m :: * -> *). (Print a, MonadIO m) => a -> m ()
putStrLn (ByteString -> MorleyClientM ()) -> ByteString -> MorleyClientM ()
forall a b. (a -> b) -> a -> b
$ WithCommonOperationData RevealOperation -> ByteString
forall a. ToJSON a => a -> ByteString
Aeson.encode WithCommonOperationData RevealOperation
op
EventOpResp WithCommonOperationData EventOperation
op -> ByteString -> MorleyClientM ()
forall a (m :: * -> *). (Print a, MonadIO m) => a -> m ()
putStrLn (ByteString -> MorleyClientM ()) -> ByteString -> MorleyClientM ()
forall a b. (a -> b) -> a -> b
$ WithCommonOperationData EventOperation -> ByteString
forall a. ToJSON a => a -> ByteString
Aeson.encode WithCommonOperationData EventOperation
op
OtherOpResp Text
kind -> Text -> MorleyClientM ()
forall (m :: * -> *). MonadIO m => Text -> m ()
putTextLn (Text -> MorleyClientM ()) -> Text -> MorleyClientM ()
forall a b. (a -> b) -> a -> b
$ Text
"Unknown operation kind: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
kind
Text -> MorleyClientM ()
forall (m :: * -> *). MonadIO m => Text -> m ()
putTextLn Text
""
Text -> MorleyClientM ()
forall (m :: * -> *). MonadIO m => Text -> m ()
putTextLn Text
"——————————————————————————————————————————————————\n"
getTicketBalanceCmd :: ClientMCmd
getTicketBalanceCmd :: Mod CommandFields (MorleyClientM ())
getTicketBalanceCmd = FilePath
-> FilePath
-> Parser (MorleyClientM ())
-> Mod CommandFields (MorleyClientM ())
forall a. FilePath -> FilePath -> Parser a -> Mod CommandFields a
mkCommandParser' FilePath
"ticket-balance" FilePath
"Get ticket balance for specific tickets" do
SomeAddressOrAlias
owner' <- (Maybe SomeAddressOrAlias
-> NamedF Identity FilePath "name"
-> NamedF Identity FilePath "help"
-> Parser SomeAddressOrAlias)
-> Parser SomeAddressOrAlias
forall a r.
(Maybe a
-> NamedF Identity FilePath "name"
-> NamedF Identity FilePath "help"
-> Parser r)
-> Parser r
ownerOption Maybe SomeAddressOrAlias
-> NamedF Identity FilePath "name"
-> NamedF Identity FilePath "help"
-> Parser SomeAddressOrAlias
someAddressOrAliasOption
KindedAddress 'AddressKindContract
tbaTicketer <- Maybe (KindedAddress 'AddressKindContract)
-> NamedF Identity FilePath "name"
-> NamedF Identity FilePath "help"
-> Parser (KindedAddress 'AddressKindContract)
forall a.
(Buildable a, HasCLReader a) =>
Maybe a
-> NamedF Identity FilePath "name"
-> NamedF Identity FilePath "help"
-> Parser a
mkCLOptionParser Maybe (KindedAddress 'AddressKindContract)
forall a. Maybe a
Nothing
(NamedF Identity FilePath "name"
-> NamedF Identity FilePath "help"
-> Parser (KindedAddress 'AddressKindContract))
-> Param (NamedF Identity FilePath "name")
-> NamedF Identity FilePath "help"
-> Parser (KindedAddress 'AddressKindContract)
forall p fn fn'. WithParam p fn fn' => fn -> Param p -> fn'
! FilePath -> Param (NamedF Identity FilePath "name")
forall (x :: Symbol) a. IsLabel x a => a
#name FilePath
"ticketer"
(NamedF Identity FilePath "help"
-> Parser (KindedAddress 'AddressKindContract))
-> Param (NamedF Identity FilePath "help")
-> Parser (KindedAddress 'AddressKindContract)
forall p fn fn'. WithParam p fn fn' => fn -> Param p -> fn'
! FilePath -> Param (NamedF Identity FilePath "help")
forall (x :: Symbol) a. IsLabel x a => a
#help FilePath
"The contract that issued the ticket."
Ty
tbaContentType <- forall a.
(Buildable a, HasCLReader a) =>
Maybe a
-> NamedF Identity FilePath "name"
-> NamedF Identity FilePath "help"
-> Parser a
mkCLOptionParser @U.Ty Maybe Ty
forall a. Maybe a
Nothing
(NamedF Identity FilePath "name"
-> NamedF Identity FilePath "help" -> Parser Ty)
-> Param (NamedF Identity FilePath "name")
-> NamedF Identity FilePath "help"
-> Parser Ty
forall p fn fn'. WithParam p fn fn' => fn -> Param p -> fn'
! FilePath -> Param (NamedF Identity FilePath "name")
forall (x :: Symbol) a. IsLabel x a => a
#name FilePath
"content-type"
(NamedF Identity FilePath "help" -> Parser Ty)
-> Param (NamedF Identity FilePath "help") -> Parser Ty
forall p fn fn'. WithParam p fn fn' => fn -> Param p -> fn'
! FilePath -> Param (NamedF Identity FilePath "help")
forall (x :: Symbol) a. IsLabel x a => a
#help FilePath
"Content type."
Value
tbaContent <- Maybe Value
-> NamedF Identity FilePath "name"
-> NamedF Identity FilePath "help"
-> Parser Value
valueOption Maybe Value
forall a. Maybe a
Nothing
(NamedF Identity FilePath "name"
-> NamedF Identity FilePath "help" -> Parser Value)
-> Param (NamedF Identity FilePath "name")
-> NamedF Identity FilePath "help"
-> Parser Value
forall p fn fn'. WithParam p fn fn' => fn -> Param p -> fn'
! FilePath -> Param (NamedF Identity FilePath "name")
forall (x :: Symbol) a. IsLabel x a => a
#name FilePath
"content"
(NamedF Identity FilePath "help" -> Parser Value)
-> Param (NamedF Identity FilePath "help") -> Parser Value
forall p fn fn'. WithParam p fn fn' => fn -> Param p -> fn'
! FilePath -> Param (NamedF Identity FilePath "help")
forall (x :: Symbol) a. IsLabel x a => a
#help FilePath
"Ticket content."
pure do
Constrained
(ConstrainAddressKind
'[ 'AddressKindImplicit, 'AddressKindContract])
KindedAddress
owner <- SomeAddressOrAlias
-> MorleyClientM (ResolvedAddress SomeAddressOrAlias)
forall addressOrAlias (m :: * -> *).
(HasTezosClient m, MonadThrow m, Resolve addressOrAlias) =>
addressOrAlias -> m (ResolvedAddress addressOrAlias)
resolveAddress SomeAddressOrAlias
owner'
Natural
bal <- Constrained
(ConstrainAddressKind
'[ 'AddressKindImplicit, 'AddressKindContract])
KindedAddress
-> GetTicketBalance -> MorleyClientM Natural
forall (m :: * -> *).
HasTezosRpc m =>
Constrained
(ConstrainAddressKind
'[ 'AddressKindImplicit, 'AddressKindContract])
KindedAddress
-> GetTicketBalance -> m Natural
getTicketBalance Constrained
(ConstrainAddressKind
'[ 'AddressKindImplicit, 'AddressKindContract])
KindedAddress
owner GetTicketBalance
{ gtbContent :: Expression
gtbContent = Value -> Expression
forall a. ToExpression a => a -> Expression
toExpression Value
tbaContent
, gtbContentType :: Expression
gtbContentType = Ty -> Expression
forall a. ToExpression a => a -> Expression
toExpression Ty
tbaContentType
, gtbTicketer :: KindedAddress 'AddressKindContract
gtbTicketer = KindedAddress 'AddressKindContract
tbaTicketer
}
Natural -> MorleyClientM ()
forall a (m :: * -> *). (MonadIO m, Show a) => a -> m ()
print Natural
bal
getAllTicketBalancesCmd :: ClientMCmd
getAllTicketBalancesCmd :: Mod CommandFields (MorleyClientM ())
getAllTicketBalancesCmd = FilePath
-> FilePath
-> Parser (MorleyClientM ())
-> Mod CommandFields (MorleyClientM ())
forall a. FilePath -> FilePath -> Parser a -> Mod CommandFields a
mkCommandParser' FilePath
"all-ticket-balances" FilePath
"Get all ticket balances" do
AddressOrAlias 'AddressKindContract
owner' <- (Maybe (AddressOrAlias 'AddressKindContract)
-> NamedF Identity FilePath "name"
-> NamedF Identity FilePath "help"
-> Parser (AddressOrAlias 'AddressKindContract))
-> Parser (AddressOrAlias 'AddressKindContract)
forall a r.
(Maybe a
-> NamedF Identity FilePath "name"
-> NamedF Identity FilePath "help"
-> Parser r)
-> Parser r
ownerOption ((Maybe (AddressOrAlias 'AddressKindContract)
-> NamedF Identity FilePath "name"
-> NamedF Identity FilePath "help"
-> Parser (AddressOrAlias 'AddressKindContract))
-> Parser (AddressOrAlias 'AddressKindContract))
-> (Maybe (AddressOrAlias 'AddressKindContract)
-> NamedF Identity FilePath "name"
-> NamedF Identity FilePath "help"
-> Parser (AddressOrAlias 'AddressKindContract))
-> Parser (AddressOrAlias 'AddressKindContract)
forall a b. (a -> b) -> a -> b
$ forall (kind :: AddressKind).
(SingI kind, L1AddressKind kind) =>
Maybe (AddressOrAlias kind)
-> NamedF Identity FilePath "name"
-> NamedF Identity FilePath "help"
-> Parser (AddressOrAlias kind)
addressOrAliasOption @'AddressKindContract
pure do
KindedAddress 'AddressKindContract
owner <- AddressOrAlias 'AddressKindContract
-> MorleyClientM
(ResolvedAddress (AddressOrAlias 'AddressKindContract))
forall addressOrAlias (m :: * -> *).
(HasTezosClient m, MonadThrow m, Resolve addressOrAlias) =>
addressOrAlias -> m (ResolvedAddress addressOrAlias)
resolveAddress AddressOrAlias 'AddressKindContract
owner'
[GetAllTicketBalancesResponse]
bals <- KindedAddress 'AddressKindContract
-> MorleyClientM [GetAllTicketBalancesResponse]
forall (m :: * -> *).
HasTezosRpc m =>
KindedAddress 'AddressKindContract
-> m [GetAllTicketBalancesResponse]
getAllTicketBalances KindedAddress 'AddressKindContract
owner
[GetAllTicketBalancesResponse]
-> (Element [GetAllTicketBalancesResponse] -> MorleyClientM ())
-> MorleyClientM ()
forall t (m :: * -> *) b.
(Container t, Monad m) =>
t -> (Element t -> m b) -> m ()
forM_ [GetAllTicketBalancesResponse]
bals \GetAllTicketBalancesResponse{KindedAddress 'AddressKindContract
Expression
TezosNat
gatbrTicketer :: KindedAddress 'AddressKindContract
gatbrContentType :: Expression
gatbrContent :: Expression
gatbrAmount :: TezosNat
gatbrTicketer :: GetAllTicketBalancesResponse -> KindedAddress 'AddressKindContract
gatbrContentType :: GetAllTicketBalancesResponse -> Expression
gatbrContent :: GetAllTicketBalancesResponse -> Expression
gatbrAmount :: GetAllTicketBalancesResponse -> TezosNat
..} -> do
Value
content <- (FromExpressionError -> MorleyClientM Value)
-> (Value -> MorleyClientM Value)
-> Either FromExpressionError Value
-> MorleyClientM Value
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either FromExpressionError -> MorleyClientM Value
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM Value -> MorleyClientM Value
forall a. a -> MorleyClientM a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either FromExpressionError Value -> MorleyClientM Value)
-> Either FromExpressionError Value -> MorleyClientM Value
forall a b. (a -> b) -> a -> b
$ forall a.
FromExp RegularExp a =>
Expression -> Either FromExpressionError a
fromExpression @U.Value Expression
gatbrContent
Ty
ty <- (FromExpressionError -> MorleyClientM Ty)
-> (Ty -> MorleyClientM Ty)
-> Either FromExpressionError Ty
-> MorleyClientM Ty
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either FromExpressionError -> MorleyClientM Ty
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM Ty -> MorleyClientM Ty
forall a. a -> MorleyClientM a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either FromExpressionError Ty -> MorleyClientM Ty)
-> Either FromExpressionError Ty -> MorleyClientM Ty
forall a b. (a -> b) -> a -> b
$ forall a.
FromExp RegularExp a =>
Expression -> Either FromExpressionError a
fromExpression @U.Ty Expression
gatbrContentType
Text -> MorleyClientM ()
forall (m :: * -> *). MonadIO m => Text -> m ()
putTextLn (Text -> MorleyClientM ()) -> Text -> MorleyClientM ()
forall a b. (a -> b) -> a -> b
$
Doc -> Doc -> Doc
forall a. Buildable a => Doc -> a -> Doc
nameF Doc
"Ticketer" (KindedAddress 'AddressKindContract -> Doc
forall a. Buildable a => a -> Doc
build KindedAddress 'AddressKindContract
gatbrTicketer) Doc -> Doc -> Text
forall a b. (Buildable a, FromDoc b) => a -> Doc -> b
|+ Doc
", "
Doc -> Doc -> Doc
forall b. FromDoc b => Doc -> Doc -> b
+| Doc -> Doc -> Doc
forall a. Buildable a => Doc -> a -> Doc
nameF Doc
"content" (Value -> Doc
forall a. Buildable a => a -> Doc
build Value
content) Doc -> Doc -> Doc
forall a b. (Buildable a, FromDoc b) => a -> Doc -> b
|+ Doc
", "
Doc -> Doc -> Doc
forall b. FromDoc b => Doc -> Doc -> b
+| Doc -> Doc -> Doc
forall a. Buildable a => Doc -> a -> Doc
nameF Doc
"type" (Ty -> Doc
forall a. Buildable a => a -> Doc
build Ty
ty) Doc -> Doc -> Doc
forall a b. (Buildable a, FromDoc b) => a -> Doc -> b
|+ Doc
", "
Doc -> Doc -> Doc
forall b. FromDoc b => Doc -> Doc -> b
+| Doc -> Doc -> Doc
forall a. Buildable a => Doc -> a -> Doc
nameF Doc
"amount" (Natural -> Doc
forall a. Buildable a => a -> Doc
build (Natural -> Doc) -> Natural -> Doc
forall a b. (a -> b) -> a -> b
$ TezosNat -> Natural
forall a. StringEncode a -> a
unStringEncode TezosNat
gatbrAmount)
transferTicketCmd :: ClientMCmd
transferTicketCmd :: Mod CommandFields (MorleyClientM ())
transferTicketCmd = FilePath
-> FilePath
-> Parser (MorleyClientM ())
-> Mod CommandFields (MorleyClientM ())
forall a. FilePath -> FilePath -> Parser a -> Mod CommandFields a
mkCommandParser' FilePath
"transfer-ticket"
FilePath
"Perform a ticket transfer to the given contract with given amount and parameter." do
AddressOrAlias 'AddressKindImplicit
ttaSender <- forall (kind :: AddressKind).
(SingI kind, L1AddressKind kind) =>
Maybe (AddressOrAlias kind)
-> NamedF Identity FilePath "name"
-> NamedF Identity FilePath "help"
-> Parser (AddressOrAlias kind)
addressOrAliasOption @'AddressKindImplicit Maybe (AddressOrAlias 'AddressKindImplicit)
forall a. Maybe a
Nothing
(NamedF Identity FilePath "name"
-> NamedF Identity FilePath "help"
-> Parser (AddressOrAlias 'AddressKindImplicit))
-> Param (NamedF Identity FilePath "name")
-> NamedF Identity FilePath "help"
-> Parser (AddressOrAlias 'AddressKindImplicit)
forall p fn fn'. WithParam p fn fn' => fn -> Param p -> fn'
! FilePath -> Param (NamedF Identity FilePath "name")
forall (x :: Symbol) a. IsLabel x a => a
#name FilePath
"from"
(NamedF Identity FilePath "help"
-> Parser (AddressOrAlias 'AddressKindImplicit))
-> Param (NamedF Identity FilePath "help")
-> Parser (AddressOrAlias 'AddressKindImplicit)
forall p fn fn'. WithParam p fn fn' => fn -> Param p -> fn'
! FilePath -> Param (NamedF Identity FilePath "help")
forall (x :: Symbol) a. IsLabel x a => a
#help FilePath
"Address or alias from which transfer is performed."
Natural
ttaTicketAmount <- forall a.
(Buildable a, HasCLReader a) =>
Maybe a
-> NamedF Identity FilePath "name"
-> NamedF Identity FilePath "help"
-> Parser a
mkCLOptionParser @Natural Maybe Natural
forall a. Maybe a
Nothing
(NamedF Identity FilePath "name"
-> NamedF Identity FilePath "help" -> Parser Natural)
-> Param (NamedF Identity FilePath "name")
-> NamedF Identity FilePath "help"
-> Parser Natural
forall p fn fn'. WithParam p fn fn' => fn -> Param p -> fn'
! FilePath -> Param (NamedF Identity FilePath "name")
forall (x :: Symbol) a. IsLabel x a => a
#name FilePath
"amount"
(NamedF Identity FilePath "help" -> Parser Natural)
-> Param (NamedF Identity FilePath "help") -> Parser Natural
forall p fn fn'. WithParam p fn fn' => fn -> Param p -> fn'
! FilePath -> Param (NamedF Identity FilePath "help")
forall (x :: Symbol) a. IsLabel x a => a
#help FilePath
"Ticket amount."
Value
ttaTicketContents <- forall a.
(Buildable a, HasCLReader a) =>
Maybe a
-> NamedF Identity FilePath "name"
-> NamedF Identity FilePath "help"
-> Parser a
mkCLOptionParser @U.Value Maybe Value
forall a. Maybe a
Nothing
(NamedF Identity FilePath "name"
-> NamedF Identity FilePath "help" -> Parser Value)
-> Param (NamedF Identity FilePath "name")
-> NamedF Identity FilePath "help"
-> Parser Value
forall p fn fn'. WithParam p fn fn' => fn -> Param p -> fn'
! FilePath -> Param (NamedF Identity FilePath "name")
forall (x :: Symbol) a. IsLabel x a => a
#name FilePath
"value"
(NamedF Identity FilePath "help" -> Parser Value)
-> Param (NamedF Identity FilePath "help") -> Parser Value
forall p fn fn'. WithParam p fn fn' => fn -> Param p -> fn'
! FilePath -> Param (NamedF Identity FilePath "help")
forall (x :: Symbol) a. IsLabel x a => a
#help FilePath
"Ticket value."
Ty
ttaTicketType <- forall a.
(Buildable a, HasCLReader a) =>
Maybe a
-> NamedF Identity FilePath "name"
-> NamedF Identity FilePath "help"
-> Parser a
mkCLOptionParser @U.Ty Maybe Ty
forall a. Maybe a
Nothing
(NamedF Identity FilePath "name"
-> NamedF Identity FilePath "help" -> Parser Ty)
-> Param (NamedF Identity FilePath "name")
-> NamedF Identity FilePath "help"
-> Parser Ty
forall p fn fn'. WithParam p fn fn' => fn -> Param p -> fn'
! FilePath -> Param (NamedF Identity FilePath "name")
forall (x :: Symbol) a. IsLabel x a => a
#name FilePath
"type"
(NamedF Identity FilePath "help" -> Parser Ty)
-> Param (NamedF Identity FilePath "help") -> Parser Ty
forall p fn fn'. WithParam p fn fn' => fn -> Param p -> fn'
! FilePath -> Param (NamedF Identity FilePath "help")
forall (x :: Symbol) a. IsLabel x a => a
#help FilePath
"Ticket type."
AddressOrAlias 'AddressKindContract
ttaTicketTicketer <- forall a.
(Buildable a, HasCLReader a) =>
Maybe a
-> NamedF Identity FilePath "name"
-> NamedF Identity FilePath "help"
-> Parser a
mkCLOptionParser @ContractAddressOrAlias Maybe (AddressOrAlias 'AddressKindContract)
forall a. Maybe a
Nothing
(NamedF Identity FilePath "name"
-> NamedF Identity FilePath "help"
-> Parser (AddressOrAlias 'AddressKindContract))
-> Param (NamedF Identity FilePath "name")
-> NamedF Identity FilePath "help"
-> Parser (AddressOrAlias 'AddressKindContract)
forall p fn fn'. WithParam p fn fn' => fn -> Param p -> fn'
! FilePath -> Param (NamedF Identity FilePath "name")
forall (x :: Symbol) a. IsLabel x a => a
#name FilePath
"ticketer"
(NamedF Identity FilePath "help"
-> Parser (AddressOrAlias 'AddressKindContract))
-> Param (NamedF Identity FilePath "help")
-> Parser (AddressOrAlias 'AddressKindContract)
forall p fn fn'. WithParam p fn fn' => fn -> Param p -> fn'
! FilePath -> Param (NamedF Identity FilePath "help")
forall (x :: Symbol) a. IsLabel x a => a
#help FilePath
"Ticketer address or alias."
SomeAddressOrAlias
ttaDestination <- Maybe SomeAddressOrAlias
-> NamedF Identity FilePath "name"
-> NamedF Identity FilePath "help"
-> Parser SomeAddressOrAlias
someAddressOrAliasOption Maybe SomeAddressOrAlias
forall a. Maybe a
Nothing
(NamedF Identity FilePath "name"
-> NamedF Identity FilePath "help" -> Parser SomeAddressOrAlias)
-> Param (NamedF Identity FilePath "name")
-> NamedF Identity FilePath "help"
-> Parser SomeAddressOrAlias
forall p fn fn'. WithParam p fn fn' => fn -> Param p -> fn'
! FilePath -> Param (NamedF Identity FilePath "name")
forall (x :: Symbol) a. IsLabel x a => a
#name FilePath
"to"
(NamedF Identity FilePath "help" -> Parser SomeAddressOrAlias)
-> Param (NamedF Identity FilePath "help")
-> Parser SomeAddressOrAlias
forall p fn fn'. WithParam p fn fn' => fn -> Param p -> fn'
! FilePath -> Param (NamedF Identity FilePath "help")
forall (x :: Symbol) a. IsLabel x a => a
#help FilePath
"Address or alias of the transfer's destination."
Maybe Mutez
ttaMbFee <- Parser (Maybe Mutez)
feeOption
pure $ Ty
-> (forall (t :: T). SingI t => Notes t -> MorleyClientM ())
-> MorleyClientM ()
forall r. Ty -> (forall (t :: T). SingI t => Notes t -> r) -> r
T.withUType Ty
ttaTicketType \(Notes t
_ :: T.Notes t) -> do
Dict (ParameterScope t, Comparable t)
T.Dict <- MorleyClientM
(Either TcTypeError (Dict (ParameterScope t, Comparable t)))
-> MorleyClientM (Dict (ParameterScope t, Comparable t))
forall (m :: * -> *) e a.
(MonadThrow m, Exception e) =>
m (Either e a) -> m a
throwLeft (MorleyClientM
(Either TcTypeError (Dict (ParameterScope t, Comparable t)))
-> MorleyClientM (Dict (ParameterScope t, Comparable t)))
-> MorleyClientM
(Either TcTypeError (Dict (ParameterScope t, Comparable t)))
-> MorleyClientM (Dict (ParameterScope t, Comparable t))
forall a b. (a -> b) -> a -> b
$ Either TcTypeError (Dict (ParameterScope t, Comparable t))
-> MorleyClientM
(Either TcTypeError (Dict (ParameterScope t, Comparable t)))
forall a. a -> MorleyClientM a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either TcTypeError (Dict (ParameterScope t, Comparable t))
-> MorleyClientM
(Either TcTypeError (Dict (ParameterScope t, Comparable t))))
-> Either TcTypeError (Dict (ParameterScope t, Comparable t))
-> MorleyClientM
(Either TcTypeError (Dict (ParameterScope t, Comparable t)))
forall a b. (a -> b) -> a -> b
$ (BadTypeForScope -> TcTypeError)
-> Either BadTypeForScope (Dict (ParameterScope t, Comparable t))
-> Either TcTypeError (Dict (ParameterScope t, Comparable t))
forall a b c. (a -> b) -> Either a c -> Either b c
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first (T -> BadTypeForScope -> TcTypeError
TC.UnsupportedTypeForScope (forall {k} (a :: k). (SingKind k, SingI a) => Demote k
forall (a :: T). (SingKind T, SingI a) => Demote T
demote @t))
(Either BadTypeForScope (Dict (ParameterScope t, Comparable t))
-> Either TcTypeError (Dict (ParameterScope t, Comparable t)))
-> Either BadTypeForScope (Dict (ParameterScope t, Comparable t))
-> Either TcTypeError (Dict (ParameterScope t, Comparable t))
forall a b. (a -> b) -> a -> b
$ forall (c :: Constraint).
CheckScope c =>
Either BadTypeForScope (Dict c)
T.checkScope @(T.ParameterScope t, T.Comparable t)
ResolvedAddressAndAlias (AddressOrAlias 'AddressKindImplicit)
sendAddress <- AddressOrAlias 'AddressKindImplicit
-> MorleyClientM
(ResolvedAddressAndAlias (AddressOrAlias 'AddressKindImplicit))
forall addressOrAlias (m :: * -> *).
(HasTezosClient m, MonadThrow m, Resolve addressOrAlias) =>
addressOrAlias -> m (ResolvedAddressAndAlias addressOrAlias)
resolveAddressWithAlias AddressOrAlias 'AddressKindImplicit
ttaSender
Constrained
(ConstrainAddressKind
'[ 'AddressKindImplicit, 'AddressKindContract])
KindedAddress
destAddress <- SomeAddressOrAlias
-> MorleyClientM (ResolvedAddress SomeAddressOrAlias)
forall addressOrAlias (m :: * -> *).
(HasTezosClient m, MonadThrow m, Resolve addressOrAlias) =>
addressOrAlias -> m (ResolvedAddress addressOrAlias)
resolveAddress SomeAddressOrAlias
ttaDestination
ResolvedAddress (AddressOrAlias 'AddressKindContract)
ticketer <- AddressOrAlias 'AddressKindContract
-> MorleyClientM
(ResolvedAddress (AddressOrAlias 'AddressKindContract))
forall addressOrAlias (m :: * -> *).
(HasTezosClient m, MonadThrow m, Resolve addressOrAlias) =>
addressOrAlias -> m (ResolvedAddress addressOrAlias)
resolveAddress AddressOrAlias 'AddressKindContract
ttaTicketTicketer
(OperationHash
operationHash, [WithSource EventOperation]
contractEvents) :: (OperationHash, [WithSource EventOperation]) <-
Constrained
(ConstrainAddressKind
'[ 'AddressKindImplicit, 'AddressKindContract])
KindedAddress
-> (forall (t :: AddressKind).
ConstrainAddressKind
'[ 'AddressKindImplicit, 'AddressKindContract] t =>
KindedAddress t
-> MorleyClientM (OperationHash, [WithSource EventOperation]))
-> MorleyClientM (OperationHash, [WithSource EventOperation])
forall {k} (c :: k -> Constraint) (f :: k -> *) r.
Constrained c f -> (forall (t :: k). c t => f t -> r) -> r
withConstrained Constrained
(ConstrainAddressKind
'[ 'AddressKindImplicit, 'AddressKindContract])
KindedAddress
destAddress \case
destContract :: KindedAddress t
destContract@ContractAddress{} -> do
Contract
contract <- KindedAddress 'AddressKindContract -> MorleyClientM Contract
forall (m :: * -> *).
HasTezosRpc m =>
KindedAddress 'AddressKindContract -> m Contract
getContract KindedAddress t
KindedAddress 'AddressKindContract
destContract
SomeContract (Contract{} :: Contract cp st) <-
MorleyClientM (Either (TcError' ExpandedOp) SomeContract)
-> MorleyClientM SomeContract
forall (m :: * -> *) e a.
(MonadThrow m, Exception e) =>
m (Either e a) -> m a
throwLeft (MorleyClientM (Either (TcError' ExpandedOp) SomeContract)
-> MorleyClientM SomeContract)
-> MorleyClientM (Either (TcError' ExpandedOp) SomeContract)
-> MorleyClientM SomeContract
forall a b. (a -> b) -> a -> b
$ Either (TcError' ExpandedOp) SomeContract
-> MorleyClientM (Either (TcError' ExpandedOp) SomeContract)
forall a. a -> MorleyClientM a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either (TcError' ExpandedOp) SomeContract
-> MorleyClientM (Either (TcError' ExpandedOp) SomeContract))
-> Either (TcError' ExpandedOp) SomeContract
-> MorleyClientM (Either (TcError' ExpandedOp) SomeContract)
forall a b. (a -> b) -> a -> b
$ TypeCheckOptions
-> TypeCheckResult ExpandedOp SomeContract
-> Either (TcError' ExpandedOp) SomeContract
forall op a.
TypeCheckOptions -> TypeCheckResult op a -> Either (TcError' op) a
TC.typeCheckingWith TypeCheckOptions
forall a. Default a => a
def (TypeCheckResult ExpandedOp SomeContract
-> Either (TcError' ExpandedOp) SomeContract)
-> TypeCheckResult ExpandedOp SomeContract
-> Either (TcError' ExpandedOp) SomeContract
forall a b. (a -> b) -> a -> b
$ Contract -> TypeCheckResult ExpandedOp SomeContract
TC.typeCheckContract Contract
contract
Constrained (SingT a
_ :: T.SingT t') :: Constrained T.SingI T.SingT <- case forall {k} (a :: k). SingI a => Sing a
forall (a :: T). SingI a => Sing a
T.sing @cp of
T.STTicket Sing n
x -> Constrained SingI SingT -> MorleyClientM (Constrained SingI SingT)
forall a. a -> MorleyClientM a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Constrained SingI SingT
-> MorleyClientM (Constrained SingI SingT))
-> Constrained SingI SingT
-> MorleyClientM (Constrained SingI SingT)
forall a b. (a -> b) -> a -> b
$ forall {k} (c :: k -> Constraint) (f :: k -> *) (a :: k).
c a =>
f a -> Constrained c f
forall (c :: T -> Constraint) (f :: T -> *) (a :: T).
c a =>
f a -> Constrained c f
Constrained @T.SingI Sing n
SingT n
x
Sing cp
x -> TcError' ExpandedOp -> MorleyClientM (Constrained SingI SingT)
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM (TcError' ExpandedOp -> MorleyClientM (Constrained SingI SingT))
-> TcError' ExpandedOp -> MorleyClientM (Constrained SingI SingT)
forall a b. (a -> b) -> a -> b
$ forall op. Text -> Maybe TcTypeError -> TcError' op
TC.TcContractError @U.ExpandedOp
(Text
"Expected contract to accept tickets, but it had type " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Demote T -> Text
forall a b. (Buildable a, FromDoc b) => a -> b
pretty (Sing cp -> Demote T
forall k (a :: k). SingKind k => Sing a -> Demote k
forall (a :: T). Sing a -> Demote T
fromSing Sing cp
x))
(Maybe TcTypeError -> TcError' ExpandedOp)
-> Maybe TcTypeError -> TcError' ExpandedOp
forall a b. (a -> b) -> a -> b
$ TcTypeError -> Maybe TcTypeError
forall a. a -> Maybe a
Just (TcTypeError -> Maybe TcTypeError)
-> TcTypeError -> Maybe TcTypeError
forall a b. (a -> b) -> a -> b
$ NonEmpty (NonEmpty Text) -> TcTypeError
TC.UnexpectedType (OneItem (NonEmpty (NonEmpty Text)) -> NonEmpty (NonEmpty Text)
forall x. One x => OneItem x -> x
one (OneItem (NonEmpty (NonEmpty Text)) -> NonEmpty (NonEmpty Text))
-> OneItem (NonEmpty (NonEmpty Text)) -> NonEmpty (NonEmpty Text)
forall a b. (a -> b) -> a -> b
$ OneItem (OneItem (NonEmpty (NonEmpty Text)))
-> OneItem (NonEmpty (NonEmpty Text))
forall x. One x => OneItem x -> x
one (OneItem (OneItem (NonEmpty (NonEmpty Text)))
-> OneItem (NonEmpty (NonEmpty Text)))
-> OneItem (OneItem (NonEmpty (NonEmpty Text)))
-> OneItem (NonEmpty (NonEmpty Text))
forall a b. (a -> b) -> a -> b
$ Text
OneItem (OneItem (NonEmpty (NonEmpty Text)))
"ticket 'a")
t :~: a
Refl <- forall (a :: T) (b :: T) (m :: * -> *).
(SingI a, SingI b, Monad m) =>
(forall x. MismatchError T -> m x) -> m (a :~: b)
T.requireEq @t @t' ((forall x. MismatchError T -> MorleyClientM x)
-> MorleyClientM (t :~: a))
-> (forall x. MismatchError T -> MorleyClientM x)
-> MorleyClientM (t :~: a)
forall a b. (a -> b) -> a -> b
$ TcTypeError -> MorleyClientM x
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwM (TcTypeError -> MorleyClientM x)
-> (MismatchError T -> TcTypeError)
-> MismatchError T
-> MorleyClientM x
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MismatchError T -> TcTypeError
TC.TypeEqError
Value a
parameter <- MorleyClientM (Either (TcError' ExpandedOp) (Value a))
-> MorleyClientM (Value a)
forall (m :: * -> *) e a.
(MonadThrow m, Exception e) =>
m (Either e a) -> m a
throwLeft (MorleyClientM (Either (TcError' ExpandedOp) (Value a))
-> MorleyClientM (Value a))
-> MorleyClientM (Either (TcError' ExpandedOp) (Value a))
-> MorleyClientM (Value a)
forall a b. (a -> b) -> a -> b
$ Either (TcError' ExpandedOp) (Value a)
-> MorleyClientM (Either (TcError' ExpandedOp) (Value a))
forall a. a -> MorleyClientM a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either (TcError' ExpandedOp) (Value a)
-> MorleyClientM (Either (TcError' ExpandedOp) (Value a)))
-> Either (TcError' ExpandedOp) (Value a)
-> MorleyClientM (Either (TcError' ExpandedOp) (Value a))
forall a b. (a -> b) -> a -> b
$ TypeCheckOptions
-> TypeCheckResult ExpandedOp (Value a)
-> Either (TcError' ExpandedOp) (Value a)
forall op a.
TypeCheckOptions -> TypeCheckResult op a -> Either (TcError' op) a
TC.typeCheckingWith TypeCheckOptions
forall a. Default a => a
def (TypeCheckResult ExpandedOp (Value a)
-> Either (TcError' ExpandedOp) (Value a))
-> TypeCheckResult ExpandedOp (Value a)
-> Either (TcError' ExpandedOp) (Value a)
forall a b. (a -> b) -> a -> b
$ do
forall (t :: T).
SingI t =>
Value -> TypeCheckResult ExpandedOp (Value t)
TC.typeCheckValue @t' Value
ttaTicketContents
forall (m :: * -> *) (t :: T) env (kind :: AddressKind).
(HasTezosRpc m, HasTezosClient m, WithClientLog env m,
ParameterScope t, Comparable t) =>
AddressWithAlias 'AddressKindImplicit
-> KindedAddress kind
-> KindedAddress 'AddressKindContract
-> Value t
-> Natural
-> EpName
-> Maybe Mutez
-> m (OperationHash, [WithSource EventOperation])
transferTicket @_ @t' AddressWithAlias 'AddressKindImplicit
ResolvedAddressAndAlias (AddressOrAlias 'AddressKindImplicit)
sendAddress KindedAddress t
KindedAddress 'AddressKindContract
destContract KindedAddress 'AddressKindContract
ResolvedAddress (AddressOrAlias 'AddressKindContract)
ticketer Value a
parameter Natural
ttaTicketAmount
EpName
U.DefEpName Maybe Mutez
ttaMbFee
destImplicit :: KindedAddress t
destImplicit@ImplicitAddress{} -> do
Value t
parameter <- MorleyClientM (Either (TcError' ExpandedOp) (Value t))
-> MorleyClientM (Value t)
forall (m :: * -> *) e a.
(MonadThrow m, Exception e) =>
m (Either e a) -> m a
throwLeft (MorleyClientM (Either (TcError' ExpandedOp) (Value t))
-> MorleyClientM (Value t))
-> MorleyClientM (Either (TcError' ExpandedOp) (Value t))
-> MorleyClientM (Value t)
forall a b. (a -> b) -> a -> b
$ Either (TcError' ExpandedOp) (Value t)
-> MorleyClientM (Either (TcError' ExpandedOp) (Value t))
forall a. a -> MorleyClientM a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either (TcError' ExpandedOp) (Value t)
-> MorleyClientM (Either (TcError' ExpandedOp) (Value t)))
-> Either (TcError' ExpandedOp) (Value t)
-> MorleyClientM (Either (TcError' ExpandedOp) (Value t))
forall a b. (a -> b) -> a -> b
$ TypeCheckOptions
-> TypeCheckResult ExpandedOp (Value t)
-> Either (TcError' ExpandedOp) (Value t)
forall op a.
TypeCheckOptions -> TypeCheckResult op a -> Either (TcError' op) a
TC.typeCheckingWith TypeCheckOptions
forall a. Default a => a
def (TypeCheckResult ExpandedOp (Value t)
-> Either (TcError' ExpandedOp) (Value t))
-> TypeCheckResult ExpandedOp (Value t)
-> Either (TcError' ExpandedOp) (Value t)
forall a b. (a -> b) -> a -> b
$
forall (t :: T).
SingI t =>
Value -> TypeCheckResult ExpandedOp (Value t)
TC.typeCheckValue @t Value
ttaTicketContents
AddressWithAlias 'AddressKindImplicit
-> KindedAddress 'AddressKindImplicit
-> KindedAddress 'AddressKindContract
-> Value t
-> Natural
-> EpName
-> Maybe Mutez
-> MorleyClientM (OperationHash, [WithSource EventOperation])
forall (m :: * -> *) (t :: T) env (kind :: AddressKind).
(HasTezosRpc m, HasTezosClient m, WithClientLog env m,
ParameterScope t, Comparable t) =>
AddressWithAlias 'AddressKindImplicit
-> KindedAddress kind
-> KindedAddress 'AddressKindContract
-> Value t
-> Natural
-> EpName
-> Maybe Mutez
-> m (OperationHash, [WithSource EventOperation])
transferTicket AddressWithAlias 'AddressKindImplicit
ResolvedAddressAndAlias (AddressOrAlias 'AddressKindImplicit)
sendAddress KindedAddress t
KindedAddress 'AddressKindImplicit
destImplicit KindedAddress 'AddressKindContract
ResolvedAddress (AddressOrAlias 'AddressKindContract)
ticketer Value t
parameter Natural
ttaTicketAmount
EpName
U.DefEpName Maybe Mutez
ttaMbFee
Text -> MorleyClientM ()
forall (m :: * -> *). MonadIO m => Text -> m ()
putTextLn (Text -> MorleyClientM ()) -> Text -> MorleyClientM ()
forall a b. (a -> b) -> a -> b
$ Text
"Tickets successfully sent.\nOperation hash " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> OperationHash -> Text
forall a b. (Buildable a, FromDoc b) => a -> b
pretty OperationHash
operationHash Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"."
Bool -> MorleyClientM () -> MorleyClientM ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ([WithSource EventOperation] -> Bool
forall t. Container t => t -> Bool
null [WithSource EventOperation]
contractEvents) do
Text -> MorleyClientM ()
forall (m :: * -> *). MonadIO m => Text -> m ()
putTextLn (Text -> MorleyClientM ()) -> Text -> MorleyClientM ()
forall a b. (a -> b) -> a -> b
$ Text
"Additionally, the following contract events were emitted:"
Text -> MorleyClientM ()
forall (m :: * -> *). MonadIO m => Text -> m ()
putTextLn (Text -> MorleyClientM ()) -> Text -> MorleyClientM ()
forall a b. (a -> b) -> a -> b
$ Doc -> Text
forall a b. (Buildable a, FromDoc b) => a -> b
pretty (Doc -> Text) -> Doc -> Text
forall a b. (a -> b) -> a -> b
$ [WithSource EventOperation] -> Doc
forall a (f :: * -> *). (Buildable a, Foldable f) => f a -> Doc
blockListF [WithSource EventOperation]
contractEvents
clientParser :: Opt.Parser (IO ())
clientParser :: Parser (IO ())
clientParser = MorleyClientConfig -> MorleyClientM () -> IO ()
forall {b}. MorleyClientConfig -> MorleyClientM b -> IO b
runMorleyClientM' (MorleyClientConfig -> MorleyClientM () -> IO ())
-> Parser MorleyClientConfig -> Parser (MorleyClientM () -> IO ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser MorleyClientConfig
clientConfigParser Parser (MorleyClientM () -> IO ())
-> Parser (MorleyClientM ()) -> Parser (IO ())
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser (MorleyClientM ())
argsRawParser Parser (IO ()) -> Parser (IO ()) -> Parser (IO ())
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Parser (IO ())
Morley.argParser
where
runMorleyClientM' :: MorleyClientConfig -> MorleyClientM b -> IO b
runMorleyClientM' MorleyClientConfig
envConfig MorleyClientM b
action = do
MorleyClientEnv
env <- MorleyClientConfig -> IO MorleyClientEnv
mkMorleyClientEnv MorleyClientConfig
envConfig
MorleyClientEnv -> MorleyClientM b -> IO b
forall a. MorleyClientEnv -> MorleyClientM a -> IO a
runMorleyClientM MorleyClientEnv
env MorleyClientM b
action
argsRawParser :: Opt.Parser (MorleyClientM ())
argsRawParser :: Parser (MorleyClientM ())
argsRawParser = Mod CommandFields (MorleyClientM ()) -> Parser (MorleyClientM ())
forall a. Mod CommandFields a -> Parser a
subparser (Mod CommandFields (MorleyClientM ()) -> Parser (MorleyClientM ()))
-> Mod CommandFields (MorleyClientM ())
-> Parser (MorleyClientM ())
forall a b. (a -> b) -> a -> b
$ [Mod CommandFields (MorleyClientM ())]
-> Mod CommandFields (MorleyClientM ())
forall a. Monoid a => [a] -> a
mconcat
[ Mod CommandFields (MorleyClientM ())
originateCmd
, Mod CommandFields (MorleyClientM ())
transferCmd
, Mod CommandFields (MorleyClientM ())
transferTicketCmd
, Mod CommandFields (MorleyClientM ())
getBalanceCmd
, Mod CommandFields (MorleyClientM ())
getScriptSizeCmd
, Mod CommandFields (MorleyClientM ())
getBlockHeaderCmd
, Mod CommandFields (MorleyClientM ())
getBlockOperationsCmd
, Mod CommandFields (MorleyClientM ())
getTicketBalanceCmd
, Mod CommandFields (MorleyClientM ())
getAllTicketBalancesCmd
]
clientConfigParser :: Opt.Parser MorleyClientConfig
clientConfigParser :: Parser MorleyClientConfig
clientConfigParser = do
let mccSecretKey :: Maybe a
mccSecretKey = Maybe a
forall a. Maybe a
Nothing
Maybe BaseUrl
mccEndpointUrl <- Parser (Maybe BaseUrl)
endpointOption
FilePath
mccTezosClientPath <- Parser FilePath
pathOption
Maybe FilePath
mccMbTezosClientDataDir <- Parser (Maybe FilePath)
dataDirOption
Word
mccVerbosity <- [()] -> Word
forall i a. Num i => [a] -> i
genericLength ([()] -> Word) -> Parser [()] -> Parser Word
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser () -> Parser [()]
forall a. Parser a -> Parser [a]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many Parser ()
verboseSwitch
pure MorleyClientConfig{FilePath
Maybe FilePath
Maybe BaseUrl
Maybe SecretKey
Word
mccSecretKey :: Maybe SecretKey
mccEndpointUrl :: Maybe BaseUrl
mccTezosClientPath :: FilePath
mccMbTezosClientDataDir :: Maybe FilePath
mccVerbosity :: Word
mccEndpointUrl :: Maybe BaseUrl
mccTezosClientPath :: FilePath
mccMbTezosClientDataDir :: Maybe FilePath
mccVerbosity :: Word
mccSecretKey :: Maybe SecretKey
..}
where
verboseSwitch :: Opt.Parser ()
verboseSwitch :: Parser ()
verboseSwitch = () -> Mod FlagFields () -> Parser ()
forall a. a -> Mod FlagFields a -> Parser a
Opt.flag' () (Mod FlagFields () -> Parser ())
-> ([Mod FlagFields ()] -> Mod FlagFields ())
-> [Mod FlagFields ()]
-> Parser ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Mod FlagFields ()] -> Mod FlagFields ()
forall a. Monoid a => [a] -> a
mconcat ([Mod FlagFields ()] -> Parser ())
-> [Mod FlagFields ()] -> Parser ()
forall a b. (a -> b) -> a -> b
$
[ Char -> Mod FlagFields ()
forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
'V'
, FilePath -> Mod FlagFields ()
forall (f :: * -> *) a. FilePath -> Mod f a
help FilePath
"Increase verbosity (pass several times to increase further)."
]
data OriginateArgs = OriginateArgs
{ OriginateArgs -> Maybe FilePath
oaMbContractFile :: Maybe FilePath
, OriginateArgs -> ContractAlias
oaContractName :: ContractAlias
, OriginateArgs -> Mutez
oaInitialBalance :: Mutez
, OriginateArgs -> Value
oaInitialStorage :: U.Value
, OriginateArgs -> AddressOrAlias 'AddressKindImplicit
oaOriginateFrom :: ImplicitAddressOrAlias
, OriginateArgs -> Maybe Mutez
oaMbFee :: Maybe Mutez
, OriginateArgs -> Maybe KeyHash
oaDelegate :: Maybe KeyHash
}
originateArgsOption :: Opt.Parser OriginateArgs
originateArgsOption :: Parser OriginateArgs
originateArgsOption = do
Maybe FilePath
oaMbContractFile <- Parser (Maybe FilePath)
mbContractFileOption
ContractAlias
oaContractName <- Parser ContractAlias
contractNameOption
Mutez
oaInitialBalance <- Maybe Mutez
-> NamedF Identity FilePath "name"
-> NamedF Identity FilePath "help"
-> Parser Mutez
mutezOption (Mutez -> Maybe Mutez
forall a. a -> Maybe a
Just Mutez
zeroMutez)
(NamedF Identity FilePath "name"
-> NamedF Identity FilePath "help" -> Parser Mutez)
-> Param (NamedF Identity FilePath "name")
-> NamedF Identity FilePath "help"
-> Parser Mutez
forall p fn fn'. WithParam p fn fn' => fn -> Param p -> fn'
! FilePath -> Param (NamedF Identity FilePath "name")
forall (x :: Symbol) a. IsLabel x a => a
#name FilePath
"initial-balance"
(NamedF Identity FilePath "help" -> Parser Mutez)
-> Param (NamedF Identity FilePath "help") -> Parser Mutez
forall p fn fn'. WithParam p fn fn' => fn -> Param p -> fn'
! FilePath -> Param (NamedF Identity FilePath "help")
forall (x :: Symbol) a. IsLabel x a => a
#help FilePath
"Initial balance of the contract."
Value
oaInitialStorage <- Maybe Value
-> NamedF Identity FilePath "name"
-> NamedF Identity FilePath "help"
-> Parser Value
valueOption Maybe Value
forall a. Maybe a
Nothing
(NamedF Identity FilePath "name"
-> NamedF Identity FilePath "help" -> Parser Value)
-> Param (NamedF Identity FilePath "name")
-> NamedF Identity FilePath "help"
-> Parser Value
forall p fn fn'. WithParam p fn fn' => fn -> Param p -> fn'
! FilePath -> Param (NamedF Identity FilePath "name")
forall (x :: Symbol) a. IsLabel x a => a
#name FilePath
"initial-storage"
(NamedF Identity FilePath "help" -> Parser Value)
-> Param (NamedF Identity FilePath "help") -> Parser Value
forall p fn fn'. WithParam p fn fn' => fn -> Param p -> fn'
! FilePath -> Param (NamedF Identity FilePath "help")
forall (x :: Symbol) a. IsLabel x a => a
#help FilePath
"Initial contract storage value."
AddressOrAlias 'AddressKindImplicit
oaOriginateFrom <- Maybe (AddressOrAlias 'AddressKindImplicit)
-> NamedF Identity FilePath "name"
-> NamedF Identity FilePath "help"
-> Parser (AddressOrAlias 'AddressKindImplicit)
forall (kind :: AddressKind).
(SingI kind, L1AddressKind kind) =>
Maybe (AddressOrAlias kind)
-> NamedF Identity FilePath "name"
-> NamedF Identity FilePath "help"
-> Parser (AddressOrAlias kind)
addressOrAliasOption Maybe (AddressOrAlias 'AddressKindImplicit)
forall a. Maybe a
Nothing
(NamedF Identity FilePath "name"
-> NamedF Identity FilePath "help"
-> Parser (AddressOrAlias 'AddressKindImplicit))
-> Param (NamedF Identity FilePath "name")
-> NamedF Identity FilePath "help"
-> Parser (AddressOrAlias 'AddressKindImplicit)
forall p fn fn'. WithParam p fn fn' => fn -> Param p -> fn'
! FilePath -> Param (NamedF Identity FilePath "name")
forall (x :: Symbol) a. IsLabel x a => a
#name FilePath
"from"
(NamedF Identity FilePath "help"
-> Parser (AddressOrAlias 'AddressKindImplicit))
-> Param (NamedF Identity FilePath "help")
-> Parser (AddressOrAlias 'AddressKindImplicit)
forall p fn fn'. WithParam p fn fn' => fn -> Param p -> fn'
! FilePath -> Param (NamedF Identity FilePath "help")
forall (x :: Symbol) a. IsLabel x a => a
#help FilePath
"Address or alias of address from which origination is performed."
Maybe Mutez
oaMbFee <- Parser (Maybe Mutez)
feeOption
Maybe KeyHash
oaDelegate <- Parser KeyHash -> Parser (Maybe KeyHash)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Parser KeyHash -> Parser (Maybe KeyHash))
-> Parser KeyHash -> Parser (Maybe KeyHash)
forall a b. (a -> b) -> a -> b
$ Maybe KeyHash
-> NamedF Identity FilePath "name"
-> NamedF Identity FilePath "help"
-> Parser KeyHash
keyHashOption Maybe KeyHash
forall a. Maybe a
Nothing
(NamedF Identity FilePath "name"
-> NamedF Identity FilePath "help" -> Parser KeyHash)
-> Param (NamedF Identity FilePath "name")
-> NamedF Identity FilePath "help"
-> Parser KeyHash
forall p fn fn'. WithParam p fn fn' => fn -> Param p -> fn'
! FilePath -> Param (NamedF Identity FilePath "name")
forall (x :: Symbol) a. IsLabel x a => a
#name FilePath
"delegate"
(NamedF Identity FilePath "help" -> Parser KeyHash)
-> Param (NamedF Identity FilePath "help") -> Parser KeyHash
forall p fn fn'. WithParam p fn fn' => fn -> Param p -> fn'
! FilePath -> Param (NamedF Identity FilePath "help")
forall (x :: Symbol) a. IsLabel x a => a
#help FilePath
"Key hash of the contract's delegate"
pure OriginateArgs{Maybe FilePath
Maybe Mutez
Maybe KeyHash
Mutez
AddressOrAlias 'AddressKindImplicit
ContractAlias
Value
oaMbContractFile :: Maybe FilePath
oaContractName :: ContractAlias
oaInitialBalance :: Mutez
oaInitialStorage :: Value
oaOriginateFrom :: AddressOrAlias 'AddressKindImplicit
oaMbFee :: Maybe Mutez
oaDelegate :: Maybe KeyHash
oaMbContractFile :: Maybe FilePath
oaContractName :: ContractAlias
oaInitialBalance :: Mutez
oaInitialStorage :: Value
oaOriginateFrom :: AddressOrAlias 'AddressKindImplicit
oaMbFee :: Maybe Mutez
oaDelegate :: Maybe KeyHash
..}
blockIdOption :: Opt.Parser BlockId
blockIdOption :: Parser BlockId
blockIdOption = Maybe BlockId
-> NamedF Identity FilePath "name"
-> NamedF Identity FilePath "help"
-> Parser BlockId
forall a.
(Buildable a, HasCLReader a) =>
Maybe a
-> NamedF Identity FilePath "name"
-> NamedF Identity FilePath "help"
-> Parser a
mkCLOptionParser (BlockId -> Maybe BlockId
forall a. a -> Maybe a
Just BlockId
HeadId)
(NamedF Identity FilePath "name"
-> NamedF Identity FilePath "help" -> Parser BlockId)
-> Param (NamedF Identity FilePath "name")
-> NamedF Identity FilePath "help"
-> Parser BlockId
forall p fn fn'. WithParam p fn fn' => fn -> Param p -> fn'
! FilePath -> Param (NamedF Identity FilePath "name")
forall (x :: Symbol) a. IsLabel x a => a
#name FilePath
"block-id"
(NamedF Identity FilePath "help" -> Parser BlockId)
-> Param (NamedF Identity FilePath "help") -> Parser BlockId
forall p fn fn'. WithParam p fn fn' => fn -> Param p -> fn'
! FilePath -> Param (NamedF Identity FilePath "help")
forall (x :: Symbol) a. IsLabel x a => a
#help FilePath
"Id of the block whose header will be queried."
endpointOption :: Opt.Parser (Maybe BaseUrl)
endpointOption :: Parser (Maybe BaseUrl)
endpointOption = Parser BaseUrl -> Parser (Maybe BaseUrl)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Parser BaseUrl -> Parser (Maybe BaseUrl))
-> (Mod OptionFields BaseUrl -> Parser BaseUrl)
-> Mod OptionFields BaseUrl
-> Parser (Maybe BaseUrl)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ReadM BaseUrl -> Mod OptionFields BaseUrl -> Parser BaseUrl
forall a. ReadM a -> Mod OptionFields a -> Parser a
option ReadM BaseUrl
baseUrlReader (Mod OptionFields BaseUrl -> Parser (Maybe BaseUrl))
-> Mod OptionFields BaseUrl -> Parser (Maybe BaseUrl)
forall a b. (a -> b) -> a -> b
$
FilePath -> Mod OptionFields BaseUrl
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
long FilePath
"endpoint"
Mod OptionFields BaseUrl
-> Mod OptionFields BaseUrl -> Mod OptionFields BaseUrl
forall a. Semigroup a => a -> a -> a
<> Char -> Mod OptionFields BaseUrl
forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
'E'
Mod OptionFields BaseUrl
-> Mod OptionFields BaseUrl -> Mod OptionFields BaseUrl
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod OptionFields BaseUrl
forall (f :: * -> *) a. FilePath -> Mod f a
help FilePath
"URL of the remote Tezos node."
Mod OptionFields BaseUrl
-> Mod OptionFields BaseUrl -> Mod OptionFields BaseUrl
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod OptionFields BaseUrl
forall (f :: * -> *) a. HasMetavar f => FilePath -> Mod f a
metavar FilePath
"URL"
pathOption :: Opt.Parser FilePath
pathOption :: Parser FilePath
pathOption = Mod OptionFields FilePath -> Parser FilePath
forall s. IsString s => Mod OptionFields s -> Parser s
strOption (Mod OptionFields FilePath -> Parser FilePath)
-> Mod OptionFields FilePath -> Parser FilePath
forall a b. (a -> b) -> a -> b
$
[Mod OptionFields FilePath] -> Mod OptionFields FilePath
forall a. Monoid a => [a] -> a
mconcat [ Char -> Mod OptionFields FilePath
forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
'I', FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
long FilePath
"client-path", FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. HasMetavar f => FilePath -> Mod f a
metavar FilePath
"PATH"
, FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. FilePath -> Mod f a
help FilePath
"Path to `octez-client` binary."
, FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. HasValue f => a -> Mod f a
value FilePath
"octez-client"
, Mod OptionFields FilePath
forall a (f :: * -> *). Show a => Mod f a
Opt.showDefault
]
dataDirOption :: Opt.Parser (Maybe FilePath)
dataDirOption :: Parser (Maybe FilePath)
dataDirOption = Parser FilePath -> Parser (Maybe FilePath)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Parser FilePath -> Parser (Maybe FilePath))
-> Parser FilePath -> Parser (Maybe FilePath)
forall a b. (a -> b) -> a -> b
$ Mod OptionFields FilePath -> Parser FilePath
forall s. IsString s => Mod OptionFields s -> Parser s
strOption (Mod OptionFields FilePath -> Parser FilePath)
-> Mod OptionFields FilePath -> Parser FilePath
forall a b. (a -> b) -> a -> b
$
[Mod OptionFields FilePath] -> Mod OptionFields FilePath
forall a. Monoid a => [a] -> a
mconcat [ Char -> Mod OptionFields FilePath
forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
'd', FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
long FilePath
"data-dir", FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. HasMetavar f => FilePath -> Mod f a
metavar FilePath
"PATH"
, FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. FilePath -> Mod f a
help FilePath
"Path to `octez-client` data directory."
]
feeOption :: Opt.Parser (Maybe Mutez)
feeOption :: Parser (Maybe Mutez)
feeOption = Parser Mutez -> Parser (Maybe Mutez)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Parser Mutez -> Parser (Maybe Mutez))
-> Parser Mutez -> Parser (Maybe Mutez)
forall a b. (a -> b) -> a -> b
$ Maybe Mutez
-> NamedF Identity FilePath "name"
-> NamedF Identity FilePath "help"
-> Parser Mutez
mutezOption Maybe Mutez
forall a. Maybe a
Nothing
(NamedF Identity FilePath "name"
-> NamedF Identity FilePath "help" -> Parser Mutez)
-> Param (NamedF Identity FilePath "name")
-> NamedF Identity FilePath "help"
-> Parser Mutez
forall p fn fn'. WithParam p fn fn' => fn -> Param p -> fn'
! FilePath -> Param (NamedF Identity FilePath "name")
forall (x :: Symbol) a. IsLabel x a => a
#name FilePath
"fee"
(NamedF Identity FilePath "help" -> Parser Mutez)
-> Param (NamedF Identity FilePath "help") -> Parser Mutez
forall p fn fn'. WithParam p fn fn' => fn -> Param p -> fn'
! FilePath -> Param (NamedF Identity FilePath "help")
forall (x :: Symbol) a. IsLabel x a => a
#help FilePath
"Fee that is going to be used for the transaction. \
\By default fee will be computed automatically."
mbContractFileOption :: Opt.Parser (Maybe FilePath)
mbContractFileOption :: Parser (Maybe FilePath)
mbContractFileOption = Parser FilePath -> Parser (Maybe FilePath)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Parser FilePath -> Parser (Maybe FilePath))
-> (Mod OptionFields FilePath -> Parser FilePath)
-> Mod OptionFields FilePath
-> Parser (Maybe FilePath)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Mod OptionFields FilePath -> Parser FilePath
forall s. IsString s => Mod OptionFields s -> Parser s
strOption (Mod OptionFields FilePath -> Parser (Maybe FilePath))
-> Mod OptionFields FilePath -> Parser (Maybe FilePath)
forall a b. (a -> b) -> a -> b
$ [Mod OptionFields FilePath] -> Mod OptionFields FilePath
forall a. Monoid a => [a] -> a
mconcat
[ FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
long FilePath
"contract", FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. HasMetavar f => FilePath -> Mod f a
metavar FilePath
"FILEPATH"
, FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. FilePath -> Mod f a
help FilePath
"Path to contract file."
]
scriptFileOption :: Opt.Parser FilePath
scriptFileOption :: Parser FilePath
scriptFileOption = Mod OptionFields FilePath -> Parser FilePath
forall s. IsString s => Mod OptionFields s -> Parser s
strOption (Mod OptionFields FilePath -> Parser FilePath)
-> Mod OptionFields FilePath -> Parser FilePath
forall a b. (a -> b) -> a -> b
$ [Mod OptionFields FilePath] -> Mod OptionFields FilePath
forall a. Monoid a => [a] -> a
mconcat
[ FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
long FilePath
"script", FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. HasMetavar f => FilePath -> Mod f a
metavar FilePath
"FILEPATH"
, FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. FilePath -> Mod f a
help FilePath
"Path to script file."
]
contractNameOption :: Opt.Parser ContractAlias
contractNameOption :: Parser ContractAlias
contractNameOption = (Text -> ContractAlias) -> Parser Text -> Parser ContractAlias
forall a b. (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> ContractAlias
ContractAlias (Parser Text -> Parser ContractAlias)
-> (Mod OptionFields Text -> Parser Text)
-> Mod OptionFields Text
-> Parser ContractAlias
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Mod OptionFields Text -> Parser Text
forall s. IsString s => Mod OptionFields s -> Parser s
strOption (Mod OptionFields Text -> Parser ContractAlias)
-> Mod OptionFields Text -> Parser ContractAlias
forall a b. (a -> b) -> a -> b
$ [Mod OptionFields Text] -> Mod OptionFields Text
forall a. Monoid a => [a] -> a
mconcat
[ FilePath -> Mod OptionFields Text
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
long FilePath
"contract-name"
, Text -> Mod OptionFields Text
forall (f :: * -> *) a. HasValue f => a -> Mod f a
value Text
"stdin"
, FilePath -> Mod OptionFields Text
forall (f :: * -> *) a. FilePath -> Mod f a
help FilePath
"Alias of originated contract."
]
ownerOption
:: (Maybe a -> ("name" :! String) -> ("help" :! String) -> Opt.Parser r)
-> Opt.Parser r
ownerOption :: forall a r.
(Maybe a
-> NamedF Identity FilePath "name"
-> NamedF Identity FilePath "help"
-> Parser r)
-> Parser r
ownerOption Maybe a
-> NamedF Identity FilePath "name"
-> NamedF Identity FilePath "help"
-> Parser r
f = Maybe a
-> NamedF Identity FilePath "name"
-> NamedF Identity FilePath "help"
-> Parser r
f Maybe a
forall a. Maybe a
Nothing
(NamedF Identity FilePath "name"
-> NamedF Identity FilePath "help" -> Parser r)
-> Param (NamedF Identity FilePath "name")
-> NamedF Identity FilePath "help"
-> Parser r
forall p fn fn'. WithParam p fn fn' => fn -> Param p -> fn'
! FilePath -> Param (NamedF Identity FilePath "name")
forall (x :: Symbol) a. IsLabel x a => a
#name FilePath
"owner"
(NamedF Identity FilePath "help" -> Parser r)
-> Param (NamedF Identity FilePath "help") -> Parser r
forall p fn fn'. WithParam p fn fn' => fn -> Param p -> fn'
! FilePath -> Param (NamedF Identity FilePath "help")
forall (x :: Symbol) a. IsLabel x a => a
#help FilePath
"Ticket owner"
baseUrlReader :: ReadM BaseUrl
baseUrlReader :: ReadM BaseUrl
baseUrlReader = (FilePath -> Either FilePath BaseUrl) -> ReadM BaseUrl
forall a. (FilePath -> Either FilePath a) -> ReadM a
eitherReader ((FilePath -> Either FilePath BaseUrl) -> ReadM BaseUrl)
-> (FilePath -> Either FilePath BaseUrl) -> ReadM BaseUrl
forall a b. (a -> b) -> a -> b
$ (SomeException -> FilePath)
-> Either SomeException BaseUrl -> Either FilePath BaseUrl
forall a b c. (a -> b) -> Either a c -> Either b c
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first SomeException -> FilePath
forall e. Exception e => e -> FilePath
displayException (Either SomeException BaseUrl -> Either FilePath BaseUrl)
-> (FilePath -> Either SomeException BaseUrl)
-> FilePath
-> Either FilePath BaseUrl
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> Either SomeException BaseUrl
forall (m :: * -> *). MonadThrow m => FilePath -> m BaseUrl
parseBaseUrl