-- SPDX-FileCopyrightText: 2021 Oxhead Alpha -- SPDX-License-Identifier: LicenseRef-MIT-OA -- | Functions to originate smart contracts via @octez-client@ and node RPC. module Morley.Client.Action.Origination ( originateContract , originateContracts , originateUntypedContract -- Lorentz version , lOriginateContract , lOriginateContracts -- * Large originations , originateLargeContracts , originateLargeContract , originateLargeUntypedContract -- Lorentz version , lOriginateLargeContracts , lOriginateLargeContract -- Datatypes for batch originations , LOriginationData (..) , OriginationData (..) ) where import Data.Default (def) import Lorentz qualified as L import Lorentz.Constraints import Morley.Client.Action.Common import Morley.Client.Action.Operation import Morley.Client.Action.Origination.Large import Morley.Client.Action.Transaction (runTransactions) import Morley.Client.Logging import Morley.Client.RPC.Class import Morley.Client.RPC.Error import Morley.Client.RPC.Types import Morley.Client.TezosClient import Morley.Client.Types import Morley.Michelson.TypeCheck (typeCheckContractAndStorage, typeCheckingWith) import Morley.Michelson.Typed (Contract, IsoValue(..), SomeContractAndStorage(..), Value) import Morley.Michelson.Typed.Scope import Morley.Michelson.Untyped qualified as U import Morley.Tezos.Address import Morley.Tezos.Address.Alias import Morley.Tezos.Core import Morley.Util.Exception -- | Originate given contracts with given initial storages. Returns -- operation hash (or @Nothing@ in case empty list was provided) -- and originated contracts' addresses. originateContracts :: forall m env. ( HasTezosRpc m , HasTezosClient m , WithClientLog env m ) => ImplicitAddressWithAlias -> [OriginationData] -> m (Maybe OperationHash, [ContractAddress]) originateContracts sender originations = do (opHash, res) <- runOperations sender (OpOriginate <$> originations) return (opHash, getOriginations res) where getOriginations = mapMaybe \case OpOriginate r -> Just r OpReveal{} -> Nothing _ -> error "Unexpectedly not origination" -- | Originate single contract originateContract :: forall m cp st env. ( HasTezosRpc m , HasTezosClient m , WithClientLog env m , StorageScope st , ParameterScope cp ) => AliasBehavior -> ContractAlias -> ImplicitAddressWithAlias -> Mutez -> Contract cp st -> Value st -> Maybe Mutez -> Maybe L.KeyHash -> m (OperationHash, ContractAddress) originateContract odAliasBehavior odName sender' odBalance odContract odStorage odMbFee odDelegate = do (hash, contracts) <- originateContracts sender' [OriginationData{..}] singleOriginatedContract hash contracts -- | Originate a single untyped contract originateUntypedContract :: forall m env. ( HasTezosRpc m , HasTezosClient m , WithClientLog env m ) => AliasBehavior -> ContractAlias -> ImplicitAddressWithAlias -> Mutez -> U.Contract -> U.Value -> Maybe Mutez -> Maybe L.KeyHash -> m (OperationHash, ContractAddress) originateUntypedContract aliasBehavior name sender' balance uContract initialStorage mbFee mbDelegate = do SomeContractAndStorage contract storage <- throwLeft . pure . typeCheckingWith def $ typeCheckContractAndStorage uContract initialStorage originateContract aliasBehavior name sender' balance contract storage mbFee mbDelegate -- | Lorentz version of 'originateContracts' lOriginateContracts :: forall m env. ( HasTezosRpc m , HasTezosClient m , WithClientLog env m ) => ImplicitAddressWithAlias -> [LOriginationData] -> m (Maybe OperationHash, [ContractAddress]) lOriginateContracts sender' originations = originateContracts sender' $ map convertLOriginationData originations -- | Originate single Lorentz contract lOriginateContract :: forall m cp st vd env. ( HasTezosRpc m , HasTezosClient m , WithClientLog env m , NiceStorage st , NiceParameterFull cp ) => AliasBehavior -> ContractAlias -> ImplicitAddressWithAlias -> Mutez -> L.Contract cp st vd -> st -> Maybe Mutez -> Maybe L.KeyHash -> m (OperationHash, ContractAddress) lOriginateContract lodAliasBehavior lodName sender' lodBalance lodContract lodStorage lodMbFee lodDelegate = do (hash, contracts) <- lOriginateContracts sender' [LOriginationData{..}] singleOriginatedContract @m hash contracts -------------------------------------------------------------------------------- -- Large Originations -------------------------------------------------------------------------------- -- | Automated multi-step origination process for contracts that don't fit into -- the origination limit. See "Morley.Client.Action.Origination.Large". originateLargeContracts :: forall m env. ( HasTezosRpc m , HasTezosClient m , WithClientLog env m ) => ImplicitAddressWithAlias -> [OriginationData] -> m (Maybe OperationHash, [ContractAddress]) originateLargeContracts sender'@(AddressWithAlias senderAddress _) largeOriginations = do -- calculate large contract originators let originators = map mkLargeOriginationData largeOriginations -- originate them. Note: we use the operation hash from here even tho the -- large contracts are originated in another one, because those happen in -- several different transactions. (opHash, originatorsAddr) <- originateContracts sender' $ map (mkLargeOriginatorData senderAddress) originators -- run all the transactions needed (for each large contract originator) -- Note: it is not possible to run these all at once, because the node won't -- accept a transaction batch where the sum of the storage cost is over 16k, -- so here we need to run them one by one. mapM_ (runTransactions sender' . (: [])) . concat $ zipWith mkLargeOriginatorTransactions originatorsAddr originators -- get the addresses of the originated large contracts back from the originators -- and remember their addresses with their aliases originatedContracts <- zipWithM retrieveLargeContracts originatorsAddr largeOriginations return (opHash, originatedContracts) -- | Originate a single large contract originateLargeContract :: forall m cp st env. ( HasTezosRpc m , HasTezosClient m , WithClientLog env m , StorageScope st , ParameterScope cp ) => AliasBehavior -> ContractAlias -> ImplicitAddressWithAlias -> Mutez -> Contract cp st -> Value st -> Maybe Mutez -> Maybe L.KeyHash -> m (OperationHash, ContractAddress) originateLargeContract odAliasBehavior odName sender' odBalance odContract odStorage odMbFee odDelegate = do (hash, contracts) <- originateLargeContracts sender' [OriginationData{..}] singleOriginatedContract @m hash contracts -- | Originate a single untyped large contract originateLargeUntypedContract :: forall m env. ( HasTezosRpc m , HasTezosClient m , WithClientLog env m ) => AliasBehavior -> ContractAlias -> ImplicitAddressWithAlias -> Mutez -> U.Contract -> U.Value -> Maybe Mutez -> Maybe L.KeyHash -> m (OperationHash, ContractAddress) originateLargeUntypedContract aliasBehavior name sender' balance uContract initialStorage mbFee mbDelegate = do SomeContractAndStorage contract storage <- throwLeft . pure . typeCheckingWith def $ typeCheckContractAndStorage uContract initialStorage originateLargeContract aliasBehavior name sender' balance contract storage mbFee mbDelegate -- | Lorentz version of 'originateLargeContracts' lOriginateLargeContracts :: forall m env. ( HasTezosRpc m , HasTezosClient m , WithClientLog env m ) => ImplicitAddressWithAlias -> [LOriginationData] -> m (Maybe OperationHash, [ContractAddress]) lOriginateLargeContracts sender' originations = originateLargeContracts sender' $ map convertLOriginationData originations -- | Originate a single large Lorentz contract lOriginateLargeContract :: forall m cp st vd env. ( HasTezosRpc m , HasTezosClient m , WithClientLog env m , NiceStorage st , NiceParameter cp ) => AliasBehavior -> ContractAlias -> ImplicitAddressWithAlias -> Mutez -> L.Contract cp st vd -> st -> Maybe Mutez -> Maybe L.KeyHash -> m (OperationHash, ContractAddress) lOriginateLargeContract lodAliasBehavior lodName sender' lodBalance lodContract lodStorage lodMbFee lodDelegate = do (hash, contracts) <- lOriginateLargeContracts sender' [LOriginationData{..}] singleOriginatedContract @m hash contracts -------------------------------------------------------------------------------- -- Utilities -------------------------------------------------------------------------------- -- | Lorentz version of 'OriginationData' data LOriginationData = forall cp st vd. (NiceParameter cp, NiceStorage st) => LOriginationData { lodAliasBehavior :: AliasBehavior , lodName :: ContractAlias , lodBalance :: Mutez , lodContract :: L.Contract cp st vd , lodStorage :: st , lodDelegate :: Maybe L.KeyHash , lodMbFee :: Maybe Mutez } convertLOriginationData :: LOriginationData -> OriginationData convertLOriginationData LOriginationData {..} = case lodContract of (_ :: L.Contract cp st vd) -> OriginationData { odAliasBehavior = lodAliasBehavior , odName = lodName , odBalance = lodBalance , odContract = L.toMichelsonContract lodContract , odStorage = toVal lodStorage , odDelegate = lodDelegate , odMbFee = lodMbFee } -- | Checks that the origination result for a single contract is indeed one. singleOriginatedContract :: forall m. HasTezosRpc m => Maybe OperationHash -> [ContractAddress] -> m (OperationHash, ContractAddress) singleOriginatedContract mbHash contracts = case contracts of [addr] -> case mbHash of Just hash -> return (hash, addr) Nothing -> throwM $ RpcOriginatedNoContracts _ -> throwM $ RpcOriginatedMoreContracts contracts