morley-1.18.0: Developer tools for the Michelson Language
Safe HaskellSafe-Inferred
LanguageHaskell2010

Morley.Michelson.Untyped.Instr

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 
DUPN VarAnn Word 
SWAP 
DIG Word 
DUG Word 
PUSH VarAnn Ty (Value' op) 
SOME TypeAnn VarAnn 
NONE TypeAnn VarAnn Ty 
UNIT TypeAnn VarAnn 
IF_NONE [op] [op] 
PAIR TypeAnn VarAnn FieldAnn FieldAnn 
UNPAIR VarAnn VarAnn FieldAnn FieldAnn 
PAIRN VarAnn Word 
UNPAIRN Word 
CAR VarAnn FieldAnn 
CDR VarAnn FieldAnn 
LEFT TypeAnn VarAnn FieldAnn FieldAnn Ty 
RIGHT TypeAnn VarAnn FieldAnn FieldAnn Ty 
IF_LEFT [op] [op] 
NIL TypeAnn VarAnn Ty 
CONS VarAnn 
IF_CONS [op] [op] 
SIZE VarAnn 
EMPTY_SET TypeAnn VarAnn Ty 
EMPTY_MAP TypeAnn VarAnn Ty Ty 
EMPTY_BIG_MAP TypeAnn VarAnn Ty Ty 
MAP VarAnn [op] 
ITER [op] 
MEM VarAnn 
GET VarAnn 
GETN VarAnn Word 
UPDATE VarAnn 
UPDATEN VarAnn Word 
GET_AND_UPDATE VarAnn 
IF [op] [op] 
LOOP [op] 
LOOP_LEFT [op] 
LAMBDA VarAnn Ty Ty [op] 
EXEC VarAnn 
APPLY VarAnn 
DIP [op] 
DIPN Word [op] 
FAILWITH 
CAST VarAnn Ty 
RENAME VarAnn 
PACK VarAnn 
UNPACK TypeAnn VarAnn Ty 
CONCAT VarAnn 
SLICE VarAnn 
ISNAT VarAnn 
ADD VarAnn 
SUB VarAnn 
SUB_MUTEZ 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 
VIEW VarAnn ViewName Ty 
SELF VarAnn FieldAnn 
CONTRACT VarAnn FieldAnn Ty 
TRANSFER_TOKENS VarAnn 
SET_DELEGATE VarAnn 
CREATE_CONTRACT VarAnn VarAnn (Contract' op) 
IMPLICIT_ACCOUNT VarAnn 
NOW VarAnn 
AMOUNT VarAnn 
BALANCE VarAnn 
VOTING_POWER VarAnn 
TOTAL_VOTING_POWER VarAnn 
CHECK_SIGNATURE VarAnn 
SHA256 VarAnn 
SHA512 VarAnn 
BLAKE2B VarAnn 
SHA3 VarAnn 
KECCAK VarAnn 
HASH_KEY VarAnn 
PAIRING_CHECK VarAnn 
SOURCE VarAnn 
SENDER VarAnn 
ADDRESS VarAnn 
CHAIN_ID VarAnn 
LEVEL VarAnn 
SELF_ADDRESS VarAnn 
NEVER 
TICKET VarAnn 
READ_TICKET VarAnn 
SPLIT_TICKET VarAnn 
JOIN_TICKETS VarAnn 
OPEN_CHEST VarAnn 
SAPLING_EMPTY_STATE VarAnn Natural 
SAPLING_VERIFY_UPDATE VarAnn 
MIN_BLOCK_TIME [AnyAnn] 
EMIT VarAnn FieldAnn (Maybe Ty) 

Instances

Instances details
Functor InstrAbstract Source # 
Instance details

Defined in Morley.Michelson.Untyped.Instr

Methods

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

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

ToExpression ExpandedInstr Source # 
Instance details

Defined in Morley.Micheline.Class

FromExp x op => FromExp x (InstrAbstract op) Source # 
Instance details

Defined in Morley.Micheline.Class

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

Defined in Morley.Michelson.Untyped.Instr

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

Defined in Morley.Michelson.Untyped.Instr

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

Defined in Morley.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 :: forall r r'. (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) #

Generic (InstrAbstract op) Source # 
Instance details

Defined in Morley.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 #

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

Defined in Morley.Michelson.Untyped.Instr

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

Defined in Morley.Michelson.Untyped.Instr

Methods

rnf :: InstrAbstract op -> () #

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

Defined in Morley.Michelson.Untyped.Instr

Methods

build :: InstrAbstract op -> Builder #

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

Defined in Morley.Michelson.Untyped.Instr

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

Defined in Morley.Michelson.Untyped.Instr

type Rep (InstrAbstract op) Source # 
Instance details

Defined in Morley.Michelson.Untyped.Instr

type Rep (InstrAbstract op) = D1 ('MetaData "InstrAbstract" "Morley.Michelson.Untyped.Instr" "morley-1.18.0-inplace" '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 "DUPN" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 VarAnn) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Word)) :+: 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 Ty) :*: 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 Ty)))) :+: (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 "UNPAIR" '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 FieldAnn) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 FieldAnn))) :+: C1 ('MetaCons "PAIRN" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 VarAnn) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Word)))) :+: ((C1 ('MetaCons "UNPAIRN" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Word)) :+: 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 Ty))))))) :+: ((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 Ty)))) :+: (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 Ty))))) :+: ((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 Ty)))))))) :+: ((((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 Ty) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Ty))) :+: (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 Ty) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Ty))) :+: 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 "GETN" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 VarAnn) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Word))))) :+: ((C1 ('MetaCons "UPDATE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 VarAnn)) :+: (C1 ('MetaCons "UPDATEN" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 VarAnn) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Word)) :+: C1 ('MetaCons "GET_AND_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 Ty)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Ty) :*: 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 Ty)) :+: 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 Ty))) :+: 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 "SUB_MUTEZ" '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 "VIEW" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 VarAnn) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ViewName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Ty)))))) :+: ((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 Ty))) :+: 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 "VOTING_POWER" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 VarAnn)))) :+: ((C1 ('MetaCons "TOTAL_VOTING_POWER" '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 "SHA3" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 VarAnn)) :+: C1 ('MetaCons "KECCAK" '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 "PAIRING_CHECK" '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)) :+: C1 ('MetaCons "LEVEL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 VarAnn)))) :+: ((C1 ('MetaCons "SELF_ADDRESS" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 VarAnn)) :+: C1 ('MetaCons "NEVER" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TICKET" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 VarAnn)) :+: C1 ('MetaCons "READ_TICKET" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 VarAnn))))) :+: ((C1 ('MetaCons "SPLIT_TICKET" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 VarAnn)) :+: (C1 ('MetaCons "JOIN_TICKETS" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 VarAnn)) :+: C1 ('MetaCons "OPEN_CHEST" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 VarAnn)))) :+: ((C1 ('MetaCons "SAPLING_EMPTY_STATE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 VarAnn) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Natural)) :+: C1 ('MetaCons "SAPLING_VERIFY_UPDATE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 VarAnn))) :+: (C1 ('MetaCons "MIN_BLOCK_TIME" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [AnyAnn])) :+: C1 ('MetaCons "EMIT" '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 (Maybe Ty)))))))))))

data ExpandedOp Source #

Instances

Instances details
FromJSON ExpandedOp Source # 
Instance details

Defined in Morley.Michelson.Untyped.Instr

ToJSON ExpandedOp Source # 
Instance details

Defined in Morley.Michelson.Untyped.Instr

Data ExpandedOp Source # 
Instance details

Defined in Morley.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 :: forall r r'. (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 #

Generic ExpandedOp Source # 
Instance details

Defined in Morley.Michelson.Untyped.Instr

Associated Types

type Rep ExpandedOp :: Type -> Type #

Show ExpandedOp Source # 
Instance details

Defined in Morley.Michelson.Untyped.Instr

NFData ExpandedOp Source # 
Instance details

Defined in Morley.Michelson.Untyped.Instr

Methods

rnf :: ExpandedOp -> () #

Buildable ExpandedOp Source # 
Instance details

Defined in Morley.Michelson.Untyped.Instr

Methods

build :: ExpandedOp -> Builder #

Eq ExpandedOp Source # 
Instance details

Defined in Morley.Michelson.Untyped.Instr

ToExpression Contract Source # 
Instance details

Defined in Morley.Micheline.Class

ToExpression Value Source # 
Instance details

Defined in Morley.Micheline.Class

ToExpression ExpandedInstr Source # 
Instance details

Defined in Morley.Micheline.Class

ToExpression ExpandedOp Source # 
Instance details

Defined in Morley.Micheline.Class

RenderDoc ExpandedOp Source # 
Instance details

Defined in Morley.Michelson.Untyped.Instr

HasCLReader Value Source # 
Instance details

Defined in Morley.CLI

FromExp RegularExp ExpandedOp Source # 
Instance details

Defined in Morley.Micheline.Class

type Rep ExpandedOp Source # 
Instance details

Defined in Morley.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).