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

Michelson.Untyped.Ext

Synopsis

Documentation

data ExtInstrAbstract op Source #

Implementation-specific instructions embedded in a NOP primitive, which mark a specific point during a contract's typechecking or execution.

These instructions are not allowed to modify the contract's stack, but may impose additional constraints that can cause a contract to report errors in type-checking or testing.

Additionaly, some implementation-specific language features such as type-checking of LetMacros are implemented using this mechanism (specifically FN and FN_END).

Constructors

STACKTYPE StackTypePattern

Matches current stack against a type-pattern

FN Text StackFn [op]

A typed stack function (push and pop a TcExtFrame)

UTEST_ASSERT (TestAssert op)

Copy the current stack and run an inline assertion on it

UPRINT PrintComment

Print a comment with optional embedded StackRefs

UCOMMENT Text

A comment in Michelson code

Instances

Instances details
Functor ExtInstrAbstract Source # 
Instance details

Defined in Michelson.Untyped.Ext

Methods

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

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

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

Defined in Michelson.Untyped.Ext

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

Defined in Michelson.Untyped.Ext

Methods

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

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

toConstr :: ExtInstrAbstract op -> Constr #

dataTypeOf :: ExtInstrAbstract op -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in Michelson.Untyped.Ext

Generic (ExtInstrAbstract op) Source # 
Instance details

Defined in Michelson.Untyped.Ext

Associated Types

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

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

Defined in Michelson.Untyped.Ext

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

Defined in Michelson.Untyped.Ext

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

Defined in Michelson.Untyped.Ext

Methods

rnf :: ExtInstrAbstract op -> () #

Buildable op => Buildable (ExtInstrAbstract op) Source # 
Instance details

Defined in Michelson.Untyped.Ext

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

Defined in Michelson.Untyped.Ext

type Rep (ExtInstrAbstract op) Source # 
Instance details

Defined in Michelson.Untyped.Ext

newtype StackRef Source #

A reference into the stack.

Constructors

StackRef Natural 

Instances

Instances details
Eq StackRef Source # 
Instance details

Defined in Michelson.Untyped.Ext

Data StackRef Source # 
Instance details

Defined in Michelson.Untyped.Ext

Methods

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

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

toConstr :: StackRef -> Constr #

dataTypeOf :: StackRef -> DataType #

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

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

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

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

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

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

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

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

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

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

Show StackRef Source # 
Instance details

Defined in Michelson.Untyped.Ext

Generic StackRef Source # 
Instance details

Defined in Michelson.Untyped.Ext

Associated Types

type Rep StackRef :: Type -> Type #

Methods

from :: StackRef -> Rep StackRef x #

to :: Rep StackRef x -> StackRef #

ToJSON StackRef Source # 
Instance details

Defined in Michelson.Untyped.Ext

FromJSON StackRef Source # 
Instance details

Defined in Michelson.Untyped.Ext

NFData StackRef Source # 
Instance details

Defined in Michelson.Untyped.Ext

Methods

rnf :: StackRef -> () #

Buildable StackRef Source # 
Instance details

Defined in Michelson.Untyped.Ext

Methods

build :: StackRef -> Builder #

type Rep StackRef Source # 
Instance details

Defined in Michelson.Untyped.Ext

