Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Exinst is a library providing you with tools to recover type-indexed types whose type-indexes have been existentialized, as well as automatically deriving instances for them, as long as said type indexes are singleton types (see singleton).
In short, what exinst
currently gives you is: For any type t :: k -> *
, if
k
is a singleton type and c (t a) ::
is satisfied, then you can
existentialize away the Constraint
a
parameter with
, recover it later, and
have Some1
tc (
automatically satisfied. Currently, up to 4 type indexes
can be existentialized using Some1
t)Some1
, Some2
, Some3
and Some4
respectively.
NOTE: This tutorial asumes some familiarity with singleton types as implemented
by the singleton library.
A singleton type is, in very rough terms, a type inhabited by a single term,
which allows one to go from its term-level representation to its type-level
representation and back without much trouble. A bit like the term ()
, which
is of type ()
. Whenever you have the type ()
you know what that its
term-level representation must be ()
, and whenever you have the term ()
you know that its type must be ()
.
Synopsis
- data Some1 (f1 :: k1 -> Type) = forall a1. Some1 !(Sing a1) !(f1 a1)
- some1 :: forall k1 (f1 :: k1 -> Type) a1. SingI a1 => f1 a1 -> Some1 f1
- fromSome1 :: forall k1 (f1 :: k1 -> Type) a1. (SingI a1, SDecide k1) => Some1 f1 -> Maybe (f1 a1)
- _Some1 :: forall k1 (f1 :: k1 -> Type) a1. (SingI a1, SDecide k1) => Prism' (Some1 f1) (f1 a1)
- withSome1 :: forall k1 (f1 :: k1 -> Type) (r :: Type). Some1 f1 -> (forall a1. SingI a1 => f1 a1 -> r) -> r
- withSome1Sing :: forall k1 (f1 :: k1 -> Type) (r :: Type). Some1 f1 -> (forall a1. SingI a1 => Sing a1 -> f1 a1 -> r) -> r
- some1SingRep :: SingKind k1 => Some1 (f1 :: k1 -> Type) -> Demote k1
- same1 :: forall k1 f g x. SDecide k1 => (forall a1. SingI a1 => f a1 -> g a1 -> x) -> Some1 (f :: k1 -> Type) -> Some1 (g :: k1 -> Type) -> Maybe x
- class Dict1 (c :: k0 -> Constraint) (f1 :: k1 -> k0) where
- data Some2 (f2 :: k2 -> k1 -> Type) = forall a2 a1. Some2 !(Sing a2) !(Sing a1) !(f2 a2 a1)
- some2 :: forall k2 k1 (f2 :: k2 -> k1 -> Type) a2 a1. (SingI a2, SingI a1) => f2 a2 a1 -> Some2 f2
- fromSome2 :: forall k2 k1 (f2 :: k2 -> k1 -> Type) a2 a1. (SingI a2, SDecide k2, SingI a1, SDecide k1) => Some2 f2 -> Maybe (f2 a2 a1)
- _Some2 :: forall k2 k1 (f2 :: k2 -> k1 -> Type) a2 a1. (SingI a2, SDecide k2, SingI a1, SDecide k1) => Prism' (Some2 f2) (f2 a2 a1)
- withSome2 :: forall k2 k1 (f2 :: k2 -> k1 -> Type) (r :: Type). Some2 f2 -> (forall a2 a1. (SingI a2, SingI a1) => f2 a2 a1 -> r) -> r
- withSome2Sing :: forall k2 k1 (f2 :: k2 -> k1 -> Type) (r :: Type). Some2 f2 -> (forall a2 a1. (SingI a2, SingI a1) => Sing a2 -> Sing a1 -> f2 a2 a1 -> r) -> r
- some2SingRep :: (SingKind k2, SingKind k1) => Some2 (f2 :: k2 -> k1 -> Type) -> (Demote k2, Demote k1)
- same2 :: forall k2 k1 f g x. (SDecide k2, SDecide k1) => (forall a2 a1. SingI a1 => f a2 a1 -> g a2 a1 -> x) -> Some2 (f :: k2 -> k1 -> Type) -> Some2 (g :: k2 -> k1 -> Type) -> Maybe x
- class Dict2 (c :: k0 -> Constraint) (f2 :: k2 -> k1 -> k0) where
- data Some3 (f3 :: k3 -> k2 -> k1 -> Type) = forall a3 a2 a1. Some3 !(Sing a3) !(Sing a2) !(Sing a1) !(f3 a3 a2 a1)
- some3 :: forall k3 k2 k1 (f3 :: k3 -> k2 -> k1 -> Type) a3 a2 a1. (SingI a3, SingI a2, SingI a1) => f3 a3 a2 a1 -> Some3 f3
- fromSome3 :: forall k3 k2 k1 (f3 :: k3 -> k2 -> k1 -> Type) a3 a2 a1. (SingI a3, SDecide k3, SingI a2, SDecide k2, SingI a1, SDecide k1) => Some3 f3 -> Maybe (f3 a3 a2 a1)
- _Some3 :: forall k3 k2 k1 (f3 :: k3 -> k2 -> k1 -> Type) a3 a2 a1. (SingI a3, SDecide k3, SingI a2, SDecide k2, SingI a1, SDecide k1) => Prism' (Some3 f3) (f3 a3 a2 a1)
- withSome3 :: forall k3 k2 k1 (f3 :: k3 -> k2 -> k1 -> Type) (r :: Type). Some3 f3 -> (forall a3 a2 a1. (SingI a3, SingI a2, SingI a1) => f3 a3 a2 a1 -> r) -> r
- withSome3Sing :: forall k3 k2 k1 (f3 :: k3 -> k2 -> k1 -> Type) (r :: Type). Some3 f3 -> (forall a3 a2 a1. (SingI a3, SingI a2, SingI a1) => Sing a3 -> Sing a2 -> Sing a1 -> f3 a3 a2 a1 -> r) -> r
- some3SingRep :: (SingKind k3, SingKind k2, SingKind k1) => Some3 (f3 :: k3 -> k2 -> k1 -> Type) -> (Demote k3, Demote k2, Demote k1)
- same3 :: forall k3 k2 k1 f g x. (SDecide k3, SDecide k2, SDecide k1) => (forall a3 a2 a1. (SingI a3, SingI a2, SingI a1) => f a3 a2 a1 -> g a3 a2 a1 -> x) -> Some3 (f :: k3 -> k2 -> k1 -> Type) -> Some3 (g :: k3 -> k2 -> k1 -> Type) -> Maybe x
- class Dict3 (c :: k0 -> Constraint) (f3 :: k3 -> k2 -> k1 -> k0) where
- data Some4 (f4 :: k4 -> k3 -> k2 -> k1 -> Type) = forall a4 a3 a2 a1. Some4 !(Sing a4) !(Sing a3) !(Sing a2) !(Sing a1) !(f4 a4 a3 a2 a1)
- some4 :: forall k4 k3 k2 k1 (f4 :: k4 -> k3 -> k2 -> k1 -> Type) a4 a3 a2 a1. (SingI a4, SingI a3, SingI a2, SingI a1) => f4 a4 a3 a2 a1 -> Some4 f4
- fromSome4 :: forall k4 k3 k2 k1 (f4 :: k4 -> k3 -> k2 -> k1 -> Type) a4 a3 a2 a1. (SingI a4, SDecide k4, SingI a3, SDecide k3, SingI a2, SDecide k2, SingI a1, SDecide k1) => Some4 f4 -> Maybe (f4 a4 a3 a2 a1)
- _Some4 :: forall k4 k3 k2 k1 (f4 :: k4 -> k3 -> k2 -> k1 -> Type) a4 a3 a2 a1. (SingI a4, SDecide k4, SingI a3, SDecide k3, SingI a2, SDecide k2, SingI a1, SDecide k1) => Prism' (Some4 f4) (f4 a4 a3 a2 a1)
- withSome4 :: forall k4 k3 k2 k1 (f4 :: k4 -> k3 -> k2 -> k1 -> Type) (r :: Type). Some4 f4 -> (forall a4 a3 a2 a1. (SingI a4, SingI a3, SingI a2, SingI a1) => f4 a4 a3 a2 a1 -> r) -> r
- withSome4Sing :: forall k4 k3 k2 k1 (f4 :: k4 -> k3 -> k2 -> k1 -> Type) (r :: Type). Some4 f4 -> (forall a4 a3 a2 a1. (SingI a4, SingI a3, SingI a2, SingI a1) => Sing a4 -> Sing a3 -> Sing a2 -> Sing a1 -> f4 a4 a3 a2 a1 -> r) -> r
- some4SingRep :: (SingKind k4, SingKind k3, SingKind k2, SingKind k1) => Some4 (f4 :: k4 -> k3 -> k2 -> k1 -> Type) -> (Demote k4, Demote k3, Demote k2, Demote k1)
- same4 :: forall k4 k3 k2 k1 f g x. (SDecide k4, SDecide k3, SDecide k2, SDecide k1) => (forall a4 a3 a2 a1. (SingI a4, SingI a3, SingI a2, SingI a1) => f a4 a3 a2 a1 -> g a4 a3 a2 a1 -> x) -> Some4 (f :: k4 -> k3 -> k2 -> k1 -> Type) -> Some4 (g :: k4 -> k3 -> k2 -> k1 -> Type) -> Maybe x
- class Dict4 (c :: k0 -> Constraint) (f4 :: k4 -> k3 -> k2 -> k1 -> k0) where
- class Dict0 (c :: k0 -> Constraint) where
- data P1 l r (a1 :: k1) = P1 (l a1) (r a1)
- data P2 l r (a2 :: k2) (a1 :: k1) = P2 (l a2 a1) (r a2 a1)
- data P3 l r (a3 :: k3) (a2 :: k2) (a1 :: k1) = P3 (l a3 a2 a1) (r a3 a2 a1)
- data P4 l r (a4 :: k4) (a3 :: k3) (a2 :: k2) (a1 :: k1) = P4 (l a4 a3 a2 a1) (r a4 a3 a2 a1)
- data S1 l r (a1 :: k1)
- data S2 l r (a2 :: k2) (a1 :: k1)
- data S3 l r (a3 :: k3) (a2 :: k2) (a1 :: k1)
- data S4 l r (a4 :: k4) (a3 :: k3) (a2 :: k2) (a1 :: k1)
- data Constraint
- data Dict a where
- type family Sing :: k -> Type
- class SingI (a :: k)
Tutorial
As a motivation, let's consider the following example:
{-# LANGUAGE GADTs #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE StandaloneDeriving #-}
data Size = Big | Small
data Receptacle (a :: Size) :: * where
Vase :: Receptacle 'Small
Glass :: Receptacle 'Small
Barrel :: Receptacle 'Big
deriving instance Show
(Receptacle a)
Receptacle
can describe three types of receptacles (Vase
, Glass
and
Barrel
), while at the same time being able to indicate, at the type level,
whether the size of the receptacle is Big
or Small
. Additionally, we've
provided Show
instances for Receptacle
.
Now, if we want to put Receptacle
s in a container, for example in []
, we can
do so only as long as the Receptacle
type is fully applied and monomorphic.
That is, we can have [Receptacle 'Small]
and [Receptacle 'Big]
, but we
can't have [Receptacle]
nor [forall a. Receptacle a]
. So, if we want to
have Receptacle
s of different sizes in a container like []
, we need a
different solution.
At this point we need to ask ourselves why we need to put Receptacle
s of
different sizes in a same container. If the answer is something like “because we
want to show all of them, no matter what size they are”, then we should realize
that what we are actually asking for is that no matter what Size
our
Receptable
has, we need to be able to find a Show
instance for that
Receptacle
. In Haskell, we can express just that using existential types
and constraints hidden behind a data constructor.
-- We need to add these language extensions to the ones in the previous example
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE FlexibleContexts #-}
data ReceptacleOfAnySizeThatCanBeShown
= forall a. (Show
(Receptacle a))
=> MkReceptacleOfAnySizeThatCanBeShown (Receptacle a)
We can construct values of type ReceptacleOfAnySizeThatCanBeShown
only as long
as there exist a Show
instance for the Receptacle a
we give to the
MkReceptacleOfAnySizeThatCanBeShown
constructor. In our case, both Receptacle
'Small
and Receptacle 'Big
have Show
instances, so all of Vase
, Glass
and
Barrel
can be used successfully with MkReceptacleOfAnySizeThatCanBeShown
.
Now, ReceptacleOfAnySizeThatCanBeShown
on itself doesn't yet have a Show
instance, and we can't derive one automatically using the deriving
mechanism,
but we can give an explicit Show
instance that just forwards the work to the
Show
instance of the underlying Receptacle a
.
instanceShow
ReceptacleOfAnySizeThatCanBeShown whereshow
(MkReceptacleOfAnySizeThatCanBeShown a) =show
a
That works as intended:
>show
(MkReceptacleOfAnySizeThatCanBeShown Vase) Vase >show
(MkReceptacleOfAnySizeThatCanBeShown Barrel) Barrel
And now, as we wanted, we can put Receptacle
s of different sizes in a []
and
show them (as long as we wrap each of them as
ReceptacleOfAnySizeThatCanBeShown
, that is).
>map
show
[MkReceptacleOfAnySizeThatCanBeShown Vase, MkReceptacleOfAnySizeThatCanBeShown Barrel] [Vase, Barrel]
However, the above solution is unsatisfying for various reasons: For one, the
Show
instance for ReceptacleOfAnySizeThatCanBeShown
works only as long as
the ReceptacleOfAnySizeThatCanBeShown
itself carries a witness that the Show
constraint for Receptacle a
is satisfied, which means that if we want to write
yet another instance for ReceptacleOfAnySizeThatCanBeShown
that simply forwards
its implementation to the underlying Receptacle a
, say Eq
, then the
MkReceptacleOfAnySizeThatCanBeShown
constructor would need to be modified to witness
the Eq (Receptacle a)
instance too:
data ReceptacleOfAnySizeThatCanBeShown = forall a. (Show
(Receptacle a),Eq
(Receptacle a)) => MkReceptacleOfAnySizeThatCanBeShown (Receptacle a)
With that in place we can provide an Eq
instance for
ReceptacleOfAnySizeThatCanBeShown
as we did for Show
before, but if we pay
close attention, we can see how the implementation of
ReceptacleOfAnySizeThatCanBeShown
starts to become a bottleneck: Every
instance we want to provide for ReceptacleOfAnySizeThatCanBeShown
that simply
forwards its work to the underlying Receptacle a
needs to be witnessed by
MkReceptacleOfAnySizeThatCanBeShown
itself, it is not enough that there exists
an instance for Receptacle a
. Moreover, even the name
ReceptacleOfAnySizeThatCanBeShown
that we chose before isn't completely
accurate anymore, and will become less and less accurate as we continue adding
constraints to MkReceptacleOfAnySizeThatCanBeShown
.
Additionally, everywhere we use the MkReceptacleOfAnySizeThatCanBeShown
constructor we need to witness that the existentialized Receptacle a
satisfies
all the required constraints, which means that, if the Receptacle a
we pass to
MkReceptacleOfAnySizeThatCanBeShown
is being received, say, as a parameter to
a function, then the type of that function will also require that its caller
satisfies all of the same constraints, even though it is obvious to us,
statically, that the instances exist. We can now see how all of this becomes
unmanegeable, or at least very *boilerplatey*, as those constraints start to
propagate through our code base.
What we need is a way for instances such as the Show
instance for
ReceptacleOfAnySizeThatCanBeShown
to find the Show
instance for Receptacle
a
without it being explicitely witnessed by the
MkReceptacleOfAnySizeThatCanBeShown
constructor. That is exactly the problem
that exinst
solves: allowing existentials to find their instances. Thus,
the name of this library.
Usage
Given the code for Size
, Receptacle
and its Show
instances above, we can
achieve the same functionality as our initial ReceptacleOfAnySizeThatCanBeShown
by
existentializing the type indexes of Receptacle 'Small
and Receptacle 'Big
as
. In order to do that, we must first ensure that Some1
ReceptacleSize
and its
constructors can be used as singleton types (as supported by the singletons
library),
for which we can use some TemplateHaskell
provided by Data.Singletons.TH
:
import qualified Data.Singletons.TH Data.Singletons.TH.genSingletons [''Size]
And we'll also need a Show
instance for Size
for reasons that will become
apparent later:
deriving instance Show
Size
Now we can construct a Show1 Size
and show
achieving the same results as we
did with ReceptacleOfAnySizeThatCanBeShown
before.
Note: this code won't work yet. Keep reading.
> import Exinst (Some1
,some1
) > :tsome1
Glass :tsome1
Glass ::Some1
Receptacle >show
(some1
Glass) "Some1 Small Glass"
Well, actually, the default Show
instance for Some1
shows a bit more of
information, as it permits this string to be Read
back into a
if needed, but displaying just Some1
ReceptacleGlass
would be possible too, if
desired.
The important thing to notice in the example above is that some1
does not
require us to satisfy a
constraint, it just requires
that the type index for the type-indexed type we give it as argument is a
singleton type:Show
(Receptacle 'Small)
some1
:: forall (f1 :: k1 -> *) (a1 :: k1).SingI
a1 => f1 a1 ->Some1
f1
It is the application of show
to
which will fail to compile if
there isn't a some1
GlassShow
instance for Receptacle 'Small
, complaining that a Show
instance for
can't be found. The reason for this is that even
if Some1
ReceptableShow
instances for Some1
are derived for free, they are only derived for
where a Some1
(t :: k1 -> *)
for a specific but statically
unknown Show
(t a)a
can be found at runtime (mostly, there are other minor requirements too).
The mechanism through which instances are found at runtime relies on Dict
from
the constraints library, which
exinst
wraps in a Dict1
typeclass to be instantiated once per singleton
type.
-- The Exinst.Dict1 class classDict1
(c :: k0 ->Constraint
) (f1 :: k1 -> k0) wheredict1
::Sing
(a1 :: k1) ->Dict
(c (f1 a1))
What Dict1
says is that: for a type-indexed type f1
, given a term-level
representation of the singleton type that indexes said f1
, we can obtain a
witness that the constraint c
is satisfied by f1
applied to the singleton
type.
That class seems to be a bit too abstract, but the instances we as users need to write for it are quite silly and straightforward.
Here's an example of how to provide Show
support for
via
Some1
ReceptacleDict1
:
instance (Show
(Receptacle 'Small),Show
(Receptacle 'Big)) =>Dict1
Show
Receptacle wheredict1
= x -> case x of SSmall ->Dict
SBig ->Dict
The implementation of dict1
looks quite silly, but it has to look like that as
it is only by pattern-matching on each of the
constructors that we
learn about the type level representation of a singleton type, which we then use
to select the proper Sing
SizeShow
instance among all of those listed in the instance head.
Given this Dict1
instance, we can proceed to excecute the REPL example mentioned before
and it will work just fine.
However, that Dict1
instance is still a bit insatisfactory: If we wanted,
again, to provide Eq
support for our
type, we would need to
write yet another Some1
ReceptacleDict1
instance like the one above, but mentioning Eq
instead of Show
. We can do better.
The trick, when writing Dict1
instances such as the one above, is to leave c
and f1 :: k1 -> k0
completely polymorphic, and instead only talk concretely
about the singleton type with kind k1
. This might sound strange at first, as
c
and f1
are the only two type parameters to Dict1
. But as it often happens
when working with singleton types, we are not particularly interested in the
types involved, but in their kinds instead. So, this is the Dict1
instance
you often want to write:
instance (c (f1 'Small), c (f1 'Big)) =>Dict1
c (f1 :: Size -> k0) wheredict1
= x -> case x of SSmall ->Dict
SBig ->Dict
That instance says that for any choice of c
and f1 :: Size -> k0
, if an
instance for c (f1 a)
exists for a specific choice of a
, then, given a term
level representation for that a
and the aid of dict1
, said instance can be
looked up at runtime.
Notice that Some1
itself doesn't have any requirements about Dict1
, it's the
various instances for Some1
who rely on Dict1
. Dict1
has nothing to do
with Some1
, nor with the choice of f
nor with the choice of c
; it is only
related to the singleton type used as a type-index for f
.
The Exinst
module exports ready-made instances for Some1
, Some2
, Some3
and Some4
.
Binary
from thebinary
package.Hashable
from thehashable
package.NFData
from thedeepseq
package.Arbitrary
from theQuickCheck
package.
Furthermore, other libraries export other orphan instances for the datatypes
exported by exinst
:
- exinst-base exports
instances for
Show
,Read
,Eq
,Ord
andGeneric
from thebase
package. Depends on the largesingleton-base
package, that's why these instances are not in theexinst
package itself. - exinst-aeson exports
instances for
FromJSON
andToJSON
from theaeson
package. - exinst-bytes exports
instances for
Serial
from thebytes
package. - exinst-cereal exports
instances for
Serialize
from thecereal
package. - exinst-serialise
exports instances for
Serialise
from theserialise
package.
You are invited to read the instance heads for said instances so as to understand
what you need to provide in order to get those instances “for free”. As a rule of
thumb, most instances will require this: If you expect to have an instance for
class Y => Z a
satisfied for
, then make sure an instance
for Some1
(f :: k1 -> *)Z
is available for the DemoteRep k1
, that a
or
more general instance exists, and that the Dict1
Z (f :: k1 -> k0)Y
instance for
exists too.Some1
(f :: k1 ->
*)
Here is the full code needed to have, say, the Eq
and Show
instances
available for
:Some1
Receptacle
{-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE UndecidableInstances #-} import qualified Data.Singletons.TH import Exinst (Dict
(Dict
),Dict1
(dict1
)) data Size = Big | Small deriving (Eq
,Show
) Data.Singletons.TH.genSingletons [''Size] Data.Singletons.TH.singDecideInstances [''Size] instance (c (f 'Big), c (f 'Small)) =>Dict1
c f wheredict1
= x -> case x of SBig ->Dict
SSmall ->Dict
data Receptacle (a :: Size) :: * where Vase :: Receptacle 'Small Glass :: Receptacle 'Small Barrel :: Receptacle 'Big deriving instanceEq
(Receptacle a) deriving instanceShow
(Receptacle a)
Now,
will have Some1
ReceptacleEq
and Show
instances:
> -- TryingfromSome1
. >fromSome1
(some1
Vase) ==Just
VaseTrue
>fromSome1
(some1
Vase) ==Just
GlassFalse
>fromSome1
(some1
Vase) ==Just
BarrelFalse
> -- TryingwithSome1
>withSome1
(some1
Vase)show
Vase >withSome1
(some1
Vase) (== Vase) -- This will fail, usefromSome1
-- if you know you are expecting -- aReceptacle 'Small
> -- Trying theEq
instance. >some1
Vase ==some1
VaseTrue
>some1
Vase ==some1
GlassFalse
>some1
Vase ==some1
BarrelFalse
> -- Trying theShow
instance. >show
(some1
Vase) "Some1 Small Vase" >map
show
[some1
Vase,some1
Glass,some1
Barrel] ["Some1 Small Vase","Some1 Small Glass","Some1 Big Barrel"]
Recovering
If you have a
and you know, statically, that you need an
specific Some1
(f :: k -> *)f (a :: k)
, then you can use fromSome1
which will give you an
f (a :: k)
only if a
was the type that was existentialized by Some1
.
Using fromSome1
requires that the singleton type-index implements
SDecide
, which can be derived mechanically with
TemplateHaskell
by means of singInstance
.
If you don't know, statically, the type of f (a :: k)
, then you can use
withSome1Sing
or withSome1
to work with f (a :: k)
as long as a
never
leaves their scope (don't worry, the compiler will yell at you if you try to do
that).
Many indexes
Just like Some1
hides the last singleton type index from fully applied
type-indexed type, Some2
hides the last two type indexes, Some3
hides the
last three, and Some3
hides the last four. They can be used in the same way as
Some1
.
Like as most instances for Some1
require Dict1
instances to be present for
their singleton type-index, most instances for Some2
, Some3
and Some4
will
require that Dict2
, Dict3
or Dict4
instances exist, respectively. Writing
these instances is very straightforward. Supposing you have a type X :: T4 ->
T3 -> T2 -> T1 -> *
and want to existentialize all of the four type indexes yet
be able to continue using all of its instances, we can write something like
this:
instance (c (f1 'T1a), c (f1 'T1b)) =>Dict1
c (f1 :: T1 -> k0) wheredict1
= x -> case x of { ST1a ->Dict
; ST1b ->Dict
} instance (Dict1
c (f2 'T2a),Dict1
c (f2 'T2b)) =>Dict2
c (f2 :: T2 -> k1 -> k0) wheredict2
= x -> case x of { ST2a ->dict1
; ST2b ->dict1
} instance (Dict2
c (f3 'T3a),Dict2
c (f3 'T3b)) =>Dict3
c (f3 :: T3 -> k2 -> k1 -> k0) wheredict3
= x -> case x of { ST3a ->dict2
; ST3b ->dict2
} instance (Dict3
c (f4 'T4a),Dict3
c (f4 'T4b)) =>Dict4
c (f4 :: T4 -> k3 -> k2 -> k1 -> k0) wheredict4
= x -> case x of { ST4a ->dict3
; ST4b ->dict3
}
That is, assuming the following T1
, T2
, T3
and T4
:
data T4 = T4a | T4b data T3 = T3a | T3b data T2 = T2a | T2b data T1 = T1a | T1b
Effectively, we wrote just one instance per singleton type per type-index
position, each of them promoting a term-level representation of a singleton
type to its type-level representation and forwarding the rest of the work to
a “smaller” dict. That is, dict4
reifies the type of the fourth-to-last
type-index of X
and then calls dict3
to do the same for the third-to-last
type-index of X
and so on. Notice, however, how we didn't need to mention X
in none of the instances above: As we said before, these instances are
intended to work for any choice of c
, f4
, f3
, f2
and f1
.
Writing instances
Instances for Some1
seem to come out of thin air, but the truth is that they
need to be written at least once by library authors so that, provided all its
requirements are satisfied, they are made available.
For example, when we imported Exinst before, we also brought to scope, among
other things, the Eq
instance for Some1
, which is defined as this:
instance forall (f :: k1 -> *). (SDecide
k1 ,Dict1
Eq
f ) =>Eq
(Some1
f) where (==) = \som1x som1y ->withSome1Sing
som1x $ \sa1x (x :: f a1x) ->withSome1Sing
som1y $ \sa1y (y :: f a1y) ->maybe
False
id
$ doRefl
<-testEquality
sa1x sa1y casedict1
sa1x ::Dict
(Eq
(f a1x)) ofDict
->Just
(x == y)
This code should be relatively straightforward if you are familiar with uses of
the singletons
and constraints
libraries. We are simply reifying singleton
types from their term-level representation to their type-level representation,
and afterwards using the Dict1
mechanism to lookup the required instances
during runtime. Additionaly, this instance requires that the term level
representation of the singleton type implements Show
too, as, like we saw in a
previous example, the type index itself is shown in this Show
implementation,
in the hope that it can be later recovered and reified to the type level when
using Read
.
Products and sums
Consider the following types and constructors:
data X (a ::Bool
) where XT :: X 'True
XF :: X 'False
data Y (a ::Bool
) where YT :: Y 'True
YF :: Y 'False
You can use (,)
to create a product for values of this type, and Either
to
create a sum. However, see what happens if we try to existentialize the type
index when using that approach:
> :t (some1
XT,some1
YT) (some1
XT,some1
YT) :: (Some1
X,Some1
Y) > :t (some1
XT,some1
YF) (some1
XT,some1
YF) :: (Some1
X,Some1
Y)
It works, but there is no type level guarantee that the type index taken by X
and Y
is the same. If you do want to enforce that restriction, then you can
use P1
instead:
> :tP1
P1
:: l a -> r a ->P1
l r (a :: k) > :tP1
XT YTP1
XT YT ::P1
X Y 'True
> :tP1
XT YTP1
XT YT ::P1
X Y 'True
> :tsome1
(P1
XT YT)some1
(P1
XT YT) ::Some1
(P1
X Y)
Trying to mix XT
with YF
fails, of course, since they have different type
indexes:
> :tP1
XT YF <interactive>:1:7: error: • Couldn't match type ‘'False
’ with ‘'True
’ Expected type: Y 'True
Actual type: Y 'False
• In the second argument of ‘P1
’, namely ‘YF’ In the expression:P1
XT YF
Moreover, P1
supports many common instances from base
, hashable
,
deepseq
, aeson
, bytes
, cereal
, binary
and quickcheck
out of the
box, so you can benefit from them as well.
There's also P2
, P3
and P4
for product types taking a different number of
indexes, and also S1
, S2
, S3
and S4
for sum types:
> :tS1L
S1L
:: l a ->S1
l r (a :: k) > :tS1R
S1R
:: r a ->S1
l r (a :: k) > :tS1L
XTS1L
XT ::S1
X r 'True
> :tS1R
YTS1R
YT ::S1
l Y 'True
> :tsome1
(S1L
XT)some1
(S1L
XT) ::Some1
(S1
X r) > :tsome1
(S1R
YT)some1
(S1R
YT) ::Some1
(S1
l Y)
1 type index
data Some1 (f1 :: k1 -> Type) Source #
Instances
(SingKind k1, Arbitrary (Demote k1), Dict1 Arbitrary f) => Arbitrary (Some1 f) Source # | |
(SingKind k1, Binary (Demote k1), Dict1 Binary f) => Binary (Some1 f) Source # | Compatible with the |
Dict1 NFData f => NFData (Some1 f) Source # | |
Defined in Exinst.DeepSeq | |
(SingKind k1, Hashable (Demote k1), Dict1 Hashable f, Eq (Some1 f)) => Hashable (Some1 f) Source # | |
Defined in Exinst.Hashable |
fromSome1 :: forall k1 (f1 :: k1 -> Type) a1. (SingI a1, SDecide k1) => Some1 f1 -> Maybe (f1 a1) Source #
_Some1 :: forall k1 (f1 :: k1 -> Type) a1. (SingI a1, SDecide k1) => Prism' (Some1 f1) (f1 a1) Source #
withSome1 :: forall k1 (f1 :: k1 -> Type) (r :: Type). Some1 f1 -> (forall a1. SingI a1 => f1 a1 -> r) -> r Source #
withSome1Sing :: forall k1 (f1 :: k1 -> Type) (r :: Type). Some1 f1 -> (forall a1. SingI a1 => Sing a1 -> f1 a1 -> r) -> r Source #
same1 :: forall k1 f g x. SDecide k1 => (forall a1. SingI a1 => f a1 -> g a1 -> x) -> Some1 (f :: k1 -> Type) -> Some1 (g :: k1 -> Type) -> Maybe x Source #
class Dict1 (c :: k0 -> Constraint) (f1 :: k1 -> k0) where Source #
2 type indexes
data Some2 (f2 :: k2 -> k1 -> Type) Source #
Instances
(SingKind k2, SingKind k1, Arbitrary (Demote k2), Arbitrary (Demote k1), Dict2 Arbitrary f) => Arbitrary (Some2 f) Source # | |
(SingKind k2, SingKind k1, Binary (Demote k2), Binary (Demote k1), Dict2 Binary f) => Binary (Some2 f) Source # | Compatible with the |
Dict2 NFData f => NFData (Some2 f) Source # | |
Defined in Exinst.DeepSeq | |
(SingKind k2, SingKind k1, Hashable (Demote k2), Hashable (Demote k1), Dict2 Hashable f, Eq (Some2 f)) => Hashable (Some2 f) Source # | |
Defined in Exinst.Hashable |
some2 :: forall k2 k1 (f2 :: k2 -> k1 -> Type) a2 a1. (SingI a2, SingI a1) => f2 a2 a1 -> Some2 f2 Source #
fromSome2 :: forall k2 k1 (f2 :: k2 -> k1 -> Type) a2 a1. (SingI a2, SDecide k2, SingI a1, SDecide k1) => Some2 f2 -> Maybe (f2 a2 a1) Source #
_Some2 :: forall k2 k1 (f2 :: k2 -> k1 -> Type) a2 a1. (SingI a2, SDecide k2, SingI a1, SDecide k1) => Prism' (Some2 f2) (f2 a2 a1) Source #
withSome2 :: forall k2 k1 (f2 :: k2 -> k1 -> Type) (r :: Type). Some2 f2 -> (forall a2 a1. (SingI a2, SingI a1) => f2 a2 a1 -> r) -> r Source #
withSome2Sing :: forall k2 k1 (f2 :: k2 -> k1 -> Type) (r :: Type). Some2 f2 -> (forall a2 a1. (SingI a2, SingI a1) => Sing a2 -> Sing a1 -> f2 a2 a1 -> r) -> r Source #
some2SingRep :: (SingKind k2, SingKind k1) => Some2 (f2 :: k2 -> k1 -> Type) -> (Demote k2, Demote k1) Source #
same2 :: forall k2 k1 f g x. (SDecide k2, SDecide k1) => (forall a2 a1. SingI a1 => f a2 a1 -> g a2 a1 -> x) -> Some2 (f :: k2 -> k1 -> Type) -> Some2 (g :: k2 -> k1 -> Type) -> Maybe x Source #
class Dict2 (c :: k0 -> Constraint) (f2 :: k2 -> k1 -> k0) where Source #
3 type indexes
data Some3 (f3 :: k3 -> k2 -> k1 -> Type) Source #
Instances
(SingKind k3, SingKind k2, SingKind k1, Arbitrary (Demote k3), Arbitrary (Demote k2), Arbitrary (Demote k1), Dict3 Arbitrary f) => Arbitrary (Some3 f) Source # | |
(SingKind k3, SingKind k2, SingKind k1, Binary (Demote k3), Binary (Demote k2), Binary (Demote k1), Dict3 Binary f) => Binary (Some3 f) Source # | Compatible with the |
Dict3 NFData f => NFData (Some3 f) Source # | |
Defined in Exinst.DeepSeq | |
(SingKind k3, SingKind k2, SingKind k1, Hashable (Demote k3), Hashable (Demote k2), Hashable (Demote k1), Dict3 Hashable f, Eq (Some3 f)) => Hashable (Some3 f) Source # | |
Defined in Exinst.Hashable |
some3 :: forall k3 k2 k1 (f3 :: k3 -> k2 -> k1 -> Type) a3 a2 a1. (SingI a3, SingI a2, SingI a1) => f3 a3 a2 a1 -> Some3 f3 Source #
fromSome3 :: forall k3 k2 k1 (f3 :: k3 -> k2 -> k1 -> Type) a3 a2 a1. (SingI a3, SDecide k3, SingI a2, SDecide k2, SingI a1, SDecide k1) => Some3 f3 -> Maybe (f3 a3 a2 a1) Source #
_Some3 :: forall k3 k2 k1 (f3 :: k3 -> k2 -> k1 -> Type) a3 a2 a1. (SingI a3, SDecide k3, SingI a2, SDecide k2, SingI a1, SDecide k1) => Prism' (Some3 f3) (f3 a3 a2 a1) Source #
withSome3 :: forall k3 k2 k1 (f3 :: k3 -> k2 -> k1 -> Type) (r :: Type). Some3 f3 -> (forall a3 a2 a1. (SingI a3, SingI a2, SingI a1) => f3 a3 a2 a1 -> r) -> r Source #
withSome3Sing :: forall k3 k2 k1 (f3 :: k3 -> k2 -> k1 -> Type) (r :: Type). Some3 f3 -> (forall a3 a2 a1. (SingI a3, SingI a2, SingI a1) => Sing a3 -> Sing a2 -> Sing a1 -> f3 a3 a2 a1 -> r) -> r Source #
some3SingRep :: (SingKind k3, SingKind k2, SingKind k1) => Some3 (f3 :: k3 -> k2 -> k1 -> Type) -> (Demote k3, Demote k2, Demote k1) Source #
same3 :: forall k3 k2 k1 f g x. (SDecide k3, SDecide k2, SDecide k1) => (forall a3 a2 a1. (SingI a3, SingI a2, SingI a1) => f a3 a2 a1 -> g a3 a2 a1 -> x) -> Some3 (f :: k3 -> k2 -> k1 -> Type) -> Some3 (g :: k3 -> k2 -> k1 -> Type) -> Maybe x Source #
class Dict3 (c :: k0 -> Constraint) (f3 :: k3 -> k2 -> k1 -> k0) where Source #
4 type indexes
data Some4 (f4 :: k4 -> k3 -> k2 -> k1 -> Type) Source #
Instances
(SingKind k4, SingKind k3, SingKind k2, SingKind k1, Arbitrary (Demote k4), Arbitrary (Demote k3), Arbitrary (Demote k2), Arbitrary (Demote k1), Dict4 Arbitrary f) => Arbitrary (Some4 f) Source # | |
(SingKind k4, SingKind k3, SingKind k2, SingKind k1, Binary (Demote k4), Binary (Demote k3), Binary (Demote k2), Binary (Demote k1), Dict4 Binary f) => Binary (Some4 f) Source # | Compatible with the |
Dict4 NFData f => NFData (Some4 f) Source # | |
Defined in Exinst.DeepSeq | |
(SingKind k4, SingKind k3, SingKind k2, SingKind k1, Hashable (Demote k4), Hashable (Demote k3), Hashable (Demote k2), Hashable (Demote k1), Eq (Some4 f), Dict4 Hashable f) => Hashable (Some4 f) Source # | |
Defined in Exinst.Hashable |
some4 :: forall k4 k3 k2 k1 (f4 :: k4 -> k3 -> k2 -> k1 -> Type) a4 a3 a2 a1. (SingI a4, SingI a3, SingI a2, SingI a1) => f4 a4 a3 a2 a1 -> Some4 f4 Source #
fromSome4 :: forall k4 k3 k2 k1 (f4 :: k4 -> k3 -> k2 -> k1 -> Type) a4 a3 a2 a1. (SingI a4, SDecide k4, SingI a3, SDecide k3, SingI a2, SDecide k2, SingI a1, SDecide k1) => Some4 f4 -> Maybe (f4 a4 a3 a2 a1) Source #
_Some4 :: forall k4 k3 k2 k1 (f4 :: k4 -> k3 -> k2 -> k1 -> Type) a4 a3 a2 a1. (SingI a4, SDecide k4, SingI a3, SDecide k3, SingI a2, SDecide k2, SingI a1, SDecide k1) => Prism' (Some4 f4) (f4 a4 a3 a2 a1) Source #
withSome4 :: forall k4 k3 k2 k1 (f4 :: k4 -> k3 -> k2 -> k1 -> Type) (r :: Type). Some4 f4 -> (forall a4 a3 a2 a1. (SingI a4, SingI a3, SingI a2, SingI a1) => f4 a4 a3 a2 a1 -> r) -> r Source #
withSome4Sing :: forall k4 k3 k2 k1 (f4 :: k4 -> k3 -> k2 -> k1 -> Type) (r :: Type). Some4 f4 -> (forall a4 a3 a2 a1. (SingI a4, SingI a3, SingI a2, SingI a1) => Sing a4 -> Sing a3 -> Sing a2 -> Sing a1 -> f4 a4 a3 a2 a1 -> r) -> r Source #
some4SingRep :: (SingKind k4, SingKind k3, SingKind k2, SingKind k1) => Some4 (f4 :: k4 -> k3 -> k2 -> k1 -> Type) -> (Demote k4, Demote k3, Demote k2, Demote k1) Source #
same4 :: forall k4 k3 k2 k1 f g x. (SDecide k4, SDecide k3, SDecide k2, SDecide k1) => (forall a4 a3 a2 a1. (SingI a4, SingI a3, SingI a2, SingI a1) => f a4 a3 a2 a1 -> g a4 a3 a2 a1 -> x) -> Some4 (f :: k4 -> k3 -> k2 -> k1 -> Type) -> Some4 (g :: k4 -> k3 -> k2 -> k1 -> Type) -> Maybe x Source #
class Dict4 (c :: k0 -> Constraint) (f4 :: k4 -> k3 -> k2 -> k1 -> k0) where Source #
Miscellaneous
class Dict0 (c :: k0 -> Constraint) where Source #
Products
data P1 l r (a1 :: k1) Source #
Like Product
from Data.Functor.Product, but
only intended to be used with kinds other than Type
.
This type is particularly useful when used in combination with Some1
as
, so as to ensure that Some1
(P1
l r)l
and r
are indexed
by the same type. Moreover, P1
already supports many common instances from
base
, hashable
, deepseq
, aeson
, bytes
, cereal
, binary
, and
quickcheck
out of the box, so you can benefit from them as well.
P1 (l a1) (r a1) |
Instances
(Arbitrary (l a1), Arbitrary (r a1)) => Arbitrary (P1 l r a1) Source # | |
Generic (P1 l r a1) Source # | |
(Read (l a1), Read (r a1)) => Read (P1 l r a1) Source # | |
(Show (l a1), Show (r a1)) => Show (P1 l r a1) Source # | |
(Binary (l a1), Binary (r a1)) => Binary (P1 l r a1) Source # | |
(NFData (l a1), NFData (r a1)) => NFData (P1 l r a1) Source # | |
Defined in Exinst.DeepSeq | |
(Eq (l a1), Eq (r a1)) => Eq (P1 l r a1) Source # | |
(Ord (l a1), Ord (r a1)) => Ord (P1 l r a1) Source # | |
Defined in Exinst.Internal.Product | |
(Hashable (l a1), Hashable (r a1)) => Hashable (P1 l r a1) Source # | |
Defined in Exinst.Hashable | |
type Rep (P1 l r a1) Source # | |
Defined in Exinst.Internal.Product type Rep (P1 l r a1) = D1 ('MetaData "P1" "Exinst.Internal.Product" "exinst-0.9-8vEQLIk5SDG8OqmnB34M4p" 'False) (C1 ('MetaCons "P1" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (l a1)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (r a1)))) |
data P2 l r (a2 :: k2) (a1 :: k1) Source #
Like P1
, but for l
and r
taking two type indexes.
P2 (l a2 a1) (r a2 a1) |
Instances
(Arbitrary (l a2 a1), Arbitrary (r a2 a1)) => Arbitrary (P2 l r a2 a1) Source # | |
Generic (P2 l r a2 a1) Source # | |
(Read (l a2 a1), Read (r a2 a1)) => Read (P2 l r a2 a1) Source # | |
(Show (l a2 a1), Show (r a2 a1)) => Show (P2 l r a2 a1) Source # | |
(Binary (l a2 a1), Binary (r a2 a1)) => Binary (P2 l r a2 a1) Source # | |
(NFData (l a2 a1), NFData (r a2 a1)) => NFData (P2 l r a2 a1) Source # | |
Defined in Exinst.DeepSeq | |
(Eq (l a2 a1), Eq (r a2 a1)) => Eq (P2 l r a2 a1) Source # | |
(Ord (l a2 a1), Ord (r a2 a1)) => Ord (P2 l r a2 a1) Source # | |
Defined in Exinst.Internal.Product | |
(Hashable (l a2 a1), Hashable (r a2 a1)) => Hashable (P2 l r a2 a1) Source # | |
Defined in Exinst.Hashable | |
type Rep (P2 l r a2 a1) Source # | |
Defined in Exinst.Internal.Product type Rep (P2 l r a2 a1) = D1 ('MetaData "P2" "Exinst.Internal.Product" "exinst-0.9-8vEQLIk5SDG8OqmnB34M4p" 'False) (C1 ('MetaCons "P2" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (l a2 a1)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (r a2 a1)))) |
data P3 l r (a3 :: k3) (a2 :: k2) (a1 :: k1) Source #
Like P1
, but for l
and r
taking three type indexes.
P3 (l a3 a2 a1) (r a3 a2 a1) |
Instances
(Arbitrary (l a3 a2 a1), Arbitrary (r a3 a2 a1)) => Arbitrary (P3 l r a3 a2 a1) Source # | |
Generic (P3 l r a3 a2 a1) Source # | |
(Read (l a3 a2 a1), Read (r a3 a2 a1)) => Read (P3 l r a3 a2 a1) Source # | |
(Show (l a3 a2 a1), Show (r a3 a2 a1)) => Show (P3 l r a3 a2 a1) Source # | |
(Binary (l a3 a2 a1), Binary (r a3 a2 a1)) => Binary (P3 l r a3 a2 a1) Source # | |
(NFData (l a3 a2 a1), NFData (r a3 a2 a1)) => NFData (P3 l r a3 a2 a1) Source # | |
Defined in Exinst.DeepSeq | |
(Eq (l a3 a2 a1), Eq (r a3 a2 a1)) => Eq (P3 l r a3 a2 a1) Source # | |
(Ord (l a3 a2 a1), Ord (r a3 a2 a1)) => Ord (P3 l r a3 a2 a1) Source # | |
Defined in Exinst.Internal.Product compare :: P3 l r a3 a2 a1 -> P3 l r a3 a2 a1 -> Ordering # (<) :: P3 l r a3 a2 a1 -> P3 l r a3 a2 a1 -> Bool # (<=) :: P3 l r a3 a2 a1 -> P3 l r a3 a2 a1 -> Bool # (>) :: P3 l r a3 a2 a1 -> P3 l r a3 a2 a1 -> Bool # (>=) :: P3 l r a3 a2 a1 -> P3 l r a3 a2 a1 -> Bool # max :: P3 l r a3 a2 a1 -> P3 l r a3 a2 a1 -> P3 l r a3 a2 a1 # min :: P3 l r a3 a2 a1 -> P3 l r a3 a2 a1 -> P3 l r a3 a2 a1 # | |
(Hashable (l a3 a2 a1), Hashable (r a3 a2 a1)) => Hashable (P3 l r a3 a2 a1) Source # | |
Defined in Exinst.Hashable | |
type Rep (P3 l r a3 a2 a1) Source # | |
Defined in Exinst.Internal.Product type Rep (P3 l r a3 a2 a1) = D1 ('MetaData "P3" "Exinst.Internal.Product" "exinst-0.9-8vEQLIk5SDG8OqmnB34M4p" 'False) (C1 ('MetaCons "P3" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (l a3 a2 a1)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (r a3 a2 a1)))) |
data P4 l r (a4 :: k4) (a3 :: k3) (a2 :: k2) (a1 :: k1) Source #
Like P1
, but for l
and r
taking four type indexes.
P4 (l a4 a3 a2 a1) (r a4 a3 a2 a1) |
Instances
(Arbitrary (l a4 a3 a2 a1), Arbitrary (r a4 a3 a2 a1)) => Arbitrary (P4 l r a4 a3 a2 a1) Source # | |
Generic (P4 l r a4 a3 a2 a1) Source # | |
(Read (l a4 a3 a2 a1), Read (r a4 a3 a2 a1)) => Read (P4 l r a4 a3 a2 a1) Source # | |
(Show (l a4 a3 a2 a1), Show (r a4 a3 a2 a1)) => Show (P4 l r a4 a3 a2 a1) Source # | |
(Binary (l a4 a3 a2 a1), Binary (r a4 a3 a2 a1)) => Binary (P4 l r a4 a3 a2 a1) Source # | |
(NFData (l a4 a3 a2 a1), NFData (r a4 a3 a2 a1)) => NFData (P4 l r a4 a3 a2 a1) Source # | |
Defined in Exinst.DeepSeq | |
(Eq (l a4 a3 a2 a1), Eq (r a4 a3 a2 a1)) => Eq (P4 l r a4 a3 a2 a1) Source # | |
(Ord (l a4 a3 a2 a1), Ord (r a4 a3 a2 a1)) => Ord (P4 l r a4 a3 a2 a1) Source # | |
Defined in Exinst.Internal.Product compare :: P4 l r a4 a3 a2 a1 -> P4 l r a4 a3 a2 a1 -> Ordering # (<) :: P4 l r a4 a3 a2 a1 -> P4 l r a4 a3 a2 a1 -> Bool # (<=) :: P4 l r a4 a3 a2 a1 -> P4 l r a4 a3 a2 a1 -> Bool # (>) :: P4 l r a4 a3 a2 a1 -> P4 l r a4 a3 a2 a1 -> Bool # (>=) :: P4 l r a4 a3 a2 a1 -> P4 l r a4 a3 a2 a1 -> Bool # max :: P4 l r a4 a3 a2 a1 -> P4 l r a4 a3 a2 a1 -> P4 l r a4 a3 a2 a1 # min :: P4 l r a4 a3 a2 a1 -> P4 l r a4 a3 a2 a1 -> P4 l r a4 a3 a2 a1 # | |
(Hashable (l a4 a3 a2 a1), Hashable (r a4 a3 a2 a1)) => Hashable (P4 l r a4 a3 a2 a1) Source # | |
Defined in Exinst.Hashable | |
type Rep (P4 l r a4 a3 a2 a1) Source # | |
Defined in Exinst.Internal.Product type Rep (P4 l r a4 a3 a2 a1) = D1 ('MetaData "P4" "Exinst.Internal.Product" "exinst-0.9-8vEQLIk5SDG8OqmnB34M4p" 'False) (C1 ('MetaCons "P4" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (l a4 a3 a2 a1)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (r a4 a3 a2 a1)))) |
Sums
data S1 l r (a1 :: k1) Source #
Like Sum
from Data.Functor.Sum, but
only intended to be used with kinds other than Type
.
This type is particularly useful when used in combination with Some1
as
, so as to ensure that Some1
(S1
l r)l
and r
are indexed
by the same type. Moreover, S1
already supports many common instances from
base
, hashable
, deepseq
, aeson
, bytes
, cereal
, binary
, and
quickcheck
out of the box, so you can benefit from them as well.
Instances
(Arbitrary (l a1), Arbitrary (r a1)) => Arbitrary (S1 l r a1) Source # | |
Generic (S1 l r a1) Source # | |
(Read (l a1), Read (r a1)) => Read (S1 l r a1) Source # | |
(Show (l a1), Show (r a1)) => Show (S1 l r a1) Source # | |
(Binary (l a1), Binary (r a1)) => Binary (S1 l r a1) Source # | |
(NFData (l a1), NFData (r a1)) => NFData (S1 l r a1) Source # | |
Defined in Exinst.DeepSeq | |
(Eq (l a1), Eq (r a1)) => Eq (S1 l r a1) Source # | |
(Ord (l a1), Ord (r a1)) => Ord (S1 l r a1) Source # | |
Defined in Exinst.Internal.Sum | |
(Hashable (l a1), Hashable (r a1)) => Hashable (S1 l r a1) Source # | |
Defined in Exinst.Hashable | |
type Rep (S1 l r a1) Source # | |
Defined in Exinst.Internal.Sum type Rep (S1 l r a1) = D1 ('MetaData "S1" "Exinst.Internal.Sum" "exinst-0.9-8vEQLIk5SDG8OqmnB34M4p" 'False) (C1 ('MetaCons "S1L" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (l a1))) :+: C1 ('MetaCons "S1R" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (r a1)))) |
data S2 l r (a2 :: k2) (a1 :: k1) Source #
Like S1
, but for l
and r
taking two type indexes.
Instances
(Arbitrary (l a2 a1), Arbitrary (r a2 a1)) => Arbitrary (S2 l r a2 a1) Source # | |
Generic (S2 l r a2 a1) Source # | |
(Read (l a2 a1), Read (r a2 a1)) => Read (S2 l r a2 a1) Source # | |
(Show (l a2 a1), Show (r a2 a1)) => Show (S2 l r a2 a1) Source # | |
(Binary (l a2 a1), Binary (r a2 a1)) => Binary (S2 l r a2 a1) Source # | |
(NFData (l a2 a1), NFData (r a2 a1)) => NFData (S2 l r a2 a1) Source # | |
Defined in Exinst.DeepSeq | |
(Eq (l a2 a1), Eq (r a2 a1)) => Eq (S2 l r a2 a1) Source # | |
(Ord (l a2 a1), Ord (r a2 a1)) => Ord (S2 l r a2 a1) Source # | |
Defined in Exinst.Internal.Sum | |
(Hashable (l a2 a1), Hashable (r a2 a1)) => Hashable (S2 l r a2 a1) Source # | |
Defined in Exinst.Hashable | |
type Rep (S2 l r a2 a1) Source # | |
Defined in Exinst.Internal.Sum type Rep (S2 l r a2 a1) = D1 ('MetaData "S2" "Exinst.Internal.Sum" "exinst-0.9-8vEQLIk5SDG8OqmnB34M4p" 'False) (C1 ('MetaCons "S2L" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (l a2 a1))) :+: C1 ('MetaCons "S2R" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (r a2 a1)))) |
data S3 l r (a3 :: k3) (a2 :: k2) (a1 :: k1) Source #
Like S1
, but for l
and r
taking three type indexes.
Instances
(Arbitrary (l a3 a2 a1), Arbitrary (r a3 a2 a1)) => Arbitrary (S3 l r a3 a2 a1) Source # | |
Generic (S3 l r a3 a2 a1) Source # | |
(Read (l a3 a2 a1), Read (r a3 a2 a1)) => Read (S3 l r a3 a2 a1) Source # | |
(Show (l a3 a2 a1), Show (r a3 a2 a1)) => Show (S3 l r a3 a2 a1) Source # | |
(Binary (l a3 a2 a1), Binary (r a3 a2 a1)) => Binary (S3 l r a3 a2 a1) Source # | |
(NFData (l a3 a2 a1), NFData (r a3 a2 a1)) => NFData (S3 l r a3 a2 a1) Source # | |
Defined in Exinst.DeepSeq | |
(Eq (l a3 a2 a1), Eq (r a3 a2 a1)) => Eq (S3 l r a3 a2 a1) Source # | |
(Ord (l a3 a2 a1), Ord (r a3 a2 a1)) => Ord (S3 l r a3 a2 a1) Source # | |
Defined in Exinst.Internal.Sum compare :: S3 l r a3 a2 a1 -> S3 l r a3 a2 a1 -> Ordering # (<) :: S3 l r a3 a2 a1 -> S3 l r a3 a2 a1 -> Bool # (<=) :: S3 l r a3 a2 a1 -> S3 l r a3 a2 a1 -> Bool # (>) :: S3 l r a3 a2 a1 -> S3 l r a3 a2 a1 -> Bool # (>=) :: S3 l r a3 a2 a1 -> S3 l r a3 a2 a1 -> Bool # max :: S3 l r a3 a2 a1 -> S3 l r a3 a2 a1 -> S3 l r a3 a2 a1 # min :: S3 l r a3 a2 a1 -> S3 l r a3 a2 a1 -> S3 l r a3 a2 a1 # | |
(Hashable (l a3 a2 a1), Hashable (r a3 a2 a1)) => Hashable (S3 l r a3 a2 a1) Source # | |
Defined in Exinst.Hashable | |
type Rep (S3 l r a3 a2 a1) Source # | |
Defined in Exinst.Internal.Sum type Rep (S3 l r a3 a2 a1) = D1 ('MetaData "S3" "Exinst.Internal.Sum" "exinst-0.9-8vEQLIk5SDG8OqmnB34M4p" 'False) (C1 ('MetaCons "S3L" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (l a3 a2 a1))) :+: C1 ('MetaCons "S3R" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (r a3 a2 a1)))) |
data S4 l r (a4 :: k4) (a3 :: k3) (a2 :: k2) (a1 :: k1) Source #
Like S1
, but for l
and r
taking four type indexes.
Instances
(Arbitrary (l a4 a3 a2 a1), Arbitrary (r a4 a3 a2 a1)) => Arbitrary (S4 l r a4 a3 a2 a1) Source # | |
Generic (S4 l r a4 a3 a2 a1) Source # | |
(Read (l a4 a3 a2 a1), Read (r a4 a3 a2 a1)) => Read (S4 l r a4 a3 a2 a1) Source # | |
(Show (l a4 a3 a2 a1), Show (r a4 a3 a2 a1)) => Show (S4 l r a4 a3 a2 a1) Source # | |
(Binary (l a4 a3 a2 a1), Binary (r a4 a3 a2 a1)) => Binary (S4 l r a4 a3 a2 a1) Source # | |
(NFData (l a4 a3 a2 a1), NFData (r a4 a3 a2 a1)) => NFData (S4 l r a4 a3 a2 a1) Source # | |
Defined in Exinst.DeepSeq | |
(Eq (l a4 a3 a2 a1), Eq (r a4 a3 a2 a1)) => Eq (S4 l r a4 a3 a2 a1) Source # | |
(Ord (l a4 a3 a2 a1), Ord (r a4 a3 a2 a1)) => Ord (S4 l r a4 a3 a2 a1) Source # | |
Defined in Exinst.Internal.Sum compare :: S4 l r a4 a3 a2 a1 -> S4 l r a4 a3 a2 a1 -> Ordering # (<) :: S4 l r a4 a3 a2 a1 -> S4 l r a4 a3 a2 a1 -> Bool # (<=) :: S4 l r a4 a3 a2 a1 -> S4 l r a4 a3 a2 a1 -> Bool # (>) :: S4 l r a4 a3 a2 a1 -> S4 l r a4 a3 a2 a1 -> Bool # (>=) :: S4 l r a4 a3 a2 a1 -> S4 l r a4 a3 a2 a1 -> Bool # max :: S4 l r a4 a3 a2 a1 -> S4 l r a4 a3 a2 a1 -> S4 l r a4 a3 a2 a1 # min :: S4 l r a4 a3 a2 a1 -> S4 l r a4 a3 a2 a1 -> S4 l r a4 a3 a2 a1 # | |
(Hashable (l a4 a3 a2 a1), Hashable (r a4 a3 a2 a1)) => Hashable (S4 l r a4 a3 a2 a1) Source # | |
Defined in Exinst.Hashable | |
type Rep (S4 l r a4 a3 a2 a1) Source # | |
Defined in Exinst.Internal.Sum type Rep (S4 l r a4 a3 a2 a1) = D1 ('MetaData "S4" "Exinst.Internal.Sum" "exinst-0.9-8vEQLIk5SDG8OqmnB34M4p" 'False) (C1 ('MetaCons "S4L" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (l a4 a3 a2 a1))) :+: C1 ('MetaCons "S4R" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (r a4 a3 a2 a1)))) |
Re-exports
data Constraint #
The kind of constraints, like Show a
Values of type
capture a dictionary for a constraint of type Dict
pp
.
e.g.
Dict
::Dict
(Eq
Int
)
captures a dictionary that proves we have an:
instanceEq
Int
Pattern matching on the Dict
constructor will bring this instance into scope.
Instances
() :=> (Semigroup (Dict a)) | |
() :=> (Show (Dict a)) | |
() :=> (Eq (Dict a)) | |
() :=> (Ord (Dict a)) | |
a :=> (Monoid (Dict a)) | |
a :=> (Bounded (Dict a)) | |
a :=> (Enum (Dict a)) | |
a :=> (Read (Dict a)) | |
HasDict a (Dict a) | |
Defined in Data.Constraint | |
(Typeable p, p) => Data (Dict p) | |
Defined in Data.Constraint gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Dict p -> c (Dict p) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Dict p) # toConstr :: Dict p -> Constr # dataTypeOf :: Dict p -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Dict p)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Dict p)) # gmapT :: (forall b. Data b => b -> b) -> Dict p -> Dict p # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Dict p -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Dict p -> r # gmapQ :: (forall d. Data d => d -> u) -> Dict p -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Dict p -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Dict p -> m (Dict p) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Dict p -> m (Dict p) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Dict p -> m (Dict p) # | |
a => Monoid (Dict a) | |
Semigroup (Dict a) | |
a => Bounded (Dict a) | |
a => Enum (Dict a) | |
Defined in Data.Constraint | |
a => Read (Dict a) | |
Show (Dict a) | |
NFData (Dict c) | |
Defined in Data.Constraint | |
Eq (Dict a) | |
Ord (Dict a) | |
type family Sing :: k -> Type #
The singleton kind-indexed type family.
Instances
type Sing | |
Defined in Data.Singletons | |
type Sing | |
Defined in Data.Singletons |
A SingI
constraint is essentially an implicitly-passed singleton.
If you need to satisfy this constraint with an explicit singleton, please
see withSingI
or the Sing
pattern synonym.
Instances
SingI a => SingI ('WrapSing s :: WrappedSing a) | |
Defined in Data.Singletons | |
(forall (a :: k1). SingI a => SingI (f a), (ApplyTyCon :: (k1 -> kr) -> k1 ~> kr) ~ (ApplyTyConAux1 :: (k1 -> kr) -> TyFun k1 kr -> Type)) => SingI (TyCon1 f :: k1 ~> kr) | |
Defined in Data.Singletons | |
(forall (a :: k1) (b :: k2). (SingI a, SingI b) => SingI (f a b), (ApplyTyCon :: (k2 -> kr) -> k2 ~> kr) ~ (ApplyTyConAux1 :: (k2 -> kr) -> TyFun k2 kr -> Type)) => SingI (TyCon2 f :: k1 ~> (k2 ~> kr)) | |
Defined in Data.Singletons | |
(forall (a :: k1) (b :: k2) (c :: k3). (SingI a, SingI b, SingI c) => SingI (f a b c), (ApplyTyCon :: (k3 -> kr) -> k3 ~> kr) ~ (ApplyTyConAux1 :: (k3 -> kr) -> TyFun k3 kr -> Type)) => SingI (TyCon3 f :: k1 ~> (k2 ~> (k3 ~> kr))) | |
Defined in Data.Singletons | |
(forall (a :: k1) (b :: k2) (c :: k3) (d :: k4). (SingI a, SingI b, SingI c, SingI d) => SingI (f a b c d), (ApplyTyCon :: (k4 -> kr) -> k4 ~> kr) ~ (ApplyTyConAux1 :: (k4 -> kr) -> TyFun k4 kr -> Type)) => SingI (TyCon4 f :: k1 ~> (k2 ~> (k3 ~> (k4 ~> kr)))) | |
Defined in Data.Singletons | |
(forall (a :: k1) (b :: k2) (c :: k3) (d :: k4) (e :: k5). (SingI a, SingI b, SingI c, SingI d, SingI e) => SingI (f a b c d e), (ApplyTyCon :: (k5 -> kr) -> k5 ~> kr) ~ (ApplyTyConAux1 :: (k5 -> kr) -> TyFun k5 kr -> Type)) => SingI (TyCon5 f :: k1 ~> (k2 ~> (k3 ~> (k4 ~> (k5 ~> kr))))) | |
Defined in Data.Singletons | |
(forall (a :: k1) (b :: k2) (c :: k3) (d :: k4) (e :: k5) (f' :: k6). (SingI a, SingI b, SingI c, SingI d, SingI e, SingI f') => SingI (f a b c d e f'), (ApplyTyCon :: (k6 -> kr) -> k6 ~> kr) ~ (ApplyTyConAux1 :: (k6 -> kr) -> TyFun k6 kr -> Type)) => SingI (TyCon6 f :: k1 ~> (k2 ~> (k3 ~> (k4 ~> (k5 ~> (k6 ~> kr)))))) | |
Defined in Data.Singletons | |
(forall (a :: k1) (b :: k2) (c :: k3) (d :: k4) (e :: k5) (f' :: k6) (g :: k7). (SingI a, SingI b, SingI c, SingI d, SingI e, SingI f', SingI g) => SingI (f a b c d e f' g), (ApplyTyCon :: (k7 -> kr) -> k7 ~> kr) ~ (ApplyTyConAux1 :: (k7 -> kr) -> TyFun k7 kr -> Type)) => SingI (TyCon7 f :: k1 ~> (k2 ~> (k3 ~> (k4 ~> (k5 ~> (k6 ~> (k7 ~> kr))))))) | |
Defined in Data.Singletons | |
(forall (a :: k1) (b :: k2) (c :: k3) (d :: k4) (e :: k5) (f' :: k6) (g :: k7) (h :: k8). (SingI a, SingI b, SingI c, SingI d, SingI e, SingI f', SingI g, SingI h) => SingI (f a b c d e f' g h), (ApplyTyCon :: (k8 -> kr) -> k8 ~> kr) ~ (ApplyTyConAux1 :: (k8 -> kr) -> TyFun k8 kr -> Type)) => SingI (TyCon8 f :: k1 ~> (k2 ~> (k3 ~> (k4 ~> (k5 ~> (k6 ~> (k7 ~> (k8 ~> kr)))))))) | |
Defined in Data.Singletons |