-- SPDX-FileCopyrightText: 2020 Tocqueville Group -- -- SPDX-License-Identifier: LicenseRef-MIT-TQ module Michelson.Typed.Origination ( OriginationOperation(..) , mkOriginationOperationHash -- * Operation hashing , OperationHash (..) , mkContractAddress ) where import Data.Binary.Put (putInt32be, putWord64be, runPut) import qualified Data.ByteString.Lazy as BSL import Michelson.Interpret.Pack (toBinary') import Michelson.Typed.Aliases (Value) import Michelson.Typed.Haskell.Value (IsoValue(..)) import Michelson.Typed.Instr (Contract(..), cCode) import Michelson.Typed.Scope (ParameterScope, StorageScope) import Tezos.Address (Address(ContractAddress), ContractHash(..), GlobalCounter(..), OriginationIndex(..)) import Tezos.Core (Mutez(..)) import Tezos.Crypto (KeyHash, blake2b, blake2b160) -- | Data necessary to originate a contract. data OriginationOperation = forall cp st. (StorageScope st, ParameterScope cp) => OriginationOperation { ooOriginator :: Address -- ^ Originator of the contract. , ooDelegate :: Maybe KeyHash -- ^ Optional delegate. , ooBalance :: Mutez -- ^ Initial balance of the contract. , ooStorage :: Value st -- ^ Initial storage value of the contract. , ooContract :: Contract cp st -- ^ The contract itself. } deriving stock instance Show OriginationOperation -- | Construct 'OperationHash' for an 'OriginationOperation'. mkOriginationOperationHash :: OriginationOperation -> OperationHash mkOriginationOperationHash OriginationOperation{..} = OperationHash $ blake2b packedOperation where -- In Tezos OriginationOperation is encoded as 4-tuple of -- (balance, optional delegate, code, storage) -- -- See https://gitlab.com/tezos/tezos/-/blob/f57c50e3a657956d69a1699978de9873c98f0018/src/proto_006_PsCARTHA/lib_protocol/operation_repr.ml#L314 -- and https://gitlab.com/tezos/tezos/-/blob/f57c50e3a657956d69a1699978de9873c98f0018/src/proto_006_PsCARTHA/lib_protocol/script_repr.ml#L68 packedOperation = BSL.toStrict (runPut $ putWord64be $ unMutez ooBalance) <> packMaybe (toBinary' . toVal) ooDelegate <> toBinary' (cCode ooContract) <> toBinary' ooStorage -- "optional" encoding in Tezos. -- -- See https://gitlab.com/nomadic-labs/data-encoding/-/blob/2c2b795a37e7d76e3eaa861da9855f2098edc9b9/src/binary_writer.ml#L278-283 packMaybe :: (a -> ByteString) -> Maybe a -> ByteString packMaybe _ Nothing = "\255" packMaybe f (Just a) = "\0" <> f a ---------------------------------------------------------------------------- -- Operation hash ---------------------------------------------------------------------------- newtype OperationHash = OperationHash { unOperationHash :: ByteString } deriving stock (Show, Eq, Ord, Generic) deriving anyclass (NFData) -- | Compute address of a contract from its origination operation, origination index and global counter. -- -- However, in real Tezos encoding of the operation is more than just 'OriginationOperation'. -- There an Operation has several more meta-fields plus a big sum-type of all possible operations. -- -- See here: https://gitlab.com/tezos/tezos/-/blob/f57c50e3a657956d69a1699978de9873c98f0018/src/proto_006_PsCARTHA/lib_protocol/operation_repr.ml#L78 -- -- What is important is that one (big) Operation may lead to origination of multiple contracts. That -- is why contract address is constructed from hash of the operation that originated and of index -- of the contract's origination in the execution of that operation. -- -- In other words, contract hash is calculated as the blake2b160 (20-byte) hash of -- origination operation hash + int32 origination index + word64 global counter. -- -- In Morley we do not yet support full encoding of Tezos Operations, therefore we choose -- to generate contract addresses in a simplified manner. -- -- Namely, we encode 'OriginationOperation' as we can and concat it with the origination index -- and the global counter. -- Then we take 'blake2b160' hash of the resulting bytes and consider it to be the contract's -- address. mkContractAddress :: OperationHash -> OriginationIndex -> GlobalCounter -> Address mkContractAddress (OperationHash opHash) (OriginationIndex idx) (GlobalCounter counter) = ContractAddress $ ContractHash $ blake2b160 $ opHash <> BSL.toStrict (runPut $ putInt32be idx >> putWord64be counter)