morley-1.0.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
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 #

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

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

Lift Comparable Source # 
Instance details

Defined in Michelson.Untyped.Type

Methods

lift :: Comparable -> Q Exp #

Arbitrary Comparable Source # 
Instance details

Defined in Util.Test.Arbitrary

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 #

ToADTArbitrary Comparable Source # 
Instance details

Defined in Util.Test.Arbitrary

RenderDoc Comparable Source # 
Instance details

Defined in Michelson.Untyped.Type

type Rep Comparable Source # 
Instance details

Defined in Michelson.Untyped.Type

type Rep Comparable = D1 (MetaData "Comparable" "Michelson.Untyped.Type" "morley-1.0.0-Jo9z4xumEmKBIsSgg9Z0MH" False) (C1 (MetaCons "Comparable" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 CT) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (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 #

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

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.0.0-Jo9z4xumEmKBIsSgg9Z0MH" False) (((C1 (MetaCons "Tc" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (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 "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 Comparable)) :+: 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 Comparable) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Type)) :+: C1 (MetaCons "TBigMap" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Comparable) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (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 #

Lift CT Source # 
Instance details

Defined in Michelson.Untyped.Type

Methods

lift :: CT -> Q Exp #

Arbitrary CT Source # 
Instance details

Defined in Util.Test.Arbitrary

Methods

arbitrary :: Gen CT #

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

ToADTArbitrary CT Source # 
Instance details

Defined in Util.Test.Arbitrary

SingKind CT Source # 
Instance details

Defined in Michelson.Typed.Sing

Associated Types

type Demote CT = (r :: Type) #

RenderDoc CT Source # 
Instance details

Defined in Michelson.Untyped.Type

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-1.0.0-Jo9z4xumEmKBIsSgg9Z0MH" 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
type Demote CT Source # 
Instance details

Defined in Michelson.Typed.Sing

type Demote CT = CT

pattern Tint :: T Source #

pattern Tnat :: T Source #

pattern Tstring :: T Source #

pattern Tbytes :: T Source #

pattern Tmutez :: T Source #

pattern Tbool :: T Source #

pattern Tkey_hash :: T Source #

pattern Ttimestamp :: T Source #

pattern Taddress :: T Source #

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.