morley-1.0.0: Developer tools for the Michelson Language

Safe HaskellNone
LanguageHaskell2010

Michelson.Untyped.Instr

Contents

Description

Michelson instructions in untyped model.

Synopsis

Documentation

data InstrAbstract op Source #

Michelson instruction with abstract parameter op. This parameter is necessary, because at different stages of our pipeline it will be different. Initially it can contain macros and non-flattened instructions, but then it contains only vanilla Michelson instructions.

Constructors

EXT (ExtInstrAbstract op) 
DROPN Word

"DROP n" instruction. Note: reference implementation permits int16 here. Negative numbers are parsed successfully there, but rejected later. Morley is more permissive, so we use Word here, i. e. permit more positive numbers. We do not permit negative numbers at type level. In practice, probably nobody will ever have numbers greater than ≈1000 here, at least due to gas limits. Same reasoning applies to other instructions which have a numeric parameter representing number of elements on stack.

DROP

DROP is essentially as special case for DROPN, but we need both because they are packed differently.

DUP VarAnn 
SWAP 
DIG Word 
DUG Word 
PUSH VarAnn Type (Value' op) 
SOME TypeAnn VarAnn 
NONE TypeAnn VarAnn Type 
UNIT TypeAnn VarAnn 
IF_NONE [op] [op] 
PAIR TypeAnn VarAnn FieldAnn FieldAnn 
CAR VarAnn FieldAnn 
CDR VarAnn FieldAnn 
LEFT TypeAnn VarAnn FieldAnn FieldAnn Type 
RIGHT TypeAnn VarAnn FieldAnn FieldAnn Type 
IF_LEFT [op] [op] 
NIL TypeAnn VarAnn Type 
CONS VarAnn 
IF_CONS [op] [op] 
SIZE VarAnn 
EMPTY_SET TypeAnn VarAnn Comparable 
EMPTY_MAP TypeAnn VarAnn Comparable Type 
EMPTY_BIG_MAP TypeAnn VarAnn Comparable Type 
MAP VarAnn [op] 
ITER [op] 
MEM VarAnn 
GET VarAnn 
UPDATE VarAnn 
IF [op] [op] 
LOOP [op] 
LOOP_LEFT [op] 
LAMBDA VarAnn Type Type [op] 
EXEC VarAnn 
APPLY VarAnn 
DIP [op] 
DIPN Word [op] 
FAILWITH 
CAST VarAnn Type 
RENAME VarAnn 
PACK VarAnn 
UNPACK TypeAnn VarAnn Type 
CONCAT VarAnn 
SLICE VarAnn 
ISNAT VarAnn 
ADD VarAnn 
SUB VarAnn 
MUL VarAnn 
EDIV VarAnn 
ABS VarAnn 
NEG VarAnn 
LSL VarAnn 
LSR VarAnn 
OR VarAnn 
AND VarAnn 
XOR VarAnn 
NOT VarAnn 
COMPARE VarAnn 
EQ VarAnn 
NEQ VarAnn 
LT VarAnn 
GT VarAnn 
LE VarAnn 
GE VarAnn 
INT VarAnn 
SELF VarAnn FieldAnn 
CONTRACT VarAnn FieldAnn Type 
TRANSFER_TOKENS VarAnn 
SET_DELEGATE VarAnn 
CREATE_CONTRACT VarAnn VarAnn (Contract' op) 
IMPLICIT_ACCOUNT VarAnn 
NOW VarAnn 
AMOUNT VarAnn 
BALANCE VarAnn 
CHECK_SIGNATURE VarAnn 
SHA256 VarAnn 
SHA512 VarAnn 
BLAKE2B VarAnn 
HASH_KEY VarAnn 
STEPS_TO_QUOTA VarAnn 
SOURCE VarAnn 
SENDER VarAnn 
ADDRESS VarAnn 
CHAIN_ID VarAnn 
Instances
Functor InstrAbstract Source # 
Instance details

Defined in Michelson.Untyped.Instr

Methods

fmap :: (a -> b) -> InstrAbstract a -> InstrAbstract b #

(<$) :: a -> InstrAbstract b -> InstrAbstract a #

Eq op => Eq (InstrAbstract op) Source # 
Instance details

Defined in Michelson.Untyped.Instr

Data op => Data (InstrAbstract op) Source # 
Instance details

Defined in Michelson.Untyped.Instr

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InstrAbstract op -> c (InstrAbstract op) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (InstrAbstract op) #

toConstr :: InstrAbstract op -> Constr #

dataTypeOf :: InstrAbstract op -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (InstrAbstract op)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (InstrAbstract op)) #

gmapT :: (forall b. Data b => b -> b) -> InstrAbstract op -> InstrAbstract op #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InstrAbstract op -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InstrAbstract op -> r #

gmapQ :: (forall d. Data d => d -> u) -> InstrAbstract op -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InstrAbstract op -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InstrAbstract op -> m (InstrAbstract op) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InstrAbstract op -> m (InstrAbstract op) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InstrAbstract op -> m (InstrAbstract op) #

Show op => Show (InstrAbstract op) Source # 
Instance details

Defined in Michelson.Untyped.Instr

Generic (InstrAbstract op) Source # 
Instance details

Defined in Michelson.Untyped.Instr

Associated Types

type Rep (InstrAbstract op) :: Type -> Type #

Methods

from :: InstrAbstract op -> Rep (InstrAbstract op) x #

to :: Rep (InstrAbstract op) x -> InstrAbstract op #

(Arbitrary op, Arbitrary (ExtInstrAbstract op)) => Arbitrary (InstrAbstract op) Source # 
Instance details

Defined in Util.Test.Arbitrary

ToJSON op => ToJSON (InstrAbstract op) Source # 
Instance details

Defined in Michelson.Untyped.Instr

FromJSON op => FromJSON (InstrAbstract op) Source # 
Instance details

Defined in Michelson.Untyped.Instr

(RenderDoc op, Buildable op) => Buildable (InstrAbstract op) Source # 
Instance details

Defined in Michelson.Untyped.Instr

Methods

build :: InstrAbstract op -> Builder #

(Arbitrary op, ToADTArbitrary op, Arbitrary (ExtInstrAbstract op)) => ToADTArbitrary (InstrAbstract op) Source # 
Instance details

Defined in Util.Test.Arbitrary

RenderDoc op => RenderDoc (InstrAbstract op) Source # 
Instance details

Defined in Michelson.Untyped.Instr

type Rep (InstrAbstract op) Source # 
Instance details

Defined in Michelson.Untyped.Instr

type Rep (InstrAbstract op) = D1 (MetaData "InstrAbstract" "Michelson.Untyped.Instr" "morley-1.0.0-Jo9z4xumEmKBIsSgg9Z0MH" False) ((((((C1 (MetaCons "EXT" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (ExtInstrAbstract op))) :+: C1 (MetaCons "DROPN" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Word))) :+: (C1 (MetaCons "DROP" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "DUP" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn)) :+: C1 (MetaCons "SWAP" PrefixI False) (U1 :: Type -> Type)))) :+: ((C1 (MetaCons "DIG" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Word)) :+: C1 (MetaCons "DUG" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Word))) :+: (C1 (MetaCons "PUSH" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Type) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Value' op)))) :+: (C1 (MetaCons "SOME" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 TypeAnn) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn)) :+: C1 (MetaCons "NONE" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 TypeAnn) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Type))))))) :+: (((C1 (MetaCons "UNIT" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 TypeAnn) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn)) :+: C1 (MetaCons "IF_NONE" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 [op]) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 [op]))) :+: (C1 (MetaCons "PAIR" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 TypeAnn) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 FieldAnn) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 FieldAnn))) :+: (C1 (MetaCons "CAR" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 FieldAnn)) :+: C1 (MetaCons "CDR" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 FieldAnn))))) :+: ((C1 (MetaCons "LEFT" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 TypeAnn) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 FieldAnn) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 FieldAnn) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Type)))) :+: (C1 (MetaCons "RIGHT" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 TypeAnn) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 FieldAnn) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 FieldAnn) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Type)))) :+: C1 (MetaCons "IF_LEFT" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 [op]) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 [op])))) :+: (C1 (MetaCons "NIL" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 TypeAnn) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Type))) :+: (C1 (MetaCons "CONS" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn)) :+: C1 (MetaCons "IF_CONS" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 [op]) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 [op]))))))) :+: ((((C1 (MetaCons "SIZE" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn)) :+: C1 (MetaCons "EMPTY_SET" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 TypeAnn) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Comparable)))) :+: (C1 (MetaCons "EMPTY_MAP" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 TypeAnn) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Comparable) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Type))) :+: (C1 (MetaCons "EMPTY_BIG_MAP" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 TypeAnn) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Comparable) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Type))) :+: C1 (MetaCons "MAP" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 [op]))))) :+: ((C1 (MetaCons "ITER" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 [op])) :+: C1 (MetaCons "MEM" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn))) :+: (C1 (MetaCons "GET" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn)) :+: (C1 (MetaCons "UPDATE" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn)) :+: C1 (MetaCons "IF" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 [op]) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 [op])))))) :+: (((C1 (MetaCons "LOOP" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 [op])) :+: C1 (MetaCons "LOOP_LEFT" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 [op]))) :+: (C1 (MetaCons "LAMBDA" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Type)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Type) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 [op]))) :+: (C1 (MetaCons "EXEC" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn)) :+: C1 (MetaCons "APPLY" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn))))) :+: ((C1 (MetaCons "DIP" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 [op])) :+: (C1 (MetaCons "DIPN" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Word) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 [op])) :+: C1 (MetaCons "FAILWITH" PrefixI False) (U1 :: Type -> Type))) :+: (C1 (MetaCons "CAST" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Type)) :+: (C1 (MetaCons "RENAME" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn)) :+: C1 (MetaCons "PACK" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn)))))))) :+: (((((C1 (MetaCons "UNPACK" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 TypeAnn) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Type))) :+: C1 (MetaCons "CONCAT" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn))) :+: (C1 (MetaCons "SLICE" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn)) :+: (C1 (MetaCons "ISNAT" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn)) :+: C1 (MetaCons "ADD" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn))))) :+: ((C1 (MetaCons "SUB" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn)) :+: C1 (MetaCons "MUL" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn))) :+: (C1 (MetaCons "EDIV" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn)) :+: (C1 (MetaCons "ABS" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn)) :+: C1 (MetaCons "NEG" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn)))))) :+: (((C1 (MetaCons "LSL" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn)) :+: C1 (MetaCons "LSR" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn))) :+: (C1 (MetaCons "OR" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn)) :+: (C1 (MetaCons "AND" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn)) :+: C1 (MetaCons "XOR" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn))))) :+: ((C1 (MetaCons "NOT" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn)) :+: (C1 (MetaCons "COMPARE" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn)) :+: C1 (MetaCons "EQ" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn)))) :+: (C1 (MetaCons "NEQ" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn)) :+: (C1 (MetaCons "LT" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn)) :+: C1 (MetaCons "GT" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn))))))) :+: ((((C1 (MetaCons "LE" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn)) :+: C1 (MetaCons "GE" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn))) :+: (C1 (MetaCons "INT" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn)) :+: (C1 (MetaCons "SELF" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 FieldAnn)) :+: C1 (MetaCons "CONTRACT" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 FieldAnn) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Type)))))) :+: ((C1 (MetaCons "TRANSFER_TOKENS" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn)) :+: (C1 (MetaCons "SET_DELEGATE" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn)) :+: C1 (MetaCons "CREATE_CONTRACT" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Contract' op)))))) :+: (C1 (MetaCons "IMPLICIT_ACCOUNT" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn)) :+: (C1 (MetaCons "NOW" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn)) :+: C1 (MetaCons "AMOUNT" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn)))))) :+: (((C1 (MetaCons "BALANCE" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn)) :+: C1 (MetaCons "CHECK_SIGNATURE" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn))) :+: (C1 (MetaCons "SHA256" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn)) :+: (C1 (MetaCons "SHA512" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn)) :+: C1 (MetaCons "BLAKE2B" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn))))) :+: ((C1 (MetaCons "HASH_KEY" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn)) :+: (C1 (MetaCons "STEPS_TO_QUOTA" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn)) :+: C1 (MetaCons "SOURCE" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn)))) :+: (C1 (MetaCons "SENDER" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn)) :+: (C1 (MetaCons "ADDRESS" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn)) :+: C1 (MetaCons "CHAIN_ID" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 VarAnn)))))))))

