pringletons-0.1.0.0: Classes and data structures complementing the singletons library

Safe HaskellNone
LanguageHaskell2010

Data.Singletons.Class

Contents

Synopsis

Singleton Classes

These are singleton variants of the commonly used classes from base, hashable, and aeson. These variants work on higher-kinded types instead of on ground types. For example, if you wrote the following:

data MyType = MyInt | MyBool | MyChar
$(genSingletons [''MyType])
type family Interpret m where
  Interpret 'MyInt  = Int
  Interpret 'MyChar = Char
  Interpret 'MyBool = Bool
newtype MyValue x = MyValue { getMyValue :: Interpret x }

You could then write MyValue instances for all of the classes that in this module that end in Sing1. For example:

instance EqSing1 MyValue where
  eqSing1 x a b = case x of
    SMyInt  -> a == b
    SMyChar -> a == b
    SMyBool -> a == b

For our example MyValue type, the EqSing1 instance is trivial. We simply pattern match on the singleton and then do the same thing in each case. This kind of pattern matching ends up happening any time our universe interpreter maps to types that all have Eq instances. Since writing this out is tedious, we can instead use a template haskell function provided in the Data.Case.Enumerate module:

instance EqSing1 MyValue where
  eqSing1 x a b $(enumerateConstructors 'x ''MyValue =<< [|a == b|])

Instances for the other classes here can be written similarly.

class EqSing1 f where Source

Methods

eqSing1 :: Sing a -> f a -> f a -> Bool Source

Instances

class EqSing2 f where Source

Methods

eqSing2 :: Sing a -> Sing b -> f a b -> f a b -> Bool Source

class EqSing1 f => OrdSing1 f where Source

Methods

compareSing1 :: Sing a -> f a -> f a -> Ordering Source

class EqSing2 f => OrdSing2 f where Source

Methods

compareSing2 :: Sing a -> Sing b -> f a b -> f a b -> Ordering Source

class HashableSing1 f where Source

Methods

hashWithSaltSing1 :: Sing a -> Int -> f a -> Int Source

Instances

class HashableSing2 f where Source

Methods

hashWithSaltSing2 :: Sing a -> Sing b -> Int -> f a b -> Int Source

class ToJSONSing1 f where Source

Methods

toJSONSing1 :: Sing a -> f a -> Value Source

Instances

class ToJSONSing2 f where Source

Methods

toJSONSing2 :: Sing a -> Sing b -> f a b -> Value Source

class FromJSONSing1 f where Source

Methods

parseJSONSing1 :: Sing a -> Value -> Parser (f a) Source

Instances

class FromJSONSing2 f where Source

Methods

parseJSONSing2 :: Sing a -> Sing b -> Value -> Parser (f a b) Source

Kind classes

These are kind classes. They express that something is true for all singletons of a particular kind. Note that these are different from the kind classes provided in the singletons library itself. The methods in those classes (SOrd,SEnum,etc.) work entirely on singletons. Here, the methods also work with normal data types.

Notice that classes like EqKind and OrdKind have been omitted from this library. The reason is that that functions that would be provided by these can be trivially recovered by demoting the results of methods in SEq and SOrd.

These methods in these classes all have defaults that involve demoting the singleton and using the corresponding method from the normal typeclass.

class (kproxy ~ KProxy) => ShowKind kproxy where Source

Minimal complete definition

Nothing

Methods

showsPrecKind :: Int -> Sing (x :: a) -> ShowS Source

class (kproxy ~ KProxy) => ReadKind kproxy where Source

Minimal complete definition

Nothing

Methods

readsPrecKind :: Int -> ReadS (SomeSing kproxy) Source

class (kproxy ~ KProxy) => HashableKind kproxy where Source

Minimal complete definition

Nothing

Methods

hashWithSaltKind :: Int -> Sing (x :: a) -> Int Source

class (kproxy ~ KProxy) => ToJSONKind kproxy where Source

Minimal complete definition

Nothing

Methods

toJSONKind :: Sing (x :: a) -> Value Source

class (kproxy ~ KProxy) => FromJSONKind kproxy where Source

Methods

parseJSONKind :: Value -> Parser (SomeSing kproxy) Source

class (kproxy ~ KProxy) => ToJSONKeyKind kproxy where Source

Minimal complete definition

Nothing

Methods

toJSONKeyKind :: Sing (x :: a) -> Text Source

class (kproxy ~ KProxy) => FromJSONKeyKind kproxy where Source

Minimal complete definition

Nothing

Data types

newtype Applied1 f a Source

Constructors

Applied1 

Fields

getApplied1 :: Apply f a
 

newtype Applied2 f a b Source

Constructors

Applied2 

Fields

getApplied2 :: Apply (Apply f a) b
 

newtype Applied3 f a b c Source

Constructors

Applied3 

Fields

getApplied3 :: Apply (Apply (Apply f a) b) c
 

data SomeSingWith1 kproxy f where Source

Constructors

SomeSingWith1 :: Sing a -> f a -> SomeSingWith1 KProxy f 

Instances

(EqSing1 k f, SDecide k kproxy) => Eq (SomeSingWith1 k kproxy f) Source 
(HashableKind k kproxy1, HashableSing1 k f) => Hashable (SomeSingWith1 k kproxy1 f) Source 

data SomeSingWith2 kproxy1 kproxy2 f where Source

Constructors

SomeSingWith2 :: Sing a -> Sing b -> f a b -> SomeSingWith2 KProxy KProxy f 

Instances

(ToJSONKind k kproxy1, ToJSONKind k1 kproxy2, ToJSONSing2 k k1 f) => ToJSON (SomeSingWith2 k k kproxy1 kproxy2 f) Source 
FromJSON (SomeSingWith2 k k kproxy1 kproxy2 f) Source 

Classes for Applied

These are additional classes used to provide instances for Applied1. If you have a defunctionalized typeclass that provides produces types in the category hask, you can use this. Instances will often look like this:

data Thing = ...
type family ToType (x :: Thing) :: * where ...
instance EqApplied1 ToTypeSym0 where
  eqApplied1 _ x (Applied a) (Applied b) = $(enumerateConstructors 'x ''Thing =<< [|a == b|])

class EqApplied1 f where Source

Methods

eqApplied1 :: proxy f -> Sing a -> Apply f a -> Apply f a -> Bool Source

class HashableApplied1 f where Source

Methods

hashWithSaltApplied1 :: proxy f -> Sing a -> Int -> Apply f a -> Int Source

class ToJSONApplied1 f where Source

Methods

toJSONApplied1 :: proxy f -> Sing a -> Apply f a -> Value Source

class FromJSONApplied1 f where Source

Methods

parseJSONApplied1 :: proxy f -> Sing a -> Value -> Parser (Apply f a) Source

Functions

showKind :: forall kproxy a. ShowKind kproxy => Sing a -> String Source