morley-0.1.0.5: Developer tools for the Michelson Language

Safe HaskellNone
LanguageHaskell2010

Morley.Types

Contents

Synopsis

Rexported from Michelson.Types

data Contract op Source #

Constructors

Contract 

Fields

Instances
Functor Contract Source # 
Instance details

Defined in Michelson.Untyped.Contract

Methods

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

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

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

Defined in Michelson.Untyped.Contract

Methods

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

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

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

Defined in Michelson.Untyped.Contract

Methods

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

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

toConstr :: Contract op -> Constr #

dataTypeOf :: Contract op -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in Michelson.Untyped.Contract

Methods

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

show :: Contract op -> String #

showList :: [Contract op] -> ShowS #

Generic (Contract op) Source # 
Instance details

Defined in Michelson.Untyped.Contract

Associated Types

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

Methods

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

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

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

Defined in Michelson.Untyped.Contract

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

Defined in Michelson.Untyped.Contract

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

Defined in Michelson.Untyped.Contract

Methods

build :: Contract op -> Builder #

type Rep (Contract op) Source # 
Instance details

Defined in Michelson.Untyped.Contract

type Rep (Contract op) = D1 (MetaData "Contract" "Michelson.Untyped.Contract" "morley-0.1.0.5-JGwsFje78IP81WIHW6apex" False) (C1 (MetaCons "Contract" PrefixI True) (S1 (MetaSel (Just "para") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Parameter) :*: (S1 (MetaSel (Just "stor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Storage) :*: S1 (MetaSel (Just "code") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [op]))))

data Value op Source #

Constructors

ValueInt Integer 
ValueString Text 
ValueBytes InternalByteString 
ValueUnit 
ValueTrue 
ValueFalse 
ValuePair (Value op) (Value op) 
ValueLeft (Value op) 
ValueRight (Value op) 
ValueSome (Value op) 
ValueNone 
ValueNil 
ValueSeq (NonEmpty $ Value op)

A sequence of elements: can be a list or a set. We can't distinguish lists and sets during parsing.

ValueMap (NonEmpty $ Elt op) 
ValueLambda (NonEmpty op) 
Instances
Functor Value Source # 
Instance details

Defined in Michelson.Untyped.Value

Methods

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

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

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

Defined in Michelson.Untyped.Value

Methods

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

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

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

Defined in Michelson.Untyped.Value

Methods

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

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

toConstr :: Value op -> Constr #

dataTypeOf :: Value op -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in Michelson.Untyped.Value

Methods

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

show :: Value op -> String #

showList :: [Value op] -> ShowS #

Generic (Value op) Source # 
Instance details

Defined in Michelson.Untyped.Value

Associated Types

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

Methods

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

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

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

Defined in Michelson.Untyped.Value

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

Defined in Michelson.Untyped.Value

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

Defined in Michelson.Untyped.Value

Methods

build :: Value op -> Builder #

type Rep (Value op) Source # 
Instance details

Defined in Michelson.Untyped.Value

type Rep (Value op) = D1 (MetaData "Value" "Michelson.Untyped.Value" "morley-0.1.0.5-JGwsFje78IP81WIHW6apex" False) (((C1 (MetaCons "ValueInt" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Integer)) :+: (C1 (MetaCons "ValueString" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) :+: C1 (MetaCons "ValueBytes" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 InternalByteString)))) :+: ((C1 (MetaCons "ValueUnit" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ValueTrue" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "ValueFalse" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ValuePair" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Value op)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Value op)))))) :+: (((C1 (MetaCons "ValueLeft" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Value op))) :+: C1 (MetaCons "ValueRight" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Value op)))) :+: (C1 (MetaCons "ValueSome" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Value op))) :+: C1 (MetaCons "ValueNone" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "ValueNil" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ValueSeq" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NonEmpty $ Value op)))) :+: (C1 (MetaCons "ValueMap" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NonEmpty $ Elt op))) :+: C1 (MetaCons "ValueLambda" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NonEmpty op)))))))

data Elt op Source #

Constructors

Elt (Value op) (Value op) 
Instances
Functor Elt Source # 
Instance details

Defined in Michelson.Untyped.Value

Methods

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

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

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

Defined in Michelson.Untyped.Value

Methods

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

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

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

Defined in Michelson.Untyped.Value

Methods

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

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

toConstr :: Elt op -> Constr #

dataTypeOf :: Elt op -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in Michelson.Untyped.Value

Methods

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

show :: Elt op -> String #

showList :: [Elt op] -> ShowS #

Generic (Elt op) Source # 
Instance details

Defined in Michelson.Untyped.Value

Associated Types

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

Methods

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

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

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

Defined in Michelson.Untyped.Value

Methods

toJSON :: Elt op -> Value #

toEncoding :: Elt op -> Encoding #

toJSONList :: [Elt op] -> Value #

toEncodingList :: [Elt op] -> Encoding #

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

Defined in Michelson.Untyped.Value

Methods

parseJSON :: Value -> Parser (Elt op) #

parseJSONList :: Value -> Parser [Elt op] #

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

Defined in Michelson.Untyped.Value

Methods

build :: Elt op -> Builder #

type Rep (Elt op) Source # 
Instance details

Defined in Michelson.Untyped.Value

type Rep (Elt op) = D1 (MetaData "Elt" "Michelson.Untyped.Value" "morley-0.1.0.5-JGwsFje78IP81WIHW6apex" False) (C1 (MetaCons "Elt" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Value op)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Value op))))

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.