data ExpandedOp Source #

Instances
Eq ExpandedOp Source # 
Instance details

Defined in Michelson.Untyped.Instr

Data ExpandedOp Source # 
Instance details

Defined in Michelson.Untyped.Instr

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ExpandedOp -> c ExpandedOp #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ExpandedOp #

toConstr :: ExpandedOp -> Constr #

dataTypeOf :: ExpandedOp -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ExpandedOp) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ExpandedOp) #

gmapT :: (forall b. Data b => b -> b) -> ExpandedOp -> ExpandedOp #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ExpandedOp -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ExpandedOp -> r #

gmapQ :: (forall d. Data d => d -> u) -> ExpandedOp -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ExpandedOp -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ExpandedOp -> m ExpandedOp #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ExpandedOp -> m ExpandedOp #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ExpandedOp -> m ExpandedOp #

Show ExpandedOp Source # 
Instance details

Defined in Michelson.Untyped.Instr

Generic ExpandedOp Source # 
Instance details

Defined in Michelson.Untyped.Instr

Associated Types

type Rep ExpandedOp :: Type -> Type #

Arbitrary ExpandedOp Source # 
Instance details

Defined in Util.Test.Arbitrary

Arbitrary ExpandedExtInstr Source # 
Instance details

Defined in Util.Test.Arbitrary

