morley-1.18.0: Developer tools for the Michelson Language
Safe HaskellSafe-Inferred
LanguageHaskell2010

Morley.Michelson.Typed.T

Description

Module, providing T data type, representing Michelson language types without annotations.

Synopsis

Documentation

data T Source #

Michelson language type with annotations stripped off.

Instances

Instances details
Generic T Source # 
Instance details

Defined in Morley.Michelson.Typed.T

Associated Types

type Rep T :: Type -> Type #

Methods

from :: T -> Rep T x #

to :: Rep T x -> T #

Show T Source # 
Instance details

Defined in Morley.Michelson.Typed.T

Methods

showsPrec :: Int -> T -> ShowS #

show :: T -> String #

showList :: [T] -> ShowS #

NFData T Source # 
Instance details

Defined in Morley.Michelson.Typed.T

Methods

rnf :: T -> () #

Buildable T Source # 
Instance details

Defined in Morley.Michelson.Typed.T

Methods

build :: T -> Builder #

Eq T Source # 
Instance details

Defined in Morley.Michelson.Typed.T

Methods

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

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

ToExpression T Source # 
Instance details

Defined in Morley.Micheline.Class

RenderDoc T Source # 
Instance details

Defined in Morley.Michelson.Typed.T

SingKind T Source # 
Instance details

Defined in Morley.Michelson.Typed.Sing

Associated Types

type Demote T = (r :: Type) #

Methods

fromSing :: forall (a :: T). Sing a -> Demote T #

toSing :: Demote T -> SomeSing T #

(SDecide T, SDecide Peano) => SDecide T Source # 
Instance details

Defined in Morley.Michelson.Typed.Sing

Methods

(%~) :: forall (a :: T) (b :: T). Sing a -> Sing b -> Decision (a :~: b) #

(SDecide T, SDecide Peano) => TestCoercion SingT Source # 
Instance details

Defined in Morley.Michelson.Typed.Sing

Methods

testCoercion :: forall (a :: k) (b :: k). SingT a -> SingT b -> Maybe (Coercion a b) #

(SDecide T, SDecide Peano) => TestEquality SingT Source # 
Instance details

Defined in Morley.Michelson.Typed.Sing

Methods

testEquality :: forall (a :: k) (b :: k). SingT a -> SingT b -> Maybe (a :~: b) #

FromExp x T Source # 
Instance details

Defined in Morley.Micheline.Class

Methods

fromExp :: Exp x -> Either (FromExpError x) T Source #

SingI 'TAddress Source # 
Instance details

Defined in Morley.Michelson.Typed.Sing

Methods

sing :: Sing 'TAddress #

SingI 'TBls12381Fr Source # 
Instance details

Defined in Morley.Michelson.Typed.Sing

Methods

sing :: Sing 'TBls12381Fr #

SingI 'TBls12381G1 Source # 
Instance details

Defined in Morley.Michelson.Typed.Sing

Methods

sing :: Sing 'TBls12381G1 #

SingI 'TBls12381G2 Source # 
Instance details

Defined in Morley.Michelson.Typed.Sing

Methods

sing :: Sing 'TBls12381G2 #

SingI 'TBool Source # 
Instance details

Defined in Morley.Michelson.Typed.Sing

Methods

sing :: Sing 'TBool #

SingI 'TBytes Source # 
Instance details

Defined in Morley.Michelson.Typed.Sing

Methods

sing :: Sing 'TBytes #

SingI 'TChainId Source # 
Instance details

Defined in Morley.Michelson.Typed.Sing

Methods

sing :: Sing 'TChainId #

SingI 'TChest Source # 
Instance details

Defined in Morley.Michelson.Typed.Sing

Methods

sing :: Sing 'TChest #

SingI 'TChestKey Source # 
Instance details

Defined in Morley.Michelson.Typed.Sing

Methods

sing :: Sing 'TChestKey #

SingI 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Sing

Methods

sing :: Sing 'TInt #

SingI 'TKey Source # 
Instance details

Defined in Morley.Michelson.Typed.Sing

Methods

sing :: Sing 'TKey #

SingI 'TKeyHash Source # 
Instance details

Defined in Morley.Michelson.Typed.Sing

Methods

sing :: Sing 'TKeyHash #

SingI 'TMutez Source # 
Instance details

Defined in Morley.Michelson.Typed.Sing

Methods

sing :: Sing 'TMutez #

SingI 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Sing

Methods

sing :: Sing 'TNat #

SingI 'TNever Source # 
Instance details

Defined in Morley.Michelson.Typed.Sing

Methods

sing :: Sing 'TNever #

SingI 'TOperation Source # 
Instance details

Defined in Morley.Michelson.Typed.Sing

Methods

sing :: Sing 'TOperation #

SingI 'TSignature Source # 
Instance details

Defined in Morley.Michelson.Typed.Sing

Methods

sing :: Sing 'TSignature #

SingI 'TString Source # 
Instance details

Defined in Morley.Michelson.Typed.Sing

Methods

sing :: Sing 'TString #

SingI 'TTimestamp Source # 
Instance details

