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

Michelson.Typed.Sing

Description

Module, providing singleton boilerplate for T data types.

Some functions from Data.Singletons are provided alternative version here. Some instances which are usually generated with TH are manually implemented as they require some specific constraints, namely Typeable and/or Converge, not provided in instances generated by TH.

Synopsis

Documentation

data SingT :: T -> Type where Source #

Instance of data family Sing for T. Custom instance is implemented in order to inject Typeable constraint for some of constructors.

Constructors

STKey :: SingT 'TKey 
STUnit :: SingT 'TUnit 
STSignature :: SingT 'TSignature 
STChainId :: SingT 'TChainId 
STOption :: KnownT a => Sing a -> SingT ('TOption a) 
STList :: KnownT a => Sing a -> SingT ('TList a) 
STSet :: KnownT a => Sing a -> SingT ('TSet a) 
STOperation :: SingT 'TOperation 
STContract :: KnownT a => Sing a -> SingT ('TContract a) 
STPair :: (KnownT a, KnownT b) => Sing a -> Sing b -> SingT ('TPair a b) 
STOr :: (KnownT a, KnownT b) => Sing a -> Sing b -> SingT ('TOr a b) 
STLambda :: (KnownT a, KnownT b) => Sing a -> Sing b -> SingT ('TLambda a b) 
STMap :: (KnownT a, KnownT b) => Sing a -> Sing b -> SingT ('TMap a b) 
STBigMap :: (KnownT a, KnownT b) => Sing a -> Sing b -> SingT ('TBigMap a b) 
STInt :: SingT 'TInt 
STNat :: SingT 'TNat 
STString :: SingT 'TString 
STBytes :: SingT 'TBytes 
STMutez :: SingT 'TMutez 
STBool :: SingT 'TBool 
STKeyHash :: SingT 'TKeyHash 
STTimestamp :: SingT 'TTimestamp 
STAddress :: SingT 'TAddress 

class (Typeable t, SingI t) => KnownT (t :: T) Source #

Typeable + SingI constraints.

This restricts a type to be a constructible type of T kind.

Instances

Instances details
(Typeable t, SingI t) => KnownT t Source # 
Instance details

Defined in Michelson.Typed.Sing

KnownT t => CheckScope (StorageScope t) Source # 
Instance details

Defined in Michelson.Typed.Scope

KnownT t => CheckScope (ParameterScope t) Source # 
Instance details

Defined in Michelson.Typed.Scope

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

Defined in Michelson.Typed.Value

withSomeSingT :: T -> (forall (a :: T). KnownT a => Sing a -> r) -> r Source #

Version of withSomeSing with Typeable constraint provided to processing function.

Required for not to erase these useful constraints when doing conversion from value of type T to its singleton representation.

fromSingT :: Sing (a :: T) -> T Source #

Version of fromSing specialized for use with data instance Sing :: T -> Type which requires Typeable constraint for some of its constructors

Orphan instances

SingKind T Source # 
Instance details

Associated Types

type Demote T = (r :: Type) #

Methods

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

toSing :: Demote T -> SomeSing T #

SingI 'TKey Source # 
Instance details

Methods

sing :: Sing 'TKey #

SingI 'TUnit Source # 
Instance details

Methods

sing :: Sing 'TUnit #

SingI 'TSignature Source # 
Instance details

Methods

sing :: Sing 'TSignature #

SingI 'TChainId Source # 
Instance details

Methods

sing :: Sing 'TChainId #

SingI 'TOperation Source # 
Instance details

Methods

sing :: Sing 'TOperation #

SingI 'TInt Source # 
Instance details

Methods

sing :: Sing 'TInt #

SingI 'TNat Source # 
Instance details

Methods

sing :: Sing 'TNat #

SingI 'TString Source # 
Instance details

Methods

sing :: Sing 'TString #

SingI 'TBytes Source # 
Instance details

Methods

sing :: Sing 'TBytes #

SingI 'TMutez Source # 
Instance details

Methods

sing :: Sing 'TMutez #

SingI 'TBool Source # 
Instance details

Methods

sing :: Sing 'TBool #

SingI 'TKeyHash Source # 
Instance details

Methods

sing :: Sing 'TKeyHash #

SingI 'TTimestamp Source # 
Instance details

Methods

sing :: Sing 'TTimestamp #

SingI 'TAddress Source # 
Instance details

Methods

sing :: Sing 'TAddress #

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

Methods

sing :: Sing ('TOption a) #

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

Methods

sing :: Sing ('TList a) #

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

Methods

sing :: Sing ('TSet a) #

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

Methods

sing :: Sing ('TContract a) #

(KnownT a, KnownT b) => SingI ('TPair a b :: T) Source # 
Instance details

Methods

sing :: Sing ('TPair a b) #

(KnownT a, KnownT b) => SingI ('TOr a b :: T) Source # 
Instance details

Methods

sing :: Sing ('TOr a b) #

(KnownT a, KnownT b) => SingI ('TLambda a b :: T) Source # 
Instance details

Methods

sing :: Sing ('TLambda a b) #

(KnownT a, KnownT b) => SingI ('TMap a b :: T) Source # 
Instance details

Methods

sing :: Sing ('TMap a b) #

(KnownT a, KnownT b) => SingI ('TBigMap a b :: T) Source # 
Instance details

Methods

sing :: Sing ('TBigMap a b) #