type-combinators-singletons-0.1.0.0: Interop between /type-combinators/ and /singletons/.

Copyright(c) Justin Le 2017
LicenseBSD-3
Maintainerjustin@jle.im
Stabilityunstable
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Data.Type.Combinator.Singletons

Contents

Description

There's a lot of identical data types between type-combinators and singetons, as well as similar typeclasses. This module provides conversion functions between the two, and also many appropriate instances.

Synopsis

Documentation

prodSing :: Prod Sing as -> Sing as Source #

Convert a Prod of Sings of individual values in as to a Sing for all as together.

singProd :: Sing as -> Prod Sing as Source #

Convert a Sing for as to a Prod of Sings of each individual value in as.

singLength :: Sing as -> Length as Source #

Convert a Sing for as into a Length representing the length of as.

Length as is equivalent to Prod Proxy as, so this is basically

singLength = map1 (const Proxy) . singProd

boolSing :: Boolean b -> Sing b Source #

Convert a Boolean singleton for a into the Sing singleton for a.

singBool :: Sing b -> Boolean b Source #

Convert a Sing singleton for b to a Boolean singleton for b.

data family Sing k (a :: k) :: * #

The singleton kind-indexed data family.

Instances

data Sing Bool 
data Sing Bool where
data Sing Ordering 
data Sing Nat 
data Sing Nat where
data Sing Symbol 
data Sing Symbol where
data Sing () 
data Sing () where
data Sing N # 
data Sing N where
type KnownC k (Sing k) a # 
type KnownC k (Sing k) a = SingI k a
type WitnessC ØC (SingI k a) (Sing k a) # 
type WitnessC ØC (SingI k a) (Sing k a) = ØC
data Sing [a0] 
data Sing [a0] where
data Sing (Maybe a0) 
data Sing (Maybe a0) where
data Sing (NonEmpty a0) 
data Sing (NonEmpty a0) where
data Sing (Either a0 b0) 
data Sing (Either a0 b0) where
data Sing (a0, b0) 
data Sing (a0, b0) where
data Sing ((~>) k1 k2) 
data Sing ((~>) k1 k2) = SLambda {}
data Sing (a0, b0, c0) 
data Sing (a0, b0, c0) where
data Sing (a0, b0, c0, d0) 
data Sing (a0, b0, c0, d0) where
data Sing (a0, b0, c0, d0, e0) 
data Sing (a0, b0, c0, d0, e0) where
data Sing (a0, b0, c0, d0, e0, f0) 
data Sing (a0, b0, c0, d0, e0, f0) where
data Sing (a0, b0, c0, d0, e0, f0, g0) 
data Sing (a0, b0, c0, d0, e0, f0, g0) where

type SN = (Sing :: N -> Type) Source #

type ZSym0 = Z Source #

data SSym0 l Source #

Instances

type SSym1 t = S t Source #

natSing :: Nat n -> Sing n Source #

Convert a Nat singleton for n to a Sing singleton for n.

singNat :: Sing n -> Nat n Source #

Convert a Sing singleton for n to a Nat singleton for n.

parSing :: (Sing :*: Sing) '(a, b) -> Sing '(a, b) Source #

Convert a :*: tupling of Sing a and Sing b into a single Sing for '(a, b).

singPar :: Sing '(a, b) -> (Sing :*: Sing) '(a, b) Source #

Convert a Sing of '(a, b) to a :*: tupling of Sing a and Sing b.

choiceSing :: (Sing :+: Sing) e -> Sing e Source #

Convert a :+: sum between a Sing a and Sing b into a Sing of a sum (Either) of a and b.

singChoice :: Sing e -> (Sing :+: Sing) e Source #

Convert a Sing of a sum (Either) of a and b to a :+: sum between Sing a and Sing b.

optionSing :: Option Sing a -> Sing a Source #

Convert an Option of Sing a to a Sing of an optional (Maybe) a.

singOption :: Sing a -> Option Sing a Source #

Convert a Sing of an optional (Maybe) a to an Option of Sing a.

Orphan instances

SingKind N Source # 

Associated Types

type DemoteRep N :: * #

SingI N Z Source # 

Methods

sing :: Sing Z a #

SingI N n0 => SingI N (S n0) Source # 

Methods

sing :: Sing (S n0) a #

SEq k2 => Eq1 k2 (Sing k2) Source # 

Methods

eq1 :: f a -> f a -> Bool #

neq1 :: f a -> f a -> Bool #

SOrd k2 => Ord1 k2 (Sing k2) Source # 

Methods

compare1 :: f a -> f a -> Ordering #

(<#) :: f a -> f a -> Bool #

(>#) :: f a -> f a -> Bool #

(<=#) :: f a -> f a -> Bool #

(>=#) :: f a -> f a -> Bool #

SingI k a => Known k (Sing k) a Source # 

Associated Types

type KnownC (Sing k) (a :: Sing k -> *) (a :: Sing k) :: Constraint #

Methods

known :: a a #

Witness ØC (SingI k a) (Sing k a) Source # 

Associated Types

type WitnessC (ØC :: Constraint) (SingI k a :: Constraint) (Sing k a) :: Constraint #

Methods

(\\) :: ØC => (SingI k a -> r) -> Sing k a -> r #