Instances
Functor (ExtU InstrAbstract) => Functor InstrAbstract Source # 
Instance details

Defined in Michelson.Untyped.Instr

Methods

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

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

Buildable ExpandedInstr Source # 
Instance details

Defined in Morley.Types

Buildable Instr Source # 
Instance details

Defined in Morley.Types

Methods

build :: Instr -> Builder #

Buildable ParsedInstr Source # 
Instance details

Defined in Morley.Types

Methods

build :: ParsedInstr -> Builder #

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

Defined in Michelson.Untyped.Instr

(Data op, Data (ExtU InstrAbstract 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 (ExtU InstrAbstract 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 #

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

Defined in Michelson.Untyped.Instr

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

Defined in Michelson.Untyped.Instr

type ExtU InstrAbstract Source # 
Instance details

Defined in Morley.Types

type Rep (InstrAbstract op) Source # 
Instance details

Defined in Michelson.Untyped.Instr

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

newtype Op Source #

Constructors

Op 

Fields

Instances
Eq (ExtU InstrAbstract Op) => Eq Op Source # 
Instance details

Defined in Michelson.Untyped.Instr

Methods

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

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

Show (ExtU InstrAbstract Op) => Show Op Source # 
Instance details

Defined in Michelson.Untyped.Instr

Methods

showsPrec :: Int -> Op -> ShowS #

show :: Op -> String #

showList :: [Op] -> ShowS #

Generic Op Source # 
Instance details

Defined in Michelson.Untyped.Instr

Associated Types

type Rep Op :: Type -> Type #

Methods

from :: Op -> Rep Op x #

to :: Rep Op x -> Op #

ToJSON Instr => ToJSON Op Source # 
Instance details

Defined in Michelson.Untyped.Instr

FromJSON Instr => FromJSON Op Source # 
Instance details

Defined in Michelson.Untyped.Instr

Buildable Instr => Buildable Op Source # 
Instance details

Defined in Michelson.Untyped.Instr

Methods

build :: Op -> Builder #

Buildable Instr Source # 
Instance details

Defined in Morley.Types

Methods

build :: Instr -> Builder #

type Rep Op Source # 
Instance details

Defined in Michelson.Untyped.Instr

type Rep Op = D1 (MetaData "Op" "Michelson.Untyped.Instr" "morley-0.1.0.5-JGwsFje78IP81WIHW6apex" True) (C1 (MetaCons "Op" PrefixI True) (S1 (MetaSel (Just "unOp") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Instr)))

type TypeAnn = Annotation TypeTag Source #

type FieldAnn = Annotation FieldTag Source #

type VarAnn = Annotation VarTag Source #

data Type Source #

Constructors

Type T TypeAnn 
Instances
Eq Type Source # 
Instance details

Defined in Michelson.Untyped.Type

Methods

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

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

Data Type Source # 
Instance details

Defined in Michelson.Untyped.Type

Methods

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

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

toConstr :: Type -> Constr #

dataTypeOf :: Type -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Type Source # 
Instance details

Defined in Michelson.Untyped.Type

Methods

showsPrec :: Int -> Type -> ShowS #

show :: Type -> String #

showList :: [Type] -> ShowS #

Generic Type Source # 
Instance details

Defined in Michelson.Untyped.Type

Associated Types

type Rep Type :: Type -> Type #

Methods

from :: Type -> Rep Type x #

to :: Rep Type x -> Type #

ToJSON Type Source # 
Instance details

Defined in Michelson.Untyped.Type

FromJSON Type Source # 
Instance details

Defined in Michelson.Untyped.Type

Buildable Type Source # 
Instance details

Defined in Michelson.Untyped.Type

Methods

build :: Type -> Builder #

type Rep Type Source # 
Instance details

Defined in Michelson.Untyped.Type

data Comparable Source #

Constructors

Comparable CT TypeAnn 
Instances
Eq Comparable Source # 
Instance details

Defined in Michelson.Untyped.Type

Data Comparable Source # 
Instance details

Defined in Michelson.Untyped.Type

Methods

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

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

toConstr :: Comparable -> Constr #

dataTypeOf :: Comparable -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Comparable Source # 
Instance details

Defined in Michelson.Untyped.Type

Generic Comparable Source # 
Instance details

Defined in Michelson.Untyped.Type

Associated Types

type Rep Comparable :: Type -> Type #

ToJSON Comparable Source # 
Instance details

Defined in Michelson.Untyped.Type

FromJSON Comparable Source # 
Instance details

Defined in Michelson.Untyped.Type

Buildable Comparable Source # 
Instance details

Defined in Michelson.Untyped.Type

Methods

build :: Comparable -> Builder #

type Rep Comparable Source # 
Instance details

Defined in Michelson.Untyped.Type

type Rep Comparable = D1 (MetaData "Comparable" "Michelson.Untyped.Type" "morley-0.1.0.5-JGwsFje78IP81WIHW6apex" False) (C1 (MetaCons "Comparable" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CT) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TypeAnn)))

data T Source #

Instances
Eq T Source # 
Instance details

Defined in Michelson.Untyped.Type

Methods

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

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

Data T Source # 
Instance details

Defined in Michelson.Untyped.Type

Methods

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

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

toConstr :: T -> Constr #

dataTypeOf :: T -> DataType #

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

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

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

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

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

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

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

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

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

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

Show T Source # 
Instance details

Defined in Michelson.Untyped.Type

Methods

showsPrec :: Int -> T -> ShowS #

show :: T -> String #

showList :: [T] -> ShowS #

Generic T Source # 
Instance details

Defined in Michelson.Untyped.Type

Associated Types

type Rep T :: Type -> Type #

Methods

from :: T -> Rep T x #

to :: Rep T x -> T #

ToJSON T Source # 
Instance details

Defined in Michelson.Untyped.Type

FromJSON T Source # 
Instance details

Defined in Michelson.Untyped.Type

Buildable T Source # 
Instance details

Defined in Michelson.Untyped.Type

Methods

build :: T -> Builder #

type Rep T Source # 
Instance details

Defined in Michelson.Untyped.Type

type Rep T = D1 (MetaData "T" "Michelson.Untyped.Type" "morley-0.1.0.5-JGwsFje78IP81WIHW6apex" False) (((C1 (MetaCons "Tc" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CT)) :+: (C1 (MetaCons "TKey" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TUnit" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "TSignature" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TOption" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FieldAnn) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type))) :+: (C1 (MetaCons "TList" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type)) :+: C1 (MetaCons "TSet" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Comparable))))) :+: ((C1 (MetaCons "TOperation" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "TContract" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type)) :+: C1 (MetaCons "TPair" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FieldAnn) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FieldAnn)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type))))) :+: ((C1 (MetaCons "TOr" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FieldAnn) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FieldAnn)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type))) :+: C1 (MetaCons "TLambda" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type))) :+: (C1 (MetaCons "TMap" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Comparable) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type)) :+: C1 (MetaCons "TBigMap" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Comparable) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Type))))))

