Safe Haskell | None |
---|---|
Language | Haskell2010 |
The goal of the singlethongs library is to offer the bare minimum of what the singletons library offers in a small package that's easy to compile across different GHC versions, including GHCJS.
This module exports a minimal reproduction of what
the singletons package offers.
Namely Sing
, SingI
, SomeSing
and SingKind
, as well as TemplateHaskell
support for generating the relevant instances for custom types. If there is
some feature that you thing could be added to this library,
please suggest it.
The types exported by this module are not the same types as the types as the one exported by the singletons package. Even if they have the same names and implementation, they are not seen as equal by the type-checker. They are only intended to be a drop-in replacement.
Synopsis
- data family Sing (a :: k)
- class SingI (a :: k) where
- data SomeSing k where
- withSomeSing :: SingKind k => Demote k -> (forall (a :: k). Sing a -> r) -> r
- class SingKind k where
- singlethongs :: Name -> Q [Dec]
- class TestEquality (f :: k -> Type) where
- testEquality :: forall (a :: k) (b :: k). f a -> f b -> Maybe (a :~: b)
- data (a :: k) :~: (b :: k) where
Documentation
Template Haskell
singlethongs :: Name -> Q [Dec] Source #
Generate Sing
, SingI
, SingKind
and TestEquality
instances for a
datatype.
Given a datatype like Foo
below, having one or more unary constructors:
data Foo = Bar | Qux
singlethongs
''Foo
The following code will be generated:
data instanceSing
(x :: Foo) where SBar ::Sing
'Bar SQux ::Sing
'Qux instanceSingKind
Fobo where typeDemote
Foo = FoofromSing
SBar = BarfromSing
SQux = QuxtoSing
Bar =SomeSing
SBartoSing
Qux =SomeSing
SQux instanceSingI
'Bar wheresing
= SBar instanceSingI
'Qux wheresing
= SQux instanceTestEquality
(Sing
:: Foo -> *) wheretestEquality
SBar SBar =Just
Refl
testEquality
SQux SQux =Just
Refl
testEquality
_ _ =Nothing
In order to use this singlethongs
function, you will need to enable the
following GHC extensions:
{-# LANGUAGE DataKinds, GADTs, KindSignatures, TemplateHaskell, TypeFamilies #-}
Re-exports
class TestEquality (f :: k -> Type) where #
This class contains types where you can learn the equality of two types from information contained in terms. Typically, only singleton types should inhabit this class.
testEquality :: forall (a :: k) (b :: k). f a -> f b -> Maybe (a :~: b) #
Conditionally prove the equality of a
and b
.
Instances
TestEquality ((:~:) a :: k -> Type) | Since: base-4.7.0.0 |
Defined in Data.Type.Equality | |
TestEquality ((:~~:) a :: k -> Type) | Since: base-4.10.0.0 |
Defined in Data.Type.Equality |
data (a :: k) :~: (b :: k) where infix 4 #
Propositional equality. If a :~: b
is inhabited by some terminating
value, then the type a
is the same as the type b
. To use this equality
in practice, pattern-match on the a :~: b
to get out the Refl
constructor;
in the body of the pattern-match, the compiler knows that a ~ b
.
Since: base-4.7.0.0
Instances
TestEquality ((:~:) a :: k -> Type) | Since: base-4.7.0.0 |
Defined in Data.Type.Equality | |
a ~ b => Bounded (a :~: b) | Since: base-4.7.0.0 |
a ~ b => Enum (a :~: b) | Since: base-4.7.0.0 |
Defined in Data.Type.Equality | |
Eq (a :~: b) | Since: base-4.7.0.0 |
Ord (a :~: b) | Since: base-4.7.0.0 |
Defined in Data.Type.Equality | |
a ~ b => Read (a :~: b) | Since: base-4.7.0.0 |
Show (a :~: b) | Since: base-4.7.0.0 |