ghc-symbol-0: Symbol on term level
Safe HaskellTrustworthy
LanguageHaskell2010

GHC.Symbol

Description

A (slightly unsafe) term level implementation for Symbol.

As Symbol in base doesn't have any term-level operations, it's sometimes necessary to have two copies of the same data, the first one using String on term level and second one using Symbol to be promtoed to type level.

In GHC-9.2 the similar problem was fixed for Nat and Natural, which were distinct types (kinds) before that.

As String is a list of Chars, we cannot make type Symbol = String, but we could do newtype Symbol = MkSymbol String. This module fakes that by using unsafeCoerce under the hood.

Fleshing out Symbol on term level is suggested in https://gitlab.haskell.org/ghc/ghc/-/issues/10776#note_109601 in 2015.

This implementation is slightly unsafe, as currently Symbol is defined as empty data type:

data Symbol

This means that you can write

dangerous :: Symbol -> Int
dangerous x = case x of

and because GHC sees through everything, and knows that Symbol is empty, the above compiles without a warning.

If Symbol was defined as newtype Symbol = Symbol Any, the above problem would go away, and also implementation of this module would be safer, as unsafeCoerceing from lifted type to Any and back is guaranteed to work.

Of course life would be easier if we just had

newtype Symbol = MkSymbol String

but until that is done, you may find this module useful.

Note: Symbol is not Text. Text has an invariant: it represents valid Unicode text. Symbol is just a list of characters (= Unicode codepoints), like String. E.g.

>>> "\55555" :: String
"\55555"
>>> "\55555" :: Symbol
"\55555"

but text replaces surrogate codepoints:

>>> "\55555" :: Text
"\65533"

Symbol could use some packed representation of list of characters, if also KnownSymbol would use it as well. Currently KnownSymbol dictionary carries a String, so having Symbol be a String is justified'.

Synopsis

Symbol type

data Symbol #

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

Instances

Instances details
IsList Symbol Source # 
Instance details

Defined in GHC.Symbol

Associated Types

type Item Symbol #

Eq Symbol Source # 
Instance details

Defined in GHC.Symbol

Methods

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

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

Ord Symbol Source # 
Instance details

Defined in GHC.Symbol

Read Symbol Source # 
Instance details

Defined in GHC.Symbol

Show Symbol Source #
>>> "foo" :: Symbol
"foo"
Instance details

Defined in GHC.Symbol

IsString Symbol Source #
>>> "foo" :: Symbol
"foo"
Instance details

Defined in GHC.Symbol

Methods

fromString :: String -> Symbol #

Semigroup Symbol Source # 
Instance details

Defined in GHC.Symbol

Monoid Symbol Source # 
Instance details

Defined in GHC.Symbol

PrintfArg Symbol Source # 
Instance details

Defined in GHC.Symbol

Binary Symbol Source # 
Instance details

Defined in GHC.Symbol

Methods

put :: Symbol -> Put #

get :: Get Symbol #

putList :: [Symbol] -> Put #

NFData Symbol Source # 
Instance details

Defined in GHC.Symbol

Methods

rnf :: Symbol -> () #

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

Lift Symbol Source # 
Instance details

Defined in GHC.Symbol

Methods

lift :: Symbol -> Q Exp #

liftTyped :: Symbol -> Q (TExp Symbol) #

KnownSymbol a => SingI (a :: Symbol)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

sing :: Sing a

type Item Symbol Source # 
Instance details

Defined in GHC.Symbol

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

consSymbol :: Char -> Symbol -> Symbol Source #

Prepend a character to a Symbol

>>> consSymbol 'a' "cute"
"acute"

unconsSymbol :: Symbol -> Maybe (Char, Symbol) Source #

Inverse of consSymbol

>>> unconsSymbol ""
Nothing
>>> unconsSymbol "mother"
Just ('m',"other")

Type level

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

symbolVal :: forall n proxy. KnownSymbol n => proxy n -> Symbol Source #

>>> symbolVal (Proxy @"foobar")
"foobar"

symbolVal' :: forall n. KnownSymbol n => Proxy# n -> Symbol Source #

type family AppendSymbol (a :: Symbol) (b :: Symbol) :: Symbol where ... #

Concatenation of type-level symbols.

Since: base-4.10.0.0

type family CmpSymbol (a :: Symbol) (b :: Symbol) :: Ordering where ... #

Comparison of type-level symbols, as a function.

Since: base-4.7.0.0

someSymbolVal :: Symbol -> SomeSymbol Source #

>>> someSymbolVal "foobar"
"foobar"

data SomeSymbol #

This type represents unknown type-level symbols.

Constructors

KnownSymbol n => SomeSymbol (Proxy n)

Since: base-4.7.0.0

Instances

Instances details
Eq SomeSymbol

Since: base-4.7.0.0

Instance details

Defined in GHC.TypeLits

Ord SomeSymbol

Since: base-4.7.0.0

Instance details

Defined in GHC.TypeLits

Read SomeSymbol

Since: base-4.7.0.0

Instance details

Defined in GHC.TypeLits

Show SomeSymbol

Since: base-4.7.0.0

Instance details

Defined in GHC.TypeLits

sameSymbol :: forall (a :: Symbol) (b :: Symbol). (KnownSymbol a, KnownSymbol b) => Proxy a -> Proxy b -> Maybe (a :~: b) #

We either get evidence that this function was instantiated with the same type-level symbols, or Nothing.

Since: base-4.7.0.0

Orphan instances

IsList Symbol Source # 
Instance details

Associated Types

type Item Symbol #

Eq Symbol Source # 
Instance details

Methods

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

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

Ord Symbol Source # 
Instance details

Read Symbol Source # 
Instance details

Show Symbol Source #
>>> "foo" :: Symbol
"foo"
Instance details

IsString Symbol Source #
>>> "foo" :: Symbol
"foo"
Instance details

Methods

fromString :: String -> Symbol #

Semigroup Symbol Source # 
Instance details

Monoid Symbol Source # 
Instance details

PrintfArg Symbol Source # 
Instance details

Binary Symbol Source # 
Instance details

Methods

put :: Symbol -> Put #

get :: Get Symbol #

putList :: [Symbol] -> Put #

NFData Symbol Source # 
Instance details

Methods

rnf :: Symbol -> () #

Lift Symbol Source # 
Instance details

Methods

lift :: Symbol -> Q Exp #

liftTyped :: Symbol -> Q (TExp Symbol) #