data CT Source #

Instances
Bounded CT Source # 
Instance details

Defined in Michelson.Untyped.Type

Methods

minBound :: CT #

maxBound :: CT #

Enum CT Source # 
Instance details

Defined in Michelson.Untyped.Type

Methods

succ :: CT -> CT #

pred :: CT -> CT #

toEnum :: Int -> CT #

fromEnum :: CT -> Int #

enumFrom :: CT -> [CT] #

enumFromThen :: CT -> CT -> [CT] #

enumFromTo :: CT -> CT -> [CT] #

enumFromThenTo :: CT -> CT -> CT -> [CT] #

Eq CT Source # 
Instance details

Defined in Michelson.Untyped.Type

Methods

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

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

Data CT Source # 
Instance details

Defined in Michelson.Untyped.Type

Methods

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

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

toConstr :: CT -> Constr #

dataTypeOf :: CT -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CT Source # 
Instance details

Defined in Michelson.Untyped.Type

Methods

compare :: CT -> CT -> Ordering #

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

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

(>) :: CT -> CT -> Bool #

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

max :: CT -> CT -> CT #

min :: CT -> CT -> CT #

Show CT Source # 
Instance details

Defined in Michelson.Untyped.Type

Methods

showsPrec :: Int -> CT -> ShowS #

show :: CT -> String #

showList :: [CT] -> ShowS #

Generic CT Source # 
Instance details

Defined in Michelson.Untyped.Type

Associated Types

type Rep CT :: Type -> Type #

Methods

from :: CT -> Rep CT x #

to :: Rep CT x -> CT #

ToJSON CT Source # 
Instance details

Defined in Michelson.Untyped.Type

FromJSON CT Source # 
Instance details

Defined in Michelson.Untyped.Type

Buildable CT Source # 
Instance details

Defined in Michelson.Untyped.Type

Methods

build :: CT -> Builder #

SingI CInt Source # 
Instance details

Defined in Michelson.Typed.Sing

Methods

sing :: Sing CInt #

SingI CNat Source # 
Instance details

Defined in Michelson.Typed.Sing

