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

Michelson.Untyped.Type

Description

Michelson types represented in untyped model.

Synopsis

Documentation

data Ty Source #

Constructors

Ty ~T TypeAnn 

Instances

Instances details
Eq Ty Source # 
Instance details

Defined in Michelson.Untyped.Type

Methods

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

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

Data Ty 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) -> Ty -> c Ty #

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

toConstr :: Ty -> Constr #

dataTypeOf :: Ty -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Ty Source # 
Instance details

Defined in Michelson.Untyped.Type

Methods

showsPrec :: Int -> Ty -> ShowS #

show :: Ty -> String #

showList :: [Ty] -> ShowS #

Generic Ty Source # 
Instance details

Defined in Michelson.Untyped.Type

Associated Types

type Rep Ty :: Type -> Type #

Methods

from :: Ty -> Rep Ty x #

to :: Rep Ty x -> Ty #

ToJSON Ty Source # 
Instance details

Defined in Michelson.Untyped.Type

FromJSON Ty Source # 
Instance details

Defined in Michelson.Untyped.Type

NFData Ty Source # 
Instance details

Defined in Michelson.Untyped.Type

Methods

rnf :: Ty -> () #

Buildable Ty Source # 
Instance details

Defined in Michelson.Untyped.Type

Methods

build :: Ty -> Builder #

RenderDoc Ty Source # 
Instance details

Defined in Michelson.Untyped.Type

FromExpression Ty Source # 
Instance details

Defined in Morley.Micheline.Class

ToExpression Ty Source # 
Instance details

Defined in Morley.Micheline.Class

Lift Ty Source # 
Instance details

Defined in Michelson.Untyped.Type

Methods

lift :: Ty -> Q Exp #

liftTyped :: Ty -> Q (TExp Ty) #

RenderDoc (Prettier Ty) Source # 
Instance details

Defined in Michelson.Untyped.Type

type Rep Ty Source # 
Instance details

Defined in Michelson.Untyped.Type

data T Source #

Instances

Instances details
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 :: forall r r'. (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

NFData T Source # 
Instance details

Defined in Michelson.Untyped.Type

Methods

rnf :: T -> () #

Buildable T Source # 
Instance details

Defined in Michelson.Untyped.Type

Methods

build :: T -> Builder #

RenderDoc T Source # 
Instance details

Defined in Michelson.Untyped.Type

FromExpression T Source # 
Instance details

Defined in Morley.Micheline.Class

ToExpression T Source # 
Instance details

Defined in Morley.Micheline.Class

Lift T Source # 
Instance details

Defined in Michelson.Untyped.Type

Methods

lift :: T -> Q Exp #

liftTyped :: T -> Q (TExp T) #

type Rep T Source # 
Instance details

Defined in Michelson.Untyped.Type

type Rep T = D1 ('MetaData "T" "Michelson.Untyped.Type" "morley-1.15.1-inplace" 'False) ((((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 "TChainId" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TOption" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Ty))) :+: (C1 ('MetaCons "TList" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Ty)) :+: C1 ('MetaCons "TSet" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Ty))))) :+: ((C1 ('MetaCons "TOperation" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "TContract" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Ty)) :+: C1 ('MetaCons "TTicket" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Ty)))) :+: ((C1 ('MetaCons "TPair" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 FieldAnn) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 FieldAnn) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 VarAnn))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 VarAnn) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Ty) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Ty)))) :+: C1 ('MetaCons "TOr" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 FieldAnn) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 FieldAnn)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Ty) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Ty)))) :+: (C1 ('MetaCons "TLambda" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Ty) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Ty)) :+: C1 ('MetaCons "TMap" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Ty) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Ty)))))) :+: (((C1 ('MetaCons "TBigMap" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Ty) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Ty)) :+: (C1 ('MetaCons "TInt" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TNat" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "TString" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TBytes" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TMutez" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TBool" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "TKeyHash" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "TBls12381Fr" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TBls12381G1" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "TBls12381G2" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TTimestamp" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TAddress" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TNever" 'PrefixI 'False) (U1 :: Type -> Type))))))

data ParameterType Source #

Since Babylon parameter type can have special root annotation.

Constructors

ParameterType Ty RootAnn 

Instances

Instances details
Eq ParameterType Source # 
Instance details

Defined in Michelson.Untyped.Type

Data ParameterType 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) -> ParameterType -> c ParameterType #

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

toConstr :: ParameterType -> Constr #

dataTypeOf :: ParameterType -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ParameterType Source # 
Instance details

Defined in Michelson.Untyped.Type

Generic ParameterType Source # 
Instance details

Defined in Michelson.Untyped.Type

Associated Types

type Rep ParameterType :: Type -> Type #

ToJSON ParameterType Source # 
Instance details

Defined in Michelson.Untyped.Type

FromJSON ParameterType Source # 
Instance details

Defined in Michelson.Untyped.Type

NFData ParameterType Source # 
Instance details

Defined in Michelson.Untyped.Type

Methods

rnf :: ParameterType -> () #

Buildable ParameterType Source # 
Instance details

Defined in Michelson.Untyped.Type

RenderDoc ParameterType Source # 
Instance details

Defined in Michelson.Untyped.Type

Lift ParameterType Source # 
Instance details

Defined in Michelson.Untyped.Type

RenderDoc (Prettier ParameterType) Source # 
Instance details

Defined in Michelson.Untyped.Type

type Rep ParameterType Source # 
Instance details

Defined in Michelson.Untyped.Type

type Rep ParameterType = D1 ('MetaData "ParameterType" "Michelson.Untyped.Type" "morley-1.15.1-inplace" 'False) (C1 ('MetaCons "ParameterType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Ty) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 RootAnn)))

tpair :: Ty -> Ty -> T Source #

tor :: Ty -> Ty -> T Source #

typair :: Ty -> Ty -> Ty Source #

tyor :: Ty -> Ty -> Ty Source #

tyImplicitAccountParam :: Ty Source #

For implicit account, which Ty its parameter seems to have from outside.