parameterized-utils-2.1.5.0: Classes and data structures for working with data-kind indexed types
Copyright(c) Galois Inc 2014-2019
MaintainerJoe Hendrix <jhendrix@galois.com>
Safe HaskellTrustworthy
LanguageHaskell2010

Data.Parameterized.SymbolRepr

Description

This defines a type family SymbolRepr for representing a type-level string (AKA symbol) at runtime. This can be used to branch on a type-level value.

The TestEquality and OrdF instances for SymbolRepr are implemented using unsafeCoerce. This should be typesafe because we maintain the invariant that the string value contained in a SymbolRepr value matches its static type.

At the type level, symbols have very few operations, so SymbolRepr correspondingly has very few functions that manipulate them.

Synopsis

SymbolRepr

data SymbolRepr (nm :: Symbol) Source #

A runtime representation of a GHC type-level symbol.

Instances

Instances details
TestEquality SymbolRepr Source # 
Instance details

Defined in Data.Parameterized.SymbolRepr

Methods

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

HashableF SymbolRepr Source # 
Instance details

Defined in Data.Parameterized.SymbolRepr

Methods

hashWithSaltF :: forall (tp :: k). Int -> SymbolRepr tp -> Int Source #

hashF :: forall (tp :: k). SymbolRepr tp -> Int Source #

ShowF SymbolRepr Source # 
Instance details

Defined in Data.Parameterized.SymbolRepr

Methods

withShow :: forall p q (tp :: k) a. p SymbolRepr -> q tp -> (Show (SymbolRepr tp) => a) -> a Source #

showF :: forall (tp :: k). SymbolRepr tp -> String Source #

showsPrecF :: forall (tp :: k). Int -> SymbolRepr tp -> String -> String Source #

OrdF SymbolRepr Source # 
Instance details

Defined in Data.Parameterized.SymbolRepr

Methods

compareF :: forall (x :: k) (y :: k). SymbolRepr x -> SymbolRepr y -> OrderingF x y Source #

leqF :: forall (x :: k) (y :: k). SymbolRepr x -> SymbolRepr y -> Bool Source #

ltF :: forall (x :: k) (y :: k). SymbolRepr x -> SymbolRepr y -> Bool Source #

geqF :: forall (x :: k) (y :: k). SymbolRepr x -> SymbolRepr y -> Bool Source #

gtF :: forall (x :: k) (y :: k). SymbolRepr x -> SymbolRepr y -> Bool Source #

IsRepr SymbolRepr Source # 
Instance details

Defined in Data.Parameterized.WithRepr

Methods

withRepr :: forall (a :: k) r. SymbolRepr a -> (KnownRepr SymbolRepr a => r) -> r Source #

KnownSymbol s => KnownRepr SymbolRepr (s :: Symbol) Source # 
Instance details

Defined in Data.Parameterized.SymbolRepr

Eq (SymbolRepr x) Source # 
Instance details

Defined in Data.Parameterized.SymbolRepr

Methods

(==) :: SymbolRepr x -> SymbolRepr x -> Bool #

(/=) :: SymbolRepr x -> SymbolRepr x -> Bool #

Ord (SymbolRepr x) Source # 
Instance details

Defined in Data.Parameterized.SymbolRepr

Show (SymbolRepr nm) Source # 
Instance details

Defined in Data.Parameterized.SymbolRepr

Methods

showsPrec :: Int -> SymbolRepr nm -> ShowS #

show :: SymbolRepr nm -> String #

showList :: [SymbolRepr nm] -> ShowS #

Hashable (SymbolRepr nm) Source # 
Instance details

Defined in Data.Parameterized.SymbolRepr

Methods

hashWithSalt :: Int -> SymbolRepr nm -> Int #

hash :: SymbolRepr nm -> Int #

symbolRepr :: SymbolRepr nm -> Text Source #

The underlying text representation of the symbol

knownSymbol :: KnownSymbol s => SymbolRepr s Source #

Generate a value representative for the type level symbol.

someSymbol :: Text -> Some SymbolRepr Source #

Generate a symbol representative at runtime. The type-level symbol will be abstract, as it is hidden by the Some constructor.

data SomeSym (c :: Symbol -> Type) Source #

The SomeSym hides a Symbol parameter but preserves a KnownSymbol constraint on the hidden parameter.

Constructors

forall (s :: Symbol).KnownSymbol s => SomeSym (c s) 

viewSomeSym :: (forall (s :: Symbol). KnownSymbol s => c s -> r) -> SomeSym c -> r Source #

Projects a value out of a SomeSym into a function, re-ifying the Symbol type parameter to the called function, along with the KnownSymbol constraint on that Symbol value.

Re-exports

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

Defined in Data.Parameterized.SymbolRepr

Methods

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

HashableF SymbolRepr Source # 
Instance details

Defined in Data.Parameterized.SymbolRepr

Methods

hashWithSaltF :: forall (tp :: k). Int -> SymbolRepr tp -> Int Source #

hashF :: forall (tp :: k). SymbolRepr tp -> Int Source #

ShowF SymbolRepr Source # 
Instance details

Defined in Data.Parameterized.SymbolRepr

Methods

withShow :: forall p q (tp :: k) a. p SymbolRepr -> q tp -> (Show (SymbolRepr tp) => a) -> a Source #

showF :: forall (tp :: k). SymbolRepr tp -> String Source #

showsPrecF :: forall (tp :: k). Int -> SymbolRepr tp -> String -> String Source #

OrdF SymbolRepr Source # 
Instance details

Defined in Data.Parameterized.SymbolRepr

Methods

compareF :: forall (x :: k) (y :: k). SymbolRepr x -> SymbolRepr y -> OrderingF x y Source #

leqF :: forall (x :: k) (y :: k). SymbolRepr x -> SymbolRepr y -> Bool Source #

ltF :: forall (x :: k) (y :: k). SymbolRepr x -> SymbolRepr y -> Bool Source #

geqF :: forall (x :: k) (y :: k). SymbolRepr x -> SymbolRepr y -> Bool Source #

gtF :: forall (x :: k) (y :: k). SymbolRepr x -> SymbolRepr y -> Bool Source #

KnownSymbol a => SingI (a :: Symbol)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

sing :: Sing a

IsRepr SymbolRepr Source # 
Instance details

Defined in Data.Parameterized.WithRepr

Methods

withRepr :: forall (a :: k) r. SymbolRepr a -> (KnownRepr SymbolRepr a => r) -> r Source #

KnownSymbol n => Reifies (n :: Symbol) String 
Instance details

Defined in Data.Reflection

Methods

reflect :: proxy n -> String #

KnownSymbol s => KnownRepr SymbolRepr (s :: Symbol) Source # 
Instance details

Defined in Data.Parameterized.SymbolRepr

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

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