Methods

sing :: Sing CNat #

SingI CString Source # 
Instance details

Defined in Michelson.Typed.Sing

Methods

sing :: Sing CString #

SingI CBytes Source # 
Instance details

Defined in Michelson.Typed.Sing

Methods

sing :: Sing CBytes #

SingI CMutez Source # 
Instance details

Defined in Michelson.Typed.Sing

Methods

sing :: Sing CMutez #

SingI CBool Source # 
Instance details

Defined in Michelson.Typed.Sing

Methods

sing :: Sing CBool #

SingI CKeyHash Source # 
Instance details

Defined in Michelson.Typed.Sing

Methods

sing :: Sing CKeyHash #

SingI CTimestamp Source # 
Instance details

Defined in Michelson.Typed.Sing

Methods

sing :: Sing CTimestamp #

SingI CAddress Source # 
Instance details

Defined in Michelson.Typed.Sing

Methods

sing :: Sing CAddress #

type Rep CT Source # 
Instance details

Defined in Michelson.Untyped.Type

type Rep CT = D1 (MetaData "CT" "Michelson.Untyped.Type" "morley-0.1.0.5-JGwsFje78IP81WIHW6apex" False) (((C1 (MetaCons "CInt" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CNat" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "CString" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CBytes" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "CMutez" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CBool" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "CKeyHash" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "CTimestamp" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CAddress" PrefixI False) (U1 :: Type -> Type)))))
data Sing (a :: CT) Source #

Instance of data family Sing for CT.

Instance details

Defined in Michelson.Typed.Sing

data Sing (a :: CT) where

newtype Annotation tag Source #

Constructors

Annotation Text 
Instances
Semigroup VarAnn Source # 
Instance details

Defined in Michelson.Untyped.Annotation

Monoid VarAnn Source # 
Instance details

Defined in Michelson.Untyped.Annotation

Buildable VarAnn Source # 
Instance details

Defined in Michelson.Untyped.Annotation

Methods

build :: VarAnn -> Builder #

Buildable FieldAnn Source # 
Instance details

Defined in Michelson.Untyped.Annotation

Methods

build :: FieldAnn -> Builder #

Buildable TypeAnn Source # 
Instance details

Defined in Michelson.Untyped.Annotation

Methods

build :: TypeAnn -> Builder #

Functor (Annotation :: Type -> Type) Source # 
Instance details

Defined in Michelson.Untyped.Annotation

Methods

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

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

Eq (Annotation tag) Source # 
Instance details

Defined in Michelson.Untyped.Annotation

Methods

(==) :: Annotation tag -> Annotation tag -> Bool #

(/=) :: Annotation tag -> Annotation tag -> Bool #

(Typeable tag, Typeable k) => Data (Annotation tag) Source # 
Instance details

Defined in Michelson.Untyped.Annotation

Methods

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

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

toConstr :: Annotation tag -> Constr #

dataTypeOf :: Annotation tag -> DataType #

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

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

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

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

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

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

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

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

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

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

IsString (Annotation tag) Source # 
Instance details

Defined in Michelson.Untyped.Annotation

Methods

fromString :: String -> Annotation tag #

Generic (Annotation tag) Source # 
Instance details

Defined in Michelson.Untyped.Annotation

Associated Types

type Rep (Annotation tag) :: Type -> Type #

Methods

from :: Annotation tag -> Rep (Annotation tag) x #

to :: Rep (Annotation tag) x -> Annotation tag #

ToJSON (Annotation tag) Source # 
Instance details

Defined in Michelson.Untyped.Annotation

FromJSON (Annotation tag) Source # 
Instance details

Defined in Michelson.Untyped.Annotation

Default (Annotation tag) Source # 
Instance details

Defined in Michelson.Untyped.Annotation

Methods

def :: Annotation tag #

type Rep (Annotation tag) Source # 
Instance details

Defined in Michelson.Untyped.Annotation

