morley-1.12.0: Developer tools for the Michelson Language
Safe HaskellNone
LanguageHaskell2010

Michelson.Macro

Synopsis

Macros types

data CadrStruct Source #

Constructors

A 
D 

Instances

Instances details
Eq CadrStruct Source # 
Instance details

Defined in Michelson.Macro

Data CadrStruct Source # 
Instance details

Defined in Michelson.Macro

Methods

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

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

toConstr :: CadrStruct -> Constr #

dataTypeOf :: CadrStruct -> DataType #

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

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

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

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

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

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

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

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

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

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

Show CadrStruct Source # 
Instance details

Defined in Michelson.Macro

Generic CadrStruct Source # 
Instance details

Defined in Michelson.Macro

Associated Types

type Rep CadrStruct :: Type -> Type #

ToJSON CadrStruct Source # 
Instance details

Defined in Michelson.Macro

FromJSON CadrStruct Source # 
Instance details

Defined in Michelson.Macro

NFData CadrStruct Source # 
Instance details

Defined in Michelson.Macro

Methods

rnf :: CadrStruct -> () #

Buildable CadrStruct Source # 
Instance details

Defined in Michelson.Macro

Methods

build :: CadrStruct -> Builder #

type Rep CadrStruct Source # 
Instance details

Defined in Michelson.Macro

