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

Michelson.Untyped.Type

Description

Michelson types represented in untyped model.

Synopsis

Documentation

data Type Source #

Constructors

Type ~T TypeAnn 

Instances

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

Lift Type Source # 
Instance details

Defined in Michelson.Untyped.Type

Methods

lift :: Type -> Q Exp #

Arbitrary Type Source # 
Instance details

Defined in Util.Test.Arbitrary

Methods

arbitrary :: Gen Type #

shrink :: Type -> [Type] #

ToJSON Type Source # 
Instance details

Defined in Michelson.Untyped.Type

FromJSON Type Source # 
Instance details

Defined in Michelson.Untyped.Type

NFData Type Source # 
Instance details

Defined in Michelson.Untyped.Type

Methods

rnf :: Type -> () #

Buildable Type Source # 
Instance details

Defined in Michelson.Untyped.Type

Methods

build :: Type -> Builder #

ToADTArbitrary Type Source # 
Instance details

Defined in Util.Test.Arbitrary

RenderDoc Type Source # 
Instance details

Defined in Michelson.Untyped.Type

RenderDoc (Prettier Type) Source # 
Instance details

Defined in Michelson.Untyped.Type

type Rep Type 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 #

Lift T Source # 
Instance details

Defined in Michelson.Untyped.Type

Methods

lift :: T -> Q Exp #

Arbitrary T Source # 
Instance details

Defined in Util.Test.Arbitrary

Methods

arbitrary :: Gen T #

shrink :: T -> [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 #

ToADTArbitrary T Source # 
Instance details

Defined in Util.Test.Arbitrary

RenderDoc T Source # 
Instance details

Defined in Michelson.Untyped.Type

type Rep T Source # 
Instance details

Defined in Michelson.Untyped.Type

type Rep T = D1 ('MetaData "T" "Michelson.Untyped.Type" "morley-1.7.0-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 Type))))) :+: ((C1 ('MetaCons "TList" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Type)) :+: (C1 ('MetaCons "TSet" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Type)) :+: C1 ('MetaCons "TOperation" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "TContract" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Type)) :+: (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 Type) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Type))) :+: 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 Type) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Type))))))) :+: (((C1 ('MetaCons "TLambda" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Type) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Type)) :+: (C1 ('MetaCons "TMap" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Type) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Type)) :+: C1 ('MetaCons "TBigMap" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Type) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Type)))) :+: (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 "TTimestamp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TAddress" 'PrefixI 'False) (U1 :: Type -> Type))))))

data ParameterType Source #

Since Babylon parameter type can have special root annotation.

Constructors

ParameterType Type 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 #

Lift ParameterType Source # 
Instance details

Defined in Michelson.Untyped.Type

Methods

lift :: ParameterType -> Q Exp #

Arbitrary ParameterType Source # 
Instance details

Defined in Util.Test.Arbitrary

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

ToADTArbitrary ParameterType Source # 
Instance details

Defined in Util.Test.Arbitrary

RenderDoc 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.7.0-inplace" 'False) (C1 ('MetaCons "ParameterType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Type) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 RootAnn)))

tpair :: Type -> Type -> T Source #

tor :: Type -> Type -> T Source #

tyImplicitAccountParam :: Type Source #

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