type Rep (Annotation tag) = D1 (MetaData "Annotation" "Michelson.Untyped.Annotation" "morley-0.1.0.5-JGwsFje78IP81WIHW6apex" True) (C1 (MetaCons "Annotation" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

newtype InternalByteString Source #

ByteString does not have an instance for ToJSON and FromJSON, to avoid orphan type class instances, make a new type wrapper around it.

Instances
Eq InternalByteString Source # 
Instance details

Defined in Michelson.Untyped.Value

Data InternalByteString Source # 
Instance details

Defined in Michelson.Untyped.Value

Methods

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

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

toConstr :: InternalByteString -> Constr #

dataTypeOf :: InternalByteString -> DataType #

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

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

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

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

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

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

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

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

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

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

Show InternalByteString Source # 
Instance details

Defined in Michelson.Untyped.Value

ToJSON InternalByteString Source # 
Instance details

Defined in Michelson.Untyped.Value

FromJSON InternalByteString Source # 
Instance details

Defined in Michelson.Untyped.Value

data CustomParserException Source #

Instances
Eq CustomParserException Source # 
Instance details

Defined in Morley.Types

Data CustomParserException Source # 
Instance details

Defined in Morley.Types

Methods

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

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

toConstr :: CustomParserException -> Constr #

dataTypeOf :: CustomParserException -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CustomParserException Source # 
Instance details

Defined in Morley.Types

Show CustomParserException Source # 
Instance details

Defined in Morley.Types

ShowErrorComponent CustomParserException Source # 
Instance details

Defined in Morley.Types

Default a => Default (Parser a) Source # 
Instance details

Defined in Morley.Types

Methods

def :: Parser a #

type Parsec e s = ParsecT e s Identity #

Parsec is a non-transformer variant of the more general ParsecT monad transformer.

data ParseErrorBundle s e #

A non-empty collection of ParseErrors equipped with PosState that allows to pretty-print the errors efficiently and correctly.

Since: megaparsec-7.0.0

Instances
(Eq s, Eq (Token s), Eq e) => Eq (ParseErrorBundle s e) 
Instance details

Defined in Text.Megaparsec.Error

(Data s, Data (Token s), Ord (Token s), Data e, Ord e) => Data (ParseErrorBundle s e) 
Instance details

Defined in Text.Megaparsec.Error

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ParseErrorBundle s e -> c (ParseErrorBundle s e) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ParseErrorBundle s e) #

toConstr :: ParseErrorBundle s e -> Constr #

dataTypeOf :: ParseErrorBundle s e -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> ParseErrorBundle s e -> ParseErrorBundle s e #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ParseErrorBundle s e -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ParseErrorBundle s e -> r #

gmapQ :: (forall d. Data d => d -> u) -> ParseErrorBundle s e -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ParseErrorBundle s e -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ParseErrorBundle s e -> m (ParseErrorBundle s e) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ParseErrorBundle s e -> m (ParseErrorBundle s e) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ParseErrorBundle s e -> m (ParseErrorBundle s e) #

(Show s, Show (Token s), Show e) => Show (ParseErrorBundle s e) 
Instance details

Defined in Text.Megaparsec.Error

Generic (ParseErrorBundle s e) 
Instance details

Defined in Text.Megaparsec.Error

Associated Types

type Rep (ParseErrorBundle s e) :: Type -> Type #

(Show s, Show (Token s), Show e, ShowErrorComponent e, Stream s, Typeable s, Typeable e) => Exception (ParseErrorBundle s e) 
Instance details

Defined in Text.Megaparsec.Error

(NFData s, NFData (Token s), NFData e) => NFData (ParseErrorBundle s e) 
Instance details

Defined in Text.Megaparsec.Error

Methods

rnf :: ParseErrorBundle s e -> () #

type Rep (ParseErrorBundle s e) 
Instance details

Defined in Text.Megaparsec.Error

type Rep (ParseErrorBundle s e) = D1 (MetaData "ParseErrorBundle" "Text.Megaparsec.Error" "megaparsec-7.0.4-9ALYGrjYOOC9k3jnVKNZ4m" False) (C1 (MetaCons "ParseErrorBundle" PrefixI True) (S1 (MetaSel (Just "bundleErrors") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NonEmpty (ParseError s e))) :*: S1 (MetaSel (Just "bundlePosState") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (PosState s))))

data LetEnv Source #

The environment containing lets from the let-block

Instances
Eq LetEnv Source # 
Instance details

Defined in Morley.Types

Methods

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

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

Show LetEnv Source # 
Instance details

Defined in Morley.Types

Default a => Default (Parser a) Source # 
Instance details

Defined in Morley.Types

Methods

def :: Parser a #

data UExtInstrAbstract 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

Begin a typed stack function (push a TcExtFrame)

FN_END

End a stack function (pop a TcExtFrame)

UTEST_ASSERT (UTestAssert op)

Copy the current stack and run an inline assertion on it

UPRINT PrintComment

Print a comment with optional embedded StackRefs

Instances
Functor UExtInstrAbstract Source # 
Instance details

Defined in Morley.Types

Conversible ExtInstr (UExtInstrAbstract ExpandedOp) Source # 
Instance details

Defined in Morley.Types

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

Defined in Morley.Types

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

Defined in Morley.Types

Methods

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

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

toConstr :: UExtInstrAbstract op -> Constr #

dataTypeOf :: UExtInstrAbstract op -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in Morley.Types

Generic (UExtInstrAbstract op) Source # 
Instance details

Defined in Morley.Types

Associated Types

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

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

Defined in Morley.Types

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

Defined in Morley.Types

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

Defined in Morley.Types

type Rep (UExtInstrAbstract op) Source # 
Instance details

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

Primitive Michelson instruction

Mac Macro

Built-in Michelson macro defined by the specification

LMac LetMacro

User-defined macro with instructions to be inlined