ToJSON ExpandedOp Source # 
Instance details

Defined in Michelson.Untyped.Instr

FromJSON ExpandedOp Source # 
Instance details

Defined in Michelson.Untyped.Instr

Buildable ExpandedOp Source # 
Instance details

Defined in Michelson.Untyped.Instr

Methods

build :: ExpandedOp -> Builder #

ToADTArbitrary ExpandedOp Source # 
Instance details

Defined in Util.Test.Arbitrary

RenderDoc ExpandedOp Source # 
Instance details

Defined in Michelson.Untyped.Instr

type Rep ExpandedOp Source # 
Instance details

Defined in Michelson.Untyped.Instr

flattenExpandedOp :: ExpandedOp -> [ExpandedInstr] Source #

Flatten all SeqEx in ExpandedOp. This function is mostly for testing. It returns instructions with the same logic, but they are not strictly equivalent, because they are serialized differently (grouping instructions into sequences affects the way they are PACK'ed).

Contract's address

data OriginationOperation Source #

Data necessary to originate a contract.

Constructors

OriginationOperation 

Fields

Instances
Show OriginationOperation Source # 
Instance details

Defined in Michelson.Untyped.Instr

Generic OriginationOperation Source # 
Instance details

Defined in Michelson.Untyped.Instr

Associated Types

type Rep OriginationOperation :: Type -> Type #

ToJSON OriginationOperation Source # 
Instance details

Defined in Michelson.Untyped.Instr

FromJSON OriginationOperation Source # 
Instance details

Defined in Michelson.Untyped.Instr

type Rep OriginationOperation Source # 
Instance details

Defined in Michelson.Untyped.Instr

mkContractAddress :: OriginationOperation -> Address Source #

Compute address of a contract from its origination operation.

TODO [TM-62] It's certainly imprecise, real Tezos implementation doesn't use JSON, but we don't need precise format yet, so we just use some serialization format (JSON because we have necessary instances already).