witness-0.6.1: values that witness types
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Type.Witness.Specific.Symbol

Synopsis

Documentation

data SymbolType symbol where Source #

Constructors

MkSymbolType :: KnownSymbol symbol => SymbolType symbol 

Instances

Instances details
TestEquality SymbolType Source # 
Instance details

Defined in Data.Type.Witness.Specific.Symbol

Methods

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

TestOrder SymbolType Source # 
Instance details

Defined in Data.Type.Witness.Specific.Symbol

Methods

testCompare :: forall (a :: k) (b :: k). SymbolType a -> SymbolType b -> WOrdering a b Source #

Representative SymbolType Source # 
Instance details

Defined in Data.Type.Witness.Specific.Symbol

WitnessValue SymbolType Source # 
Instance details

Defined in Data.Type.Witness.Specific.Symbol

Associated Types

type WitnessValueType SymbolType Source #

Methods

witnessToValue :: forall (t :: k). SymbolType t -> WitnessValueType SymbolType Source #

valueToWitness :: WitnessValueType SymbolType -> (forall (t :: k). SymbolType t -> r) -> r Source #

KnownSymbol symbol => Is SymbolType (symbol :: Symbol) Source # 
Instance details

Defined in Data.Type.Witness.Specific.Symbol

Show (SymbolType symbol) Source # 
Instance details

Defined in Data.Type.Witness.Specific.Symbol

Methods

showsPrec :: Int -> SymbolType symbol -> ShowS #

show :: SymbolType symbol -> String #

showList :: [SymbolType symbol] -> ShowS #

AllConstraint Show SymbolType Source # 
Instance details

Defined in Data.Type.Witness.Specific.Symbol

Methods

allConstraint :: forall (t :: kt). Dict (Show (SymbolType t)) Source #

type WitnessValueType SymbolType Source # 
Instance details

Defined in Data.Type.Witness.Specific.Symbol

data Symbol #

(Kind) This is the kind of type-level symbols. Declared here because class IP needs it

Instances

Instances details
SingKind Symbol

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type DemoteRep Symbol

Methods

fromSing :: forall (a :: Symbol). Sing a -> DemoteRep Symbol

TestEquality SymbolType Source # 
Instance details

Defined in Data.Type.Witness.Specific.Symbol

Methods

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

KnownSymbol a => SingI (a :: Symbol)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

sing :: Sing a

TestOrder SymbolType Source # 
Instance details

Defined in Data.Type.Witness.Specific.Symbol

Methods

testCompare :: forall (a :: k) (b :: k). SymbolType a -> SymbolType b -> WOrdering a b Source #

Representative SymbolType Source # 
Instance details

Defined in Data.Type.Witness.Specific.Symbol

WitnessValue SymbolType Source # 
Instance details

Defined in Data.Type.Witness.Specific.Symbol

Associated Types

type WitnessValueType SymbolType Source #

Methods

witnessToValue :: forall (t :: k). SymbolType t -> WitnessValueType SymbolType Source #

valueToWitness :: WitnessValueType SymbolType -> (forall (t :: k). SymbolType t -> r) -> r Source #

KnownSymbol symbol => Is SymbolType (symbol :: Symbol) Source # 
Instance details

Defined in Data.Type.Witness.Specific.Symbol

AllConstraint Show SymbolType Source # 
Instance details

Defined in Data.Type.Witness.Specific.Symbol

Methods

allConstraint :: forall (t :: kt). Dict (Show (SymbolType t)) Source #

type DemoteRep Symbol 
Instance details

Defined in GHC.Generics

type DemoteRep Symbol = String
data Sing (s :: Symbol) 
Instance details

Defined in GHC.Generics

data Sing (s :: Symbol) where
type WitnessValueType SymbolType Source # 
Instance details

Defined in Data.Type.Witness.Specific.Symbol

type Compare (a :: Symbol) (b :: Symbol) 
Instance details

Defined in Data.Type.Ord

type Compare (a :: Symbol) (b :: Symbol) = CmpSymbol a b

class KnownSymbol (n :: Symbol) #

This class gives the string associated with a type-level symbol. There are instances of the class for every concrete literal: "hello", etc.

Since: base-4.7.0.0

Minimal complete definition

symbolSing