type Rep CadrStruct = D1 ('MetaData "CadrStruct" "Michelson.Macro" "morley-1.12.0-inplace" 'False) (C1 ('MetaCons "A" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "D" 'PrefixI 'False) (U1 :: Type -> Type))

data PairStruct Source #

Instances

Instances details
Eq PairStruct Source # 
Instance details

Defined in Michelson.Macro

Data PairStruct Source # 
Instance details

Defined in Michelson.Macro

Methods

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

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

toConstr :: PairStruct -> Constr #

dataTypeOf :: PairStruct -> DataType #

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

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

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

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

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

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

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

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

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

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

Show PairStruct Source # 
Instance details

Defined in Michelson.Macro

Generic PairStruct Source # 
Instance details

Defined in Michelson.Macro

Associated Types

type Rep PairStruct :: Type -> Type #

ToJSON PairStruct Source # 
Instance details

Defined in Michelson.Macro

FromJSON PairStruct Source # 
Instance details

Defined in Michelson.Macro

NFData PairStruct Source # 
Instance details

Defined in Michelson.Macro

Methods

rnf :: PairStruct -> () #

Buildable PairStruct Source # 
Instance details

Defined in Michelson.Macro

Methods

build :: PairStruct -> Builder #

type Rep PairStruct Source # 
Instance details

Defined in Michelson.Macro

data UnpairStruct Source #

Instances

Instances details
Eq UnpairStruct Source # 
Instance details

Defined in Michelson.Macro

Data UnpairStruct Source # 
Instance details

Defined in Michelson.Macro

Methods

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

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

toConstr :: UnpairStruct -> Constr #

dataTypeOf :: UnpairStruct -> DataType #

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

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

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

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

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

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

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

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

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

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

Show UnpairStruct Source # 
Instance details

Defined in Michelson.Macro

Generic UnpairStruct Source # 
Instance details

Defined in Michelson.Macro

Associated Types

type Rep UnpairStruct :: Type -> Type #

ToJSON UnpairStruct Source # 
Instance details

Defined in Michelson.Macro

FromJSON UnpairStruct Source # 
Instance details

Defined in Michelson.Macro

NFData UnpairStruct Source # 
Instance details

Defined in Michelson.Macro

Methods

rnf :: UnpairStruct -> () #

Buildable UnpairStruct Source # 
Instance details

Defined in Michelson.Macro

type Rep UnpairStruct Source # 
Instance details

Defined in Michelson.Macro

data Macro Source #

Built-in Michelson Macros defined by the specification

Instances

Instances details
Eq Macro Source # 
Instance details

Defined in Michelson.Macro

Methods

(==) :: Macro -> Macro -> Bool #

(/=) :: Macro -> Macro -> Bool #

Data Macro Source # 
Instance details

Defined in Michelson.Macro

Methods

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

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

toConstr :: Macro -> Constr #

dataTypeOf :: Macro -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Macro Source # 
Instance details

Defined in Michelson.Macro

Methods

showsPrec :: Int -> Macro -> ShowS #

show :: Macro -> String #

showList :: [Macro] -> ShowS #

Generic Macro Source # 
Instance details

Defined in Michelson.Macro

Associated Types

type Rep Macro :: Type -> Type #

Methods

from :: Macro -> Rep Macro x #

to :: Rep Macro x -> Macro #

ToJSON Macro Source # 
Instance details

Defined in Michelson.Macro

FromJSON Macro Source # 
Instance details

Defined in Michelson.Macro

NFData Macro Source # 
Instance details

Defined in Michelson.Macro

Methods

rnf :: Macro -> () #

Buildable Macro Source # 
Instance details

Defined in Michelson.Macro

Methods

build :: Macro -> Builder #

type Rep Macro Source # 
Instance details

Defined in Michelson.Macro

type Rep Macro = D1 ('MetaData "Macro" "Michelson.Macro" "morley-1.12.0-inplace" 'False) ((((C1 ('MetaCons "CASE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (NonEmpty [ParsedOp]))) :+: (C1 ('MetaCons "TAG" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Natural) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (NonEmpty Type))) :+: C1 ('MetaCons "ACCESS" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Natural) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Positive)))) :+: (C1 ('MetaCons "SET" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Natural) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Positive)) :+: (C1 ('MetaCons "CONSTRUCT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (NonEmpty [ParsedOp]))) :+: C1 ('MetaCons "VIEW" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [ParsedOp]))))) :+: ((C1 ('MetaCons "VOID" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [ParsedOp])) :+: (C1 ('MetaCons "CMP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ParsedInstr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 VarAnn)) :+: C1 ('MetaCons "IFX" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ParsedInstr) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [ParsedOp]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [ParsedOp]))))) :+: ((C1 ('MetaCons "IFCMP" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ParsedInstr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 VarAnn)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [ParsedOp]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [ParsedOp]))) :+: C1 ('MetaCons "FAIL" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PAPAIR" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 PairStruct) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 TypeAnn) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 VarAnn))) :+: C1 ('MetaCons "UNPAIR" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 UnpairStruct)))))) :+: (((C1 ('MetaCons "CADR" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [CadrStruct]) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 VarAnn) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 FieldAnn))) :+: (C1 ('MetaCons "SET_CADR" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [CadrStruct]) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 VarAnn) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 FieldAnn))) :+: C1 ('MetaCons "MAP_CADR" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [CadrStruct]) :*: 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 [ParsedOp]))))) :+: ((C1 ('MetaCons "DIIP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Word) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [ParsedOp])) :+: C1 ('MetaCons "DUUP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Word) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 VarAnn))) :+: (C1 ('MetaCons "ASSERT" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ASSERTX" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ParsedInstr))))) :+: ((C1 ('MetaCons "ASSERT_CMP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ParsedInstr)) :+: (C1 ('MetaCons "ASSERT_NONE" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ASSERT_SOME" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "ASSERT_LEFT" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ASSERT_RIGHT" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "IF_SOME" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [ParsedOp]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [ParsedOp])) :+: C1 ('MetaCons "IF_RIGHT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [ParsedOp]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [ParsedOp])))))))

data LetMacro Source #

A programmer-defined macro

Constructors

LetMacro 

Fields

Instances

Instances details
Eq LetMacro Source # 
Instance details

Defined in Michelson.Macro

Data LetMacro Source # 
Instance details

Defined in Michelson.Macro

Methods

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

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

toConstr :: LetMacro -> Constr #

dataTypeOf :: LetMacro -> DataType #

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

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

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

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

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

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

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

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

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

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

Show LetMacro Source # 
Instance details

Defined in Michelson.Macro

Generic LetMacro Source # 
Instance details

Defined in Michelson.Macro

Associated Types

type Rep LetMacro :: Type -> Type #

Methods

from :: LetMacro -> Rep LetMacro x #

to :: Rep LetMacro x -> LetMacro #

ToJSON LetMacro Source # 
Instance details

Defined in Michelson.Macro

FromJSON LetMacro Source # 
Instance details

Defined in Michelson.Macro

NFData LetMacro Source # 
Instance details

Defined in Michelson.Macro

Methods

rnf :: LetMacro -> () #

Buildable LetMacro Source # 
Instance details

Defined in Michelson.Macro

Methods

build :: LetMacro -> Builder #

type Rep LetMacro Source # 
Instance details

Defined in Michelson.Macro

Morley Parsed value types

Morley Parsed instruction types

data ParsedOp Source #

Unexpanded instructions produced directly by the ops parser, which contains primitive Michelson Instructions, inline-able macros and sequences

Constructors

Prim ParsedInstr SrcPos

Primitive Michelson instruction

Mac Macro SrcPos

Built-in Michelson macro defined by the specification

LMac LetMacro SrcPos

User-defined macro with instructions to be inlined

Seq [ParsedOp] SrcPos

A sequence of instructions

Instances

Instances details
Eq ParsedOp Source # 
Instance details

Defined in Michelson.Macro

Data ParsedOp Source # 
Instance details

Defined in Michelson.Macro

Methods

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

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

toConstr :: ParsedOp -> Constr #

dataTypeOf :: ParsedOp -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ParsedOp Source # 
Instance details

Defined in Michelson.Macro

Generic ParsedOp Source # 
Instance details

Defined in Michelson.Macro

Associated Types

type Rep ParsedOp :: Type -> Type #

Methods

from :: ParsedOp -> Rep ParsedOp x #

to :: Rep ParsedOp x -> ParsedOp #

ToJSON ParsedOp Source # 
Instance details

Defined in Michelson.Macro

FromJSON ParsedOp Source # 
Instance details

Defined in Michelson.Macro

NFData ParsedOp Source # 
Instance details

Defined in Michelson.Macro

Methods

rnf :: ParsedOp -> () #

Buildable ParsedOp Source # 
Instance details

Defined in Michelson.Macro

Methods

build :: ParsedOp -> Builder #

RenderDoc ParsedOp Source # 
Instance details

Defined in Michelson.Macro

type Rep ParsedOp Source # 
Instance details

Defined in Michelson.Macro

For utilities

expandContract :: Contract' ParsedOp -> Contract Source #

Expand all macros in parsed contract.

For parsing

Internals exported for tests