Defined in Morley.Michelson.Typed.Sing

Methods

sing :: Sing 'TTimestamp #

SingI 'TTxRollupL2Address Source # 
Instance details

Defined in Morley.Michelson.Typed.Sing

SingI 'TUnit Source # 
Instance details

Defined in Morley.Michelson.Typed.Sing

Methods

sing :: Sing 'TUnit #

SingI n => SingI ('TContract n :: T) Source # 
Instance details

Defined in Morley.Michelson.Typed.Sing

Methods

sing :: Sing ('TContract n) #

SingI n => SingI ('TList n :: T) Source # 
Instance details

Defined in Morley.Michelson.Typed.Sing

Methods

sing :: Sing ('TList n) #

SingI n => SingI ('TOption n :: T) Source # 
Instance details

Defined in Morley.Michelson.Typed.Sing

Methods

sing :: Sing ('TOption n) #

SingI n => SingI ('TSaplingState n :: T) Source # 
Instance details

Defined in Morley.Michelson.Typed.Sing

Methods

sing :: Sing ('TSaplingState n) #

SingI n => SingI ('TSaplingTransaction n :: T) Source # 
Instance details

Defined in Morley.Michelson.Typed.Sing

SingI n => SingI ('TSet n :: T) Source # 
Instance details

Defined in Morley.Michelson.Typed.Sing

Methods

sing :: Sing ('TSet n) #

SingI n => SingI ('TTicket n :: T) Source # 
Instance details

Defined in Morley.Michelson.Typed.Sing

Methods

sing :: Sing ('TTicket n) #

(SingI inp, SingI out) => FromExp RegularExp (Instr '[inp] '[out]) Source # 
Instance details

Defined in Morley.Micheline.Class

(SingI n1, SingI n2) => SingI ('TBigMap n1 n2 :: T) Source # 
Instance details

Defined in Morley.Michelson.Typed.Sing

Methods

sing :: Sing ('TBigMap n1 n2) #

(SingI n1, SingI n2) => SingI ('TLambda n1 n2 :: T) Source # 
Instance details

Defined in Morley.Michelson.Typed.Sing

Methods

sing :: Sing ('TLambda n1 n2) #

(SingI n1, SingI n2) => SingI ('TMap n1 n2 :: T) Source # 
Instance details

Defined in Morley.Michelson.Typed.Sing

Methods

sing :: Sing ('TMap n1 n2) #

(SingI n1, SingI n2) => SingI ('TOr n1 n2 :: T) Source # 
Instance details

Defined in Morley.Michelson.Typed.Sing

Methods

sing :: Sing ('TOr n1 n2) #

(SingI n1, SingI n2) => SingI ('TPair n1 n2 :: T) Source # 
Instance details

Defined in Morley.Michelson.Typed.Sing

Methods

sing :: Sing ('TPair n1 n2) #

Buildable (MismatchError T) Source # 
Instance details

Defined in Morley.Michelson.Typed.T

Buildable (MismatchError [T]) Source # 
Instance details

Defined in Morley.Michelson.Typed.T

Methods

build :: MismatchError [T] -> Builder #

RenderDoc (Prettier T) Source # 
Instance details

Defined in Morley.Michelson.Typed.T

RenderDoc (MismatchError T) Source # 
Instance details

Defined in Morley.Michelson.Typed.T

RenderDoc (MismatchError [T]) Source # 
Instance details

Defined in Morley.Michelson.Typed.T

SingI t => CheckScope (ComparabilityScope t) Source # 
Instance details

Defined in Morley.Michelson.Typed.Scope

type Rep T Source # 
Instance details

Defined in Morley.Michelson.Typed.T

type Rep T = D1 ('MetaData "T" "Morley.Michelson.Typed.T" "morley-1.18.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 T)) :+: C1 ('MetaCons "TList" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 T))) :+: (C1 ('MetaCons "TSet" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 T)) :+: C1 ('MetaCons "TOperation" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "TContract" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 T)) :+: C1 ('MetaCons "TTicket" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 T))) :+: (C1 ('MetaCons "TPair" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 T) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 T)) :+: C1 ('MetaCons "TOr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 T) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 T)))) :+: ((C1 ('MetaCons "TLambda" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 T) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 T)) :+: C1 ('MetaCons "TMap" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 T) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 T))) :+: (C1 ('MetaCons "TBigMap" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 T) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 T)) :+: 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 "TChest" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "TChestKey" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TSaplingState" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Peano))) :+: (C1 ('MetaCons "TSaplingTransaction" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Peano)) :+: (C1 ('MetaCons "TTxRollupL2Address" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TNever" 'PrefixI 'False) (U1 :: Type -> Type)))))))
type Demote T Source # 
Instance details

Defined in Morley.Michelson.Typed.Sing

type Demote T = T
type Sing Source # 
Instance details

Defined in Morley.Michelson.Typed.Sing

type Sing = SingT

toUType :: T -> Ty Source #

Converts from T to Ty.

buildStack :: [T] -> Builder Source #

Format type stack in a pretty way.