morley-0.3.0: Developer tools for the Michelson Language

Safe HaskellNone
LanguageHaskell2010

Michelson.Typed.Sing

Contents

Description

Module, providing singleton boilerplate for T and CT 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 family Sing (a :: k) :: Type #

The singleton kind-indexed data family.

Instances
Eq (Sing n) Source # 
Instance details

Defined in Util.Peano

Methods

(==) :: Sing n -> Sing n -> Bool #

(/=) :: Sing n -> Sing n -> Bool #

data Sing (a :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Instances

data Sing (a :: Bool) where
data Sing (a :: Ordering) 
Instance details

Defined in Data.Singletons.Prelude.Instances

data Sing (a :: Ordering) where
data Sing (n :: Nat) 
Instance details

Defined in Data.Singletons.TypeLits.Internal

data Sing (n :: Nat) where
data Sing (n :: Symbol) 
Instance details

Defined in Data.Singletons.TypeLits.Internal

data Sing (n :: Symbol) where
data Sing (a :: ()) 
Instance details

Defined in Data.Singletons.Prelude.Instances

data Sing (a :: ()) where
data Sing (a :: Void) 
Instance details

Defined in Data.Singletons.Prelude.Instances

data Sing (a :: Void)
data Sing (a :: All) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

data Sing (a :: All) where
data Sing (a :: Any) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

data Sing (a :: Any) where
data Sing (_ :: Nat) Source # 
Instance details

Defined in Util.Peano

data Sing (_ :: Nat) where
data Sing (a :: CT) Source #

Instance of data family Sing for CT.

Instance details

Defined in Michelson.Typed.Sing

data Sing (a :: CT) where
data Sing (a :: T) Source #

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

Instance details

Defined in Michelson.Typed.Sing

data Sing (a :: T) where
data Sing (b :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.Instances

data Sing (b :: [a]) where
  • SNil :: forall a (b :: [a]). Sing ([] :: [a])
  • SCons :: forall a (b :: [a]) (n1 :: a) (n2 :: [a]). Sing n1 -> Sing n2 -> Sing (n1 ': n2)
data Sing (b :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Instances

data Sing (b :: Maybe a) where
data Sing (b :: Min a) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

data Sing (b :: Min a) where
data Sing (b :: Max a) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

data Sing (b :: Max a) where
data Sing (b :: First a) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

data Sing (b :: First a) where
data Sing (b :: Last a) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

data Sing (b :: Last a) where
data Sing (a :: WrappedMonoid m) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

data Sing (a :: WrappedMonoid m) where
data Sing (b :: Option a) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

data Sing (b :: Option a) where
data Sing (b :: Identity a) 
Instance details

Defined in Data.Singletons.Prelude.Instances

data Sing (b :: Identity a) where
data Sing (b :: First a) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

data Sing (b :: First a) where
data Sing (b :: Last a) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

data Sing (b :: Last a) where
data Sing (b :: Dual a) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

data Sing (b :: Dual a) where
data Sing (b :: Sum a) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

data Sing (b :: Sum a) where
data Sing (b :: Product a) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

data Sing (b :: Product a) where
data Sing (b :: Down a) 
Instance details

Defined in Data.Singletons.Prelude.Ord

data Sing (b :: Down a) where
data Sing (b :: NonEmpty a) 
Instance details

Defined in Data.Singletons.Prelude.Instances

data Sing (b :: NonEmpty a) where
data Sing (b :: Endo a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

data Sing (b :: Endo a) where
data Sing (b :: MaxInternal a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

data Sing (b :: MaxInternal a) where
data Sing (b :: MinInternal a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

data Sing (b :: MinInternal a) where
data Sing (c :: Either a b) 
Instance details

Defined in Data.Singletons.Prelude.Instances

data Sing (c :: Either a b) where
data Sing (c :: (a, b)) 
Instance details

Defined in Data.Singletons.Prelude.Instances

data Sing (c :: (a, b)) where
data Sing (c :: Arg a b) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

data Sing (c :: Arg a b) where
newtype Sing (f :: k1 ~> k2) 
Instance details

Defined in Data.Singletons.Internal

newtype Sing (f :: k1 ~> k2) = SLambda {}
data Sing (b :: StateL s a) 
Instance details

Defined in Data.Singletons.Prelude.Traversable

data Sing (b :: StateL s a) where
  • SStateL :: forall s a (b :: StateL s a) (x :: s ~> (s, a)). Sing x -> Sing (StateL x)
data Sing (b :: StateR s a) 
Instance details

Defined in Data.Singletons.Prelude.Traversable

data Sing (b :: StateR s a) where
  • SStateR :: forall s a (b :: StateR s a) (x :: s ~> (s, a)). Sing x -> Sing (StateR x)
data Sing (d :: (a, b, c)) 
Instance details

Defined in Data.Singletons.Prelude.Instances

data Sing (d :: (a, b, c)) where
data Sing (c :: Const a b) 
Instance details

Defined in Data.Singletons.Prelude.Const

data Sing (c :: Const a b) where
data Sing (e :: (a, b, c, d)) 
Instance details

Defined in Data.Singletons.Prelude.Instances

data Sing (e :: (a, b, c, d)) where
data Sing (f :: (a, b, c, d, e)) 
Instance details

Defined in Data.Singletons.Prelude.Instances

data Sing (f :: (a, b, c, d, e)) where
  • STuple5 :: forall a b c d e (f :: (a, b, c, d, e)) (n1 :: a) (n2 :: b) (n3 :: c) (n4 :: d) (n5 :: e). Sing n1 -> Sing n2 -> Sing n3 -> Sing n4 -> Sing n5 -> Sing ((,,,,) n1 n2 n3 n4 n5)
data Sing (g :: (a, b, c, d, e, f)) 
Instance details

Defined in Data.Singletons.Prelude.Instances

data Sing (g :: (a, b, c, d, e, f)) where
  • STuple6 :: forall a b c d e f (g :: (a, b, c, d, e, f)) (n1 :: a) (n2 :: b) (n3 :: c) (n4 :: d) (n5 :: e) (n6 :: f). Sing n1 -> Sing n2 -> Sing n3 -> Sing n4 -> Sing n5 -> Sing n6 -> Sing ((,,,,,) n1 n2 n3 n4 n5 n6)
data Sing (h :: (a, b, c, d, e, f, g)) 
Instance details

Defined in Data.Singletons.Prelude.Instances

data Sing (h :: (a, b, c, d, e, f, g)) where
  • STuple7 :: forall a b c d e f g (h :: (a, b, c, d, e, f, g)) (n1 :: a) (n2 :: b) (n3 :: c) (n4 :: d) (n5 :: e) (n6 :: f) (n7 :: g). Sing n1 -> Sing n2 -> Sing n3 -> Sing n4 -> Sing n5 -> Sing n6 -> Sing n7 -> Sing ((,,,,,,) n1 n2 n3 n4 n5 n6 n7)

withSomeSingT :: T -> (forall (a :: T). (Typeable a, SingI 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.

withSomeSingCT :: CT -> (forall (a :: CT). (SingI a, Typeable a) => Sing a -> r) -> r Source #

Version of withSomeSing with Typeable constraint provided to processing function.

Required for not to erase this useful constraint when doing conversion from value of type CT 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

fromSingCT :: Sing (a :: CT) -> CT Source #

Orphan instances

SingKind CT Source # 
Instance details

Associated Types

type Demote CT = (r :: Type) #

SingKind T Source # 
Instance details

Associated Types

type Demote T = (r :: Type) #

Methods

fromSing :: Sing a -> Demote T #

toSing :: Demote T -> SomeSing T #

SingI CInt Source # 
Instance details

Methods

sing :: Sing CInt #

SingI CNat Source # 
Instance details

Methods

sing :: Sing CNat #

SingI CString Source # 
Instance details

Methods

sing :: Sing CString #

SingI CBytes Source # 
Instance details

Methods

sing :: Sing CBytes #

SingI CMutez Source # 
Instance details

Methods

sing :: Sing CMutez #

SingI CBool Source # 
Instance details

Methods

sing :: Sing CBool #

SingI CKeyHash Source # 
Instance details

Methods

sing :: Sing CKeyHash #

SingI CTimestamp Source # 
Instance details

Methods

sing :: Sing CTimestamp #

SingI CAddress Source # 
Instance details

Methods

sing :: Sing CAddress #

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 TOperation Source # 
Instance details

Methods

sing :: Sing TOperation #

(SingI t, Typeable t) => SingI (Tc t :: T) Source # 
Instance details

Methods

sing :: Sing (Tc t) #

(SingI a, Typeable a) => SingI (TOption a :: T) Source # 
Instance details

Methods

sing :: Sing (TOption a) #

(SingI a, Typeable a) => SingI (TList a :: T) Source # 
Instance details

Methods

sing :: Sing (TList a) #

(SingI a, Typeable a) => SingI (TSet a :: T) Source # 
Instance details

Methods

sing :: Sing (TSet a) #

(SingI a, Typeable a) => SingI (TContract a :: T) Source # 
Instance details

Methods

sing :: Sing (TContract a) #

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

Methods

sing :: Sing (TPair a b) #

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

Methods

sing :: Sing (TOr a b) #

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

Methods

sing :: Sing (TLambda a b) #

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

Methods

sing :: Sing (TMap a b) #

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

Methods

sing :: Sing (TBigMap a b) #