-- SPDX-FileCopyrightText: 2020 Tocqueville Group -- -- SPDX-License-Identifier: LicenseRef-MIT-TQ -- | Measuring operation size. -- -- When originating a contract or making a transfer, tezos node forms operation -- which is submitted over network. Size of this operation depends on content -- of originated contract or transfer parameter resp., and tezos has a hard -- limit on operation size thus it has to be accounted. -- -- Functions declared in this module allow assessing size of origination or -- transfer operation with up to constant precision because it yet accounts only -- for Michelson primitives participating in the operation. -- Other stuff which affects op size include parameters which user passes to -- origination or transfer themselves, for instance, amount of mutez carried -- to the contract. ATM we don't have necessary primitives in Haskell to be -- able to handle those parameters here, probably waiting for [TM-89]. -- Currently, we can assess overall transfer size only approximately, like -- in 'smallTransferOpSize'. module Morley.Michelson.Untyped.OpSize ( OpSize (..) , opSizeHardLimit , smallTransferOpSize , instrOpSize , expandedInstrsOpSize , valueOpSize ) where import Fmt (Buildable(..)) import Prelude hiding (Ordering(..)) import qualified Unsafe (fromIntegral) import Morley.Michelson.Interpret.Utils import Morley.Michelson.Untyped.Aliases import Morley.Michelson.Untyped.Annotation import Morley.Michelson.Untyped.Contract import Morley.Michelson.Untyped.Instr import Morley.Michelson.Untyped.Type import Morley.Michelson.Untyped.Value import Morley.Michelson.Untyped.View -- | Operation size in bytes. -- -- We use newtype wrapper because there are different units of measure -- (another one is gas, and we don't want to confuse them). newtype OpSize = OpSize { unOpSize :: Word } deriving stock (Show, Eq, Ord) instance Buildable OpSize where build = build . unOpSize instance Semigroup OpSize where OpSize a <> OpSize b = OpSize (a + b) instance Monoid OpSize where mempty = OpSize 0 -- | Maximal operation size allowed by Tezos production nodes. opSizeHardLimit :: OpSize opSizeHardLimit = OpSize 16384 -- | Base cost of any transfer of 0 mutez with no extra parameters. -- (Add @valueOpSize \@ to it to get assessment of actual transfer op size) smallTransferOpSize :: OpSize smallTransferOpSize = OpSize 162 instrOpSize :: InstrAbstract ExpandedOp -> OpSize instrOpSize = (OpSize 2 <>) . \case EXT{} -> mempty DROPN n -> stackDepthOpSize n DROP -> mempty DUP va -> annsOpSize va DUPN va n -> annsOpSize va <> stackDepthOpSize n SWAP -> mempty DIG n -> stackDepthOpSize n DUG n -> stackDepthOpSize n PUSH va t v -> annsOpSize va <> typeOpSize t <> valueOpSize v SOME ta va -> annsOpSize ta va NONE ta va t -> annsOpSize ta va <> typeOpSize t UNIT ta va -> annsOpSize ta va IF_NONE l r -> ifOpSize l r PAIR ta va fal far -> annsOpSize ta va fal far UNPAIR va1 va2 fal far -> annsOpSize va1 va2 fal far PAIRN va n -> annsOpSize va <> stackDepthOpSize n UNPAIRN n -> stackDepthOpSize n CAR va fa -> annsOpSize va fa CDR va fa -> annsOpSize va fa LEFT ta va fal far t -> annsOpSize ta va fal far <> typeOpSize t RIGHT ta va fal far t -> annsOpSize ta va fal far <> typeOpSize t IF_LEFT l r -> ifOpSize l r NIL ta va t -> annsOpSize ta va <> typeOpSize t CONS va -> annsOpSize va IF_CONS l r -> ifOpSize l r SIZE va -> annsOpSize va EMPTY_SET ta va ct -> annsOpSize ta va <> innerOpSize ct EMPTY_MAP ta va ct t -> annsOpSize ta va <> innerOpSize ct <> typeOpSize t EMPTY_BIG_MAP ta va ct t -> annsOpSize ta va <> innerOpSize ct <> typeOpSize t MAP va is -> annsOpSize va <> subcodeOpSize is ITER is -> subcodeOpSize is MEM va -> annsOpSize va GET va -> annsOpSize va GETN va n -> annsOpSize va <> stackDepthOpSize n UPDATE va -> annsOpSize va UPDATEN va n -> annsOpSize va <> stackDepthOpSize n GET_AND_UPDATE va -> annsOpSize va IF l r -> ifOpSize l r LOOP is -> expandedInstrsOpSize is LOOP_LEFT is -> expandedInstrsOpSize is LAMBDA va ti to is -> annsOpSize va <> typeOpSize ti <> typeOpSize to <> expandedInstrsOpSize is EXEC va -> annsOpSize va APPLY va -> annsOpSize va DIP is -> subcodeOpSize is DIPN n is -> stackDepthOpSize n <> subcodeOpSize is FAILWITH -> mempty CAST va t -> annsOpSize va <> typeOpSize t RENAME va -> annsOpSize va PACK va -> annsOpSize va UNPACK ta va t -> annsOpSize ta va <> typeOpSize t CONCAT va -> annsOpSize va SLICE va -> annsOpSize va ISNAT va -> annsOpSize va ADD va -> annsOpSize va SUB va -> annsOpSize va MUL va -> annsOpSize va EDIV va -> annsOpSize va ABS va -> annsOpSize va NEG va -> annsOpSize va LSL va -> annsOpSize va LSR va -> annsOpSize va OR va -> annsOpSize va AND va -> annsOpSize va XOR va -> annsOpSize va NOT va -> annsOpSize va COMPARE va -> annsOpSize va EQ va -> annsOpSize va NEQ va -> annsOpSize va LT va -> annsOpSize va LE va -> annsOpSize va GT va -> annsOpSize va GE va -> annsOpSize va INT va -> annsOpSize va VIEW va n t -> annsOpSize va <> viewNameSize n <> typeOpSize t SELF va fa -> annsOpSize va fa CONTRACT va fa t -> annsOpSize va fa <> typeOpSize t TRANSFER_TOKENS va -> annsOpSize va SET_DELEGATE va -> annsOpSize va CREATE_CONTRACT va1 va2 c -> annsOpSize va1 va2 <> contractOpSize c IMPLICIT_ACCOUNT va -> annsOpSize va NOW va -> annsOpSize va AMOUNT va -> annsOpSize va BALANCE va -> annsOpSize va VOTING_POWER va -> annsOpSize va TOTAL_VOTING_POWER va -> annsOpSize va CHECK_SIGNATURE va -> annsOpSize va SHA256 va -> annsOpSize va SHA512 va -> annsOpSize va BLAKE2B va -> annsOpSize va SHA3 va -> annsOpSize va KECCAK va -> annsOpSize va HASH_KEY va -> annsOpSize va PAIRING_CHECK va -> annsOpSize va SOURCE va -> annsOpSize va SENDER va -> annsOpSize va ADDRESS va -> annsOpSize va CHAIN_ID va -> annsOpSize va LEVEL va -> annsOpSize va SELF_ADDRESS va -> annsOpSize va NEVER -> mempty TICKET va -> annsOpSize va READ_TICKET va -> annsOpSize va SPLIT_TICKET va -> annsOpSize va JOIN_TICKETS va -> annsOpSize va OPEN_CHEST va -> annsOpSize va where subcodeOpSize is = expandedInstrOpSize (SeqEx is) ifOpSize l r = expandedInstrOpSize (SeqEx l) <> expandedInstrOpSize (SeqEx r) stackDepthOpSize n = OpSize 1 <> numOpSize n expandedInstrOpSize :: ExpandedOp -> OpSize expandedInstrOpSize = \case PrimEx i -> instrOpSize i SeqEx is -> OpSize 5 <> expandedInstrsOpSize is WithSrcEx _ i -> expandedInstrOpSize i expandedInstrsOpSize :: [ExpandedOp] -> OpSize expandedInstrsOpSize = foldMap expandedInstrOpSize viewNameSize :: ViewName -> OpSize viewNameSize = OpSize . Unsafe.fromIntegral @Int @Word . length . unViewName viewOpSize :: View -> OpSize viewOpSize (View name param ret code) = mconcat [ OpSize 2 , viewNameSize name , typeOpSize param , typeOpSize ret , expandedInstrsOpSize code ] contractOpSize :: Contract -> OpSize contractOpSize (Contract (ParameterType cp rootAnn) st is _ view_) = OpSize 16 <> typeOpSize' [rootAnn] cp <> typeOpSize st <> expandedInstrsOpSize is <> foldMap viewOpSize view_ numOpSize :: Integral i => i -> OpSize numOpSize = OpSize . Unsafe.fromIntegral @Int @Word . length . encodeZarithNumber . fromIntegral valueOpSize :: Value -> OpSize valueOpSize = (OpSize 1 <>) . \case ValueInt i -> numOpSize i ValueString s -> (seqOpSize <>) . OpSize . Unsafe.fromIntegral @Int @Word $ length s ValueBytes (InternalByteString b) -> (seqOpSize <>) . OpSize . Unsafe.fromIntegral @Int @Word $ length b ValueUnit -> baseOpSize ValueTrue -> baseOpSize ValueFalse -> baseOpSize ValuePair l r -> baseOpSize <> valueOpSize l <> valueOpSize r ValueLeft x -> baseOpSize <> valueOpSize x ValueRight x -> baseOpSize <> valueOpSize x ValueSome x -> baseOpSize <> valueOpSize x ValueNone -> baseOpSize ValueNil -> seqOpSize ValueSeq l -> seqOpSize <> foldMap valueOpSize l ValueMap m -> seqOpSize <> foldMap eltOpSize m ValueLambda m -> seqOpSize <> foldMap expandedInstrOpSize m where baseOpSize = OpSize 1 seqOpSize = OpSize 4 eltOpSize (Elt k v) = OpSize 2 <> valueOpSize k <> valueOpSize v typeOpSize :: Ty -> OpSize typeOpSize = typeOpSize' [] typeOpSize' :: [FieldAnn] -> Ty -> OpSize typeOpSize' anns (Ty t ta) = tOpSize t <> annsOpSize ta anns tOpSize :: T -> OpSize tOpSize t = OpSize 2 <> case t of TKey -> mempty TUnit -> mempty TSignature -> mempty TChainId -> mempty TOption a -> typeOpSize a TList a -> typeOpSize a TSet a -> innerOpSize a TOperation -> mempty TTicket a -> typeOpSize a TContract a -> typeOpSize a -- Nested variable annotations don't use any extra operation size. TPair al ar _ _ l r -> typeOpSize' [al] l <> typeOpSize' [ar] r TOr al ar l r -> typeOpSize' [al] l <> typeOpSize' [ar] r TLambda i o -> typeOpSize i <> typeOpSize o TMap k v -> innerOpSize k <> typeOpSize v TBigMap k v -> innerOpSize k <> typeOpSize v TInt -> mempty TNat -> mempty TString -> mempty TBytes -> mempty TMutez -> mempty TBool -> mempty TKeyHash -> mempty TBls12381Fr -> mempty TBls12381G1 -> mempty TBls12381G2 -> mempty TTimestamp -> mempty TAddress -> mempty TChest -> mempty TChestKey -> mempty TNever -> mempty innerOpSize :: Ty -> OpSize innerOpSize (Ty _ a) = (OpSize 2) <> annsOpSize a -- | Accepts an arbitrary number of 'TypeAnn' 'FieldAnn' and/or 'VarAnn' that -- belong to the same entity and returns their total operation size. -- -- Note that annotations which belong to the same entity (type or instruction) -- __must be__ considered in aggregate using one call of this function and to be -- specified in order. See 'AnnotationSet' for details. annsOpSize :: AnnsOpSizeVararg x => x annsOpSize = annsOpSizeVararg emptyAnnSet class AnnsOpSizeVararg x where annsOpSizeVararg :: AnnotationSet -> x instance (KnownAnnTag t, AnnsOpSizeVararg x) => AnnsOpSizeVararg (Annotation t -> x) where annsOpSizeVararg acc an = annsOpSizeVararg (acc <> singleAnnSet an) instance (KnownAnnTag t, AnnsOpSizeVararg x) => AnnsOpSizeVararg ([Annotation t] -> x) where annsOpSizeVararg acc ans = annsOpSizeVararg (acc <> singleGroupAnnSet ans) instance AnnsOpSizeVararg OpSize where annsOpSizeVararg = annsOpSizeImpl annsOpSizeImpl :: AnnotationSet -> OpSize annsOpSizeImpl annSet | isNoAnnSet annSet = mempty | otherwise = OpSize . Unsafe.fromIntegral @Int @Word $ 3 * (minAnnSetSize annSet + 1)