Seq [ParsedOp]

A sequence of instructions

Instances
Eq ParsedOp Source # 
Instance details

Defined in Morley.Types

Data ParsedOp Source # 
Instance details

Defined in Morley.Types

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 :: (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 Morley.Types

Generic ParsedOp Source # 
Instance details

Defined in Morley.Types

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 Morley.Types

FromJSON ParsedOp Source # 
Instance details

Defined in Morley.Types

Buildable ParsedOp Source # 
Instance details

Defined in Morley.Types

Methods

build :: ParsedOp -> Builder #

Buildable ParsedInstr Source # 
Instance details

Defined in Morley.Types

Methods

build :: ParsedInstr -> Builder #

type Rep ParsedOp Source # 
Instance details

Defined in Morley.Types

Morley Expanded instruction types

data ExpandedOp Source #

Instances
Eq ExpandedInstr => Eq ExpandedOp Source # 
Instance details

Defined in Michelson.Untyped.Instr

Data ExpandedInstr => 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 ExpandedInstr => 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 #

ToJSON ExpandedInstr => ToJSON ExpandedOp Source # 
Instance details

Defined in Michelson.Untyped.Instr

FromJSON ExpandedInstr => FromJSON ExpandedOp Source # 
Instance details

Defined in Michelson.Untyped.Instr

Buildable ExpandedInstr => Buildable ExpandedOp Source # 
Instance details

Defined in Michelson.Untyped.Instr

Methods

build :: ExpandedOp -> Builder #

Buildable ExpandedInstr Source # 
Instance details

Defined in Morley.Types

Conversible ExtInstr (UExtInstrAbstract ExpandedOp) Source # 
Instance details

Defined in Morley.Types

type Rep ExpandedOp Source # 
Instance details

Defined in Michelson.Untyped.Instr

Michelson Instructions and Instruction Macros

data PairStruct Source #

Instances
Eq PairStruct Source # 
Instance details

Defined in Morley.Types

Data PairStruct Source # 
Instance details

Defined in Morley.Types

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 :: (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 Morley.Types

Generic PairStruct Source # 
Instance details

Defined in Morley.Types

Associated Types

type Rep PairStruct :: Type -> Type #

ToJSON PairStruct Source # 
Instance details

Defined in Morley.Types

FromJSON PairStruct Source # 
Instance details

Defined in Morley.Types

Buildable PairStruct Source # 
Instance details

Defined in Morley.Types

Methods

build :: PairStruct -> Builder #

type Rep PairStruct Source # 
Instance details

Defined in Morley.Types

data CadrStruct Source #

Constructors

A 
D 
Instances
Eq CadrStruct Source # 
Instance details

Defined in Morley.Types

Data CadrStruct Source # 
Instance details

Defined in Morley.Types

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 :: (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 Morley.Types

Generic CadrStruct Source # 
Instance details

Defined in Morley.Types

Associated Types

type Rep CadrStruct :: Type -> Type #

ToJSON CadrStruct Source # 
Instance details

Defined in Morley.Types

FromJSON CadrStruct Source # 
Instance details

Defined in Morley.Types

Buildable CadrStruct Source # 
Instance details

Defined in Morley.Types

Methods

build :: CadrStruct -> Builder #

type Rep CadrStruct Source # 
Instance details

Defined in Morley.Types

type Rep CadrStruct = D1 (MetaData "CadrStruct" "Morley.Types" "morley-0.1.0.5-JGwsFje78IP81WIHW6apex" False) (C1 (MetaCons "A" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "D" PrefixI False) (U1 :: Type -> Type))

data Macro Source #

Built-in Michelson Macros defined by the specification

Instances
Eq Macro Source # 
Instance details

Defined in Morley.Types

Methods

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

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

Data Macro Source # 
Instance details

Defined in Morley.Types

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 :: (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 Morley.Types

Methods

showsPrec :: Int -> Macro -> ShowS #

show :: Macro -> String #

showList :: [Macro] -> ShowS #

Generic Macro Source # 
Instance details

Defined in Morley.Types

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 Morley.Types

FromJSON Macro Source # 
Instance details

Defined in Morley.Types

Buildable Macro Source # 
Instance details

Defined in Morley.Types

Methods

build :: Macro -> Builder #

type Rep Macro Source # 
Instance details

Defined in Morley.Types

type Rep Macro = D1 (MetaData "Macro" "Morley.Types" "morley-0.1.0.5-JGwsFje78IP81WIHW6apex" False) ((((C1 (MetaCons "CMP" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ParsedInstr) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VarAnn)) :+: C1 (MetaCons "IFX" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ParsedInstr) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ParsedOp]) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ParsedOp])))) :+: (C1 (MetaCons "IFCMP" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ParsedInstr) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VarAnn)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ParsedOp]) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ParsedOp]))) :+: C1 (MetaCons "FAIL" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "PAPAIR" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PairStruct) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TypeAnn) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VarAnn))) :+: C1 (MetaCons "UNPAIR" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PairStruct))) :+: (C1 (MetaCons "CADR" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [CadrStruct]) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VarAnn) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FieldAnn))) :+: (C1 (MetaCons "SET_CADR" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [CadrStruct]) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VarAnn) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FieldAnn))) :+: C1 (MetaCons "MAP_CADR" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [CadrStruct]) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VarAnn)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FieldAnn) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ParsedOp]))))))) :+: (((C1 (MetaCons "DIIP" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Integer) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ParsedOp])) :+: C1 (MetaCons "DUUP" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Integer) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VarAnn))) :+: (C1 (MetaCons "ASSERT" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "ASSERTX" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ParsedInstr)) :+: C1 (MetaCons "ASSERT_CMP" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (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 DecidedLazy) (Rec0 [ParsedOp]) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ParsedOp])))))))