type Rep StackRef = D1 ('MetaData "StackRef" "Michelson.Untyped.Ext" "morley-1.12.0-inplace" 'True) (C1 ('MetaCons "StackRef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Natural)))

newtype PrintComment Source #

Constructors

PrintComment 

Instances

Instances details
Eq PrintComment Source # 
Instance details

Defined in Michelson.Untyped.Ext

Data PrintComment Source # 
Instance details

Defined in Michelson.Untyped.Ext

Methods

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

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

toConstr :: PrintComment -> Constr #

dataTypeOf :: PrintComment -> DataType #

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

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

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

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

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

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

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

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

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

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

Show PrintComment Source # 
Instance details

Defined in Michelson.Untyped.Ext

Generic PrintComment Source # 
Instance details

Defined in Michelson.Untyped.Ext

Associated Types

type Rep PrintComment :: Type -> Type #

ToJSON PrintComment Source # 
Instance details

Defined in Michelson.Untyped.Ext

FromJSON PrintComment Source # 
Instance details

Defined in Michelson.Untyped.Ext

NFData PrintComment Source # 
Instance details

Defined in Michelson.Untyped.Ext

Methods

rnf :: PrintComment -> () #

Buildable PrintComment Source # 
Instance details

Defined in Michelson.Untyped.Ext

type Rep PrintComment Source # 
Instance details

Defined in Michelson.Untyped.Ext

type Rep PrintComment = D1 ('MetaData "PrintComment" "Michelson.Untyped.Ext" "morley-1.12.0-inplace" 'True) (C1 ('MetaCons "PrintComment" 'PrefixI 'True) (S1 ('MetaSel ('Just "unUPrintComment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Either Text StackRef])))

data TestAssert op Source #

Constructors

TestAssert 

Instances

Instances details
Functor TestAssert Source # 
Instance details

Defined in Michelson.Untyped.Ext

Methods

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

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

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

Defined in Michelson.Untyped.Ext

Methods

(==) :: TestAssert op -> TestAssert op -> Bool #

(/=) :: TestAssert op -> TestAssert op -> Bool #

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

Defined in Michelson.Untyped.Ext

Methods

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

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

toConstr :: TestAssert op -> Constr #

dataTypeOf :: TestAssert op -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in Michelson.Untyped.Ext

Methods

showsPrec :: Int -> TestAssert op -> ShowS #

show :: TestAssert op -> String #

showList :: [TestAssert op] -> ShowS #

Generic (TestAssert op) Source # 
Instance details

Defined in Michelson.Untyped.Ext

Associated Types

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

Methods

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

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

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

Defined in Michelson.Untyped.Ext

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

Defined in Michelson.Untyped.Ext

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

Defined in Michelson.Untyped.Ext

Methods

rnf :: TestAssert op -> () #

Buildable code => Buildable (TestAssert code) Source # 
Instance details

Defined in Michelson.Untyped.Ext

Methods

build :: TestAssert code -> Builder #

type Rep (TestAssert op) Source # 
Instance details

Defined in Michelson.Untyped.Ext

type Rep (TestAssert op) = D1 ('MetaData "TestAssert" "Michelson.Untyped.Ext" "morley-1.12.0-inplace" 'False) (C1 ('MetaCons "TestAssert" 'PrefixI 'True) (S1 ('MetaSel ('Just "tassName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Just "tassComment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 PrintComment) :*: S1 ('MetaSel ('Just "tassInstrs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [op]))))

newtype Var Source #

Constructors

Var Text 

Instances

Instances details
Eq Var Source # 
Instance details

Defined in Michelson.Untyped.Ext

Methods

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

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

Data Var Source # 
Instance details

Defined in Michelson.Untyped.Ext

Methods

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

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

toConstr :: Var -> Constr #

dataTypeOf :: Var -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Var Source # 
Instance details

Defined in Michelson.Untyped.Ext

Methods

compare :: Var -> Var -> Ordering #

(<) :: Var -> Var -> Bool #

(<=) :: Var -> Var -> Bool #

(>) :: Var -> Var -> Bool #

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

max :: Var -> Var -> Var #

min :: Var -> Var -> Var #

Show Var Source # 
Instance details

Defined in Michelson.Untyped.Ext

Methods

showsPrec :: Int -> Var -> ShowS #

show :: Var -> String #

showList :: [Var] -> ShowS #

Generic Var Source # 
Instance details

Defined in Michelson.Untyped.Ext

Associated Types

type Rep Var :: Type -> Type #

Methods

from :: Var -> Rep Var x #

to :: Rep Var x -> Var #

ToJSON Var Source # 
Instance details

Defined in Michelson.Untyped.Ext

FromJSON Var Source # 
Instance details

Defined in Michelson.Untyped.Ext

NFData Var Source # 
Instance details

Defined in Michelson.Untyped.Ext

Methods

rnf :: Var -> () #

Buildable Var Source # 
Instance details

Defined in Michelson.Untyped.Ext

Methods

build :: Var -> Builder #

type Rep Var Source # 
Instance details

Defined in Michelson.Untyped.Ext

type Rep Var = D1 ('MetaData "Var" "Michelson.Untyped.Ext" "morley-1.12.0-inplace" 'True) (C1 ('MetaCons "Var" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

data TyVar Source #

A type-variable or a type-constant

Constructors

VarID Var 
TyCon Type 

Instances

Instances details
Eq TyVar Source # 
Instance details

Defined in Michelson.Untyped.Ext

Methods

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

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

Data TyVar Source # 
Instance details

Defined in Michelson.Untyped.Ext

Methods

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

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

toConstr :: TyVar -> Constr #

dataTypeOf :: TyVar -> DataType #

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

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

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

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

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

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

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

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

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

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

Show TyVar Source # 
Instance details

Defined in Michelson.Untyped.Ext

Methods

showsPrec :: Int -> TyVar -> ShowS #

show :: TyVar -> String #

showList :: [TyVar] -> ShowS #

Generic TyVar Source # 
Instance details

Defined in Michelson.Untyped.Ext

Associated Types

type Rep TyVar :: Type -> Type #

Methods

from :: TyVar -> Rep TyVar x #

to :: Rep TyVar x -> TyVar #

ToJSON TyVar Source # 
Instance details

Defined in Michelson.Untyped.Ext

FromJSON TyVar Source # 
Instance details

Defined in Michelson.Untyped.Ext

NFData TyVar Source # 
Instance details

Defined in Michelson.Untyped.Ext

Methods

rnf :: TyVar -> () #

Buildable TyVar Source # 
Instance details

Defined in Michelson.Untyped.Ext

Methods

build :: TyVar -> Builder #

type Rep TyVar Source # 
Instance details

Defined in Michelson.Untyped.Ext

data StackTypePattern Source #

A stack pattern-match

Instances

Instances details
Eq StackTypePattern Source # 
Instance details

Defined in Michelson.Untyped.Ext

Data StackTypePattern Source # 
Instance details

Defined in Michelson.Untyped.Ext

Methods

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

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

toConstr :: StackTypePattern -> Constr #

dataTypeOf :: StackTypePattern -> DataType #

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

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

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

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

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

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

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

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

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

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

Show StackTypePattern Source # 
Instance details

Defined in Michelson.Untyped.Ext

Generic StackTypePattern Source # 
Instance details

Defined in Michelson.Untyped.Ext

Associated Types

type Rep StackTypePattern :: Type -> Type #

ToJSON StackTypePattern Source # 
Instance details

Defined in Michelson.Untyped.Ext

FromJSON StackTypePattern Source # 
Instance details

Defined in Michelson.Untyped.Ext

NFData StackTypePattern Source # 
Instance details

Defined in Michelson.Untyped.Ext

Methods

rnf :: StackTypePattern -> () #

Buildable StackTypePattern Source # 
Instance details

Defined in Michelson.Untyped.Ext

type Rep StackTypePattern Source # 
Instance details

Defined in Michelson.Untyped.Ext

type Rep StackTypePattern = D1 ('MetaData "StackTypePattern" "Michelson.Untyped.Ext" "morley-1.12.0-inplace" 'False) (C1 ('MetaCons "StkEmpty" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "StkRest" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StkCons" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 TyVar) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 StackTypePattern))))

data StackFn Source #

A stack function that expresses the type signature of a LetMacro

Instances

Instances details
Eq StackFn Source # 
Instance details

Defined in Michelson.Untyped.Ext

Methods

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

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

Data StackFn Source # 
Instance details

Defined in Michelson.Untyped.Ext

Methods

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

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

toConstr :: StackFn -> Constr #

dataTypeOf :: StackFn -> DataType #

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

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

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

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

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

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

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

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

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

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

Show StackFn Source # 
Instance details

Defined in Michelson.Untyped.Ext

Generic StackFn Source # 
Instance details

Defined in Michelson.Untyped.Ext

Associated Types

type Rep StackFn :: Type -> Type #

Methods

from :: StackFn -> Rep StackFn x #

to :: Rep StackFn x -> StackFn #

ToJSON StackFn Source # 
Instance details

Defined in Michelson.Untyped.Ext

FromJSON StackFn Source # 
Instance details

Defined in Michelson.Untyped.Ext

NFData StackFn Source # 
Instance details

Defined in Michelson.Untyped.Ext

Methods

rnf :: StackFn -> () #

Buildable StackFn Source # 
Instance details

Defined in Michelson.Untyped.Ext

Methods

build :: StackFn -> Builder #

type Rep StackFn Source # 
Instance details

Defined in Michelson.Untyped.Ext

type Rep StackFn = D1 ('MetaData "StackFn" "Michelson.Untyped.Ext" "morley-1.12.0-inplace" 'False) (C1 ('MetaCons "StackFn" 'PrefixI 'True) (S1 ('MetaSel ('Just "sfnQuantifiedVars") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe (Set Var))) :*: (S1 ('MetaSel ('Just "sfnInPattern") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 StackTypePattern) :*: S1 ('MetaSel ('Just "sfnOutPattern") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 StackTypePattern))))

varSet :: StackTypePattern -> Set Var Source #

Get the set of variables in a stack pattern

stackTypePatternToList :: StackTypePattern -> ([TyVar], Bool) Source #

Convert StackTypePattern to a list of types. Also returns Bool which is True if the pattern is a fixed list of types and False if it's a pattern match on the head of the stack.