Morley Instructions

data ExtInstr Source #

Instances
Eq ExtInstr Source # 
Instance details

Defined in Morley.Types

Show ExtInstr Source # 
Instance details

Defined in Morley.Types

Conversible ExtInstr (UExtInstrAbstract ExpandedOp) Source # 
Instance details

Defined in Morley.Types

data TestAssert where Source #

Constructors

TestAssert :: (Typeable inp, Typeable out) => Text -> PrintComment -> Instr inp (Tc CBool ': out) -> TestAssert 
Instances
Eq TestAssert Source # 
Instance details

Defined in Morley.Types

Show TestAssert Source # 
Instance details

Defined in Morley.Types

data UTestAssert op Source #

Constructors

UTestAssert 
Instances
Functor UTestAssert Source # 
Instance details

Defined in Morley.Types

Methods

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

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

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

Defined in Morley.Types

Methods

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

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

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

Defined in Morley.Types

Methods

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

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

toConstr :: UTestAssert op -> Constr #

dataTypeOf :: UTestAssert op -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in Morley.Types

Generic (UTestAssert op) Source # 
Instance details

Defined in Morley.Types

Associated Types

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

Methods

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

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

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

Defined in Morley.Types

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

Defined in Morley.Types

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

Defined in Morley.Types

Methods

build :: UTestAssert code -> Builder #

type Rep (UTestAssert op) Source # 
Instance details

Defined in Morley.Types

type Rep (UTestAssert op) = D1 (MetaData "UTestAssert" "Morley.Types" "morley-0.1.0.5-JGwsFje78IP81WIHW6apex" False) (C1 (MetaCons "UTestAssert" PrefixI True) (S1 (MetaSel (Just "tassName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: (S1 (MetaSel (Just "tassComment") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PrintComment) :*: S1 (MetaSel (Just "tassInstrs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [op]))))

newtype PrintComment Source #

Constructors

PrintComment 
Instances
Eq PrintComment Source # 
Instance details

Defined in Morley.Types

Data PrintComment Source # 
Instance details

Defined in Morley.Types

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 :: (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 Morley.Types

Generic PrintComment Source # 
Instance details

Defined in Morley.Types

Associated Types

type Rep PrintComment :: Type -> Type #

ToJSON PrintComment Source # 
Instance details

Defined in Morley.Types

FromJSON PrintComment Source # 
Instance details

Defined in Morley.Types

Buildable PrintComment Source # 
Instance details

Defined in Morley.Types

type Rep PrintComment Source # 
Instance details

Defined in Morley.Types

type Rep PrintComment = D1 (MetaData "PrintComment" "Morley.Types" "morley-0.1.0.5-JGwsFje78IP81WIHW6apex" True) (C1 (MetaCons "PrintComment" PrefixI True) (S1 (MetaSel (Just "unPrintComment") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Either Text StackRef])))

data StackTypePattern Source #

A stack pattern-match

Instances
Eq StackTypePattern Source # 
Instance details

Defined in Morley.Types

Data StackTypePattern Source # 
Instance details

Defined in Morley.Types

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 :: (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 Morley.Types

Generic StackTypePattern Source # 
Instance details

Defined in Morley.Types

Associated Types

type Rep StackTypePattern :: Type -> Type #

ToJSON StackTypePattern Source # 
Instance details

Defined in Morley.Types

FromJSON StackTypePattern Source # 
Instance details

Defined in Morley.Types

Buildable StackTypePattern Source # 
Instance details

Defined in Morley.Types

type Rep StackTypePattern Source # 
Instance details

Defined in Morley.Types

newtype StackRef Source #

A reference into the stack

Constructors

StackRef Integer 
Instances
Eq StackRef Source # 
Instance details

Defined in Morley.Types

Data StackRef Source # 
Instance details

Defined in Morley.Types

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 :: (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 Morley.Types

Generic StackRef Source # 
Instance details

Defined in Morley.Types

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 Morley.Types

FromJSON StackRef Source # 
Instance details

Defined in Morley.Types

Buildable StackRef Source # 
Instance details

Defined in Morley.Types

Methods

build :: StackRef -> Builder #

type Rep StackRef Source # 
Instance details

Defined in Morley.Types

type Rep StackRef = D1 (MetaData "StackRef" "Morley.Types" "morley-0.1.0.5-JGwsFje78IP81WIHW6apex" True) (C1 (MetaCons "StackRef" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Integer)))

newtype MorleyLogs Source #

Morley interpreter state

Constructors

MorleyLogs 

Fields

Instances
Eq MorleyLogs Source # 
Instance details

Defined in Morley.Types

Show MorleyLogs Source # 
Instance details

Defined in Morley.Types

Default MorleyLogs Source # 
Instance details

Defined in Morley.Types

Methods

def :: MorleyLogs #

Buildable MorleyLogs Source # 
Instance details

Defined in Morley.Types

Methods

build :: MorleyLogs -> Builder #

data StackFn Source #

A stack function that expresses the type signature of a LetMacro

Instances
Eq StackFn Source # 
Instance details

Defined in Morley.Types

Methods

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

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

Data StackFn Source # 
Instance details

Defined in Morley.Types

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 :: (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 Morley.Types

Generic StackFn Source # 
Instance details

Defined in Morley.Types

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 Morley.Types

FromJSON StackFn Source # 
Instance details

Defined in Morley.Types

Buildable StackFn Source # 
Instance details

Defined in Morley.Types

Methods

build :: StackFn -> Builder #

type Rep StackFn Source # 
Instance details

Defined in Morley.Types

newtype Var Source #

Constructors

Var Text 
Instances
Eq Var Source # 
Instance details

Defined in Morley.Types

Methods

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

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

Data Var Source # 
Instance details

Defined in Morley.Types

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 :: (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 Morley.Types

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 Morley.Types

Methods

showsPrec :: Int -> Var -> ShowS #

show :: Var -> String #

showList :: [Var] -> ShowS #

Generic Var Source # 
Instance details

Defined in Morley.Types

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 Morley.Types

FromJSON Var Source # 
Instance details

Defined in Morley.Types

Buildable Var Source # 
Instance details

Defined in Morley.Types

Methods

build :: Var -> Builder #

type Rep Var Source # 
Instance details

Defined in Morley.Types

type Rep Var = D1 (MetaData "Var" "Morley.Types" "morley-0.1.0.5-JGwsFje78IP81WIHW6apex" 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
Eq TyVar Source # 
Instance details

Defined in Morley.Types

Methods

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

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

Data TyVar Source # 
Instance details

Defined in Morley.Types

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 :: (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 Morley.Types

Methods

showsPrec :: Int -> TyVar -> ShowS #

show :: TyVar -> String #

showList :: [TyVar] -> ShowS #

Generic TyVar Source # 
Instance details

Defined in Morley.Types

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 Morley.Types

FromJSON TyVar Source # 
Instance details

Defined in Morley.Types

Buildable TyVar Source # 
Instance details

Defined in Morley.Types

Methods

build :: TyVar -> Builder #

type Rep TyVar Source # 
Instance details

Defined in Morley.Types

varSet :: StackTypePattern -> Set Var Source #

Get the set of variables in a stack pattern

data LetMacro Source #

A programmer-defined macro

Constructors

LetMacro 

Fields

Instances
Eq LetMacro Source # 
Instance details

Defined in Morley.Types

Data LetMacro Source # 
Instance details

Defined in Morley.Types

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 :: (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 Morley.Types

Generic LetMacro Source # 
Instance details

Defined in Morley.Types

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 Morley.Types

FromJSON LetMacro Source # 
Instance details

Defined in Morley.Types

Buildable LetMacro Source # 
Instance details

Defined in Morley.Types

Methods

build :: LetMacro -> Builder #

type Rep LetMacro Source # 
Instance details

Defined in Morley.Types

data LetValue Source #

A programmer-defined constant

Constructors

LetValue 

Fields

Instances
Eq LetValue Source # 
Instance details

Defined in Morley.Types

Show LetValue Source # 
Instance details

Defined in Morley.Types

ToJSON LetValue Source # 
Instance details

Defined in Morley.Types

FromJSON LetValue Source # 
Instance details

Defined in Morley.Types

data LetType Source #

A programmer-defined type-synonym

Constructors

LetType 

Fields

Instances
Eq LetType Source # 
Instance details

Defined in Morley.Types

Methods

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

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

Show LetType Source # 
Instance details

Defined in Morley.Types

ToJSON LetType Source # 
Instance details

Defined in Morley.Types

FromJSON LetType Source # 
Instance details

Defined in Morley.Types

Orphan instances

Buildable ExpandedInstr Source # 
Instance details

Buildable Instr Source # 
Instance details

Methods

build :: Instr -> Builder #