| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Flay
Description
The most commonly used names in this module are intended to be imported unqualified, as necessary:
import Flay (Flay, Flayable, flay, Flayable1, flay1)
The rest of the names, qualified:
import qualified Flay
IMPORTANT: Always check the changelog to learn more about changes between different versions.
Synopsis
- type Flay (c :: k -> Constraint) s t (f :: k -> Type) (g :: k -> Type) = forall m. Applicative m => (forall a. Dict (c a) -> f a -> m (g a)) -> s -> m t
- class Flayable (c :: k -> Constraint) s t (f :: k -> Type) (g :: k -> Type) | s -> f, t -> g, s g -> t, t f -> s where
- type family Flayable1 (c :: k -> Constraint) (r :: (k -> Type) -> Type) :: Constraint where ...
- flay1 :: forall c r f g. Flayable1 c r => Flay c (r f) (r g) f g
- gflay :: GFlay c s t f g => Flay (c :: k -> Constraint) s t (f :: k -> Type) (g :: k -> Type)
- type GFlay (c :: k -> Constraint) s t (f :: k -> Type) (g :: k -> Type) = (GFlay' c (Rep s) (Rep t) f g, Generic s, Generic t)
- type family All (cs :: [k -> Constraint]) (x :: k) :: Constraint where ...
- class Trivial (a :: k)
- trivialize :: forall c s t f g. Flay c s t f g -> Flay Trivial s t f g
- trivial :: forall m s t f g. (Applicative m, Flayable Trivial s t f g) => (forall a. Trivial a => f a -> m (g a)) -> s -> m t
- trivial1 :: forall m f g r. (Applicative m, Flayable1 Trivial r) => (forall a. Trivial a => f a -> m (g a)) -> r f -> m (r g)
- trivial' :: forall m c s t f g. Applicative m => Flay c s t f g -> (forall a. Trivial a => f a -> m (g a)) -> s -> m t
- collect :: (Monoid b, Flayable c s t f (Const ())) => (forall a. Dict (c a) -> f a -> b) -> s -> b
- collect1 :: (Monoid b, Flayable1 c r) => (forall a. Dict (c a) -> f a -> b) -> r f -> b
- collect' :: Monoid b => Flay c s t f (Const ()) -> (forall a. Dict (c a) -> f a -> b) -> s -> b
- zip :: forall c s1 s2 t1 t2 t3 f g h m. (Monad m, Typeable f, Flayable Typeable s1 t1 f (Const ()), Flayable Typeable s2 t2 g (Product f g), Flayable c t2 t3 (Product f g) h) => (forall x. Dict (c x) -> f x -> g x -> m (h x)) -> s1 -> s2 -> m (Maybe t3)
- zip1 :: forall c s f g h m. (Monad m, Typeable f, Flayable1 c s, Flayable1 Typeable s) => (forall x. Dict (c x) -> f x -> g x -> m (h x)) -> s f -> s g -> m (Maybe (s h))
- unsafeZip :: forall c s1 s2 t1 t2 t3 f g h m. (Monad m, Typeable f) => Flay Typeable s1 t1 f (Const ()) -> Flay Typeable s2 t2 g (Product f g) -> Flay c t2 t3 (Product f g) h -> (forall x. Dict (c x) -> f x -> g x -> m (h x)) -> s1 -> s2 -> m (Maybe t3)
- terminal :: Terminal a => a
- class Terminal a
- class GTerminal (f :: Type -> Type)
- data Pump s f
- type GPump s f = (Generic s, GPump' (Rep s) f)
- pump :: GPump s f => (forall x. x -> f x) -> s -> Pump s f
- dump :: (GPump s f, Applicative m) => (forall a. f a -> m a) -> Pump s f -> m s
- type Fields c s = GFields c (Rep s)
- type family GFields (c :: kc -> Constraint) (s :: ks -> Type) :: Constraint where ...
- type family FieldsF (c :: k -> Constraint) (r :: (k -> Type) -> Type) :: Constraint where ...
- type family GFieldsF (c :: k -> Constraint) (s :: ks -> Type) (f :: k -> Type) :: Constraint where ...
- data Dict a where
Documentation
type Flay (c :: k -> Constraint) s t (f :: k -> Type) (g :: k -> Type) = forall m. Applicative m => (forall a. Dict (c a) -> f a -> m (g a)) -> s -> m t Source #
allows converting Flay c s t f gs to t by replacing
ocurrences of f with g by applicatively applying a function
(forall a. c a => f a -> m (g a)) to targeted occurences of f a inside
s.
A Flay must obey the following identity law:
forall (fl ::Flayc s t f g). fl (constpure) ==pure
When defining Flay values, you should leave c, f, and g fully
polymorphic, as these are the most useful types of Flays.
We use instead of Dict (c a) ->c a => because the latter is often not
enough to satisfy the type checker. With this approach, one must explicitly
pattern match on the constructor in order to bring the Dict (c a)c a
instance to scope. Also, it's necessary that c is explicitly given a type
at the Flay's call site, as otherwise the type checker won't be able to
infer c on its own.
to flay: tr. v., to strip off the skin or surface of.
Mnemonic for c s t f g: Much like lenses have type indexes s t a b where
s is the input state, t is the output state, and a and b are the
input and output values respectively, in Flay, s and t represent the
input and output states like in lenses, and f and g represent the
wrappers over the input and output values respectively. The c comes at
the very beginning because it is the type you are expected to apply with
TypeApplications if necessary.
Example 1: Removing uncertainty
Consider the following types and values:
-- | Foo is a higher-kinded type parametrized over somef ::. data Foo f = Foo (fType->TypeInt) (fBool) deriving instance (Show(fInt),Show(fBool)) =>Show(Foo f)
flayFoo :: (Applicativem, cInt, cBool) =>Flayc (Foo f) (Foo g) f g flayFoo h (Foo a b) = Foo <$> hDicta <*> hDictb
foo1 :: FooMaybefoo1 = Foo (Just1)Nothing
foo2 :: FooMaybefoo2 = Foo (Just2) (JustTrue)
It is possible to remove the uncertainty of the fields in Foo perhaps
being empty (Nothing) by converting Foo to MaybeFoo .
However, we can't just write a function of type IdentityFoo because we have the possiblity of some of the fields being
Maybe -> Foo
IdentityNothing, like in foo1. Instead, we are looking for a function Foo
which will result on Maybe -> Maybe (Foo Identity)Just only as long
as all of the fields in Foo is Just, like in foo2. This is exactly what
Applicative enables us to do:
fooMaybeToIdentity :: FooMaybe->Maybe(FooIdentity) fooMaybeToIdentity (Foo a b) = Foo <$>fmappurea <*>fmappureb
Example using this in GHCi:
> fooMaybeToIdentity foo1
Nothing
> fooMaybeToIdentity foo2Just(Foo (Identity2) (IdentityTrue))
In fact, notice that we are not really working with Just, Nothing, nor
Identity directly, so we might as well just leave Maybe and Identity
polymorphic. All we need is that they both are Applicatives:
fooMToG :: (Applicativem,Applicativeg) => Foo m -> m (Foo g) fooMToG (Foo a b) = Foo <$>fmappurea <*>fmappureb
fooMToG behaves the same as fooMaybeToIdentity, but more importantly, it
is much more flexible:
> fooMToG foo2 ::Maybe(Foo [])Just(Foo [2] [True])
> fooMToG foo2 ::Maybe(Foo (EitherString))Just(Foo (Right2) (RightTrue))
Flay, among other things, is intended to generalize this pattern, so that
whatever choice of Foo, Maybe or Identity you make, you can use
Applicative this way. The easiest way to use Flay is through trivial',
which is sufficient unless we need to enforce some constraint in the target
elements wrapped in m inside foo (we don't need this now). With trivial',
we could have defined fooMToG this way:
fooMToG :: (Applicativem,Applicativeg) => Foo m -> m (Foo g) fooMToG =trivial'flayFoo (fmappure)
Some important things to notice here are that we are reusing flayFoo's
knowledge of Foo's structure, and that the construction of g using pure
applies to any value wrapped in m (Int and Bool in our case). Compare
this last fact to traverse, where the types of the targets must be the
same, and known beforehand.
Also, notice that we inlined flayFoo for convenience in this example, but
we could as well have taken it as an argument, illustrating even more how
Flay decouples the shape and targets from their processing:
flayMToG :: (Applicativem,Applicativeg) =>FlayTrivialm s t m g -> s -> m s flayMToG fl =trivial'fl (fmappure)
This is the esscence of Flay: We can work operating on the contents of a
datatype s targeted by a given Flay without knowing anything about s,
nor about the forall x. f x targets of the Flay. And we do this using an
principled approach relying on Applicative and Functor.
We can use a Flay to repurpose a datatype while maintaining its "shape".
For example, given Foo: Foo represents the presence of two
values IdentityInt and Char, Foo represents their potential absence,
MaybeFoo [] represents the potential for zero or more Ints and Chars,
Foo ( represent the presence of two values of type Const x)x, and Foo
represents two IOIO actions necessary to obtain values of type Int
and Char. We can use flayFoo to convert between these representations. In
all these cases, the shape of Foo is preserved, meaning we can continue to
pattern match or project on it. Notice that even though in this example the
f argument to Foo happens to always be a Functor, this is not necessary
at all.
Example 2: Standalone m
In the previous example, flayFoo took the type Flay when it was used in Trivial (Foo m) (Foo
g) m gflayMToG. That is, m and f were unified by
our use of fmap. However, keeping these different opens interesting
possibilities. For example, let's try and convert a Foo to a MaybeFoo
(, prompting the user for the Either String)Left side of that Either
whenever the original target value is missing.
prompt ::IOStringprompt = doputStr"Missing value! Error message? "getLine
fooMaybeToEitherIO :: FooMaybe->IO(Foo (EitherString)) fooMaybeToEitherIO =trivial'flayFoo $ \caseNothing->fmapLeftpromptJustx ->pure(Rightx)
Using this in GHCi:
> fooMaybeToEitherIO foo1 Missing value! Error message? Nooooo!!!!! Foo (Right1) (Left"Nooooo!!!!!")
> fooMaybeToEitherIO foo2 Foo (Right2) (RightTrue)
Example 3: Contexts
Extending the previous example we "replaced" the missing values with a
String, but wouldn't it be nice if we could somehow prompt a replacement
value of the original type instead? That's what the c argument to Flay is
for. Let's replace prompt so that it can construct a type other than
String:
prompt ::Readx =>IOx prompt = doputStr"Missing value! Replacement? "readLn
Notice how prompt now has a constraint. In order to be able to
use the result of Read xprompt as a replacement for our missing values in Foo
, we will have to mention MaybeRead as the c argument to Flay,
which implies that Read will have to be a constraint satisfied by all of
the targets of our Flay (as seen in the constraints in flayFoo). We can't
use trivial' anymore, we need to use flayFoo directly:
fooMaybeToIdentityIO :: FooMaybe->IO(FooIdentity) fooMaybeToIdentityIO = flayFoo h where h ::Dict(Reada) ->Maybea ->IO(Identitya) hDict= \caseNothing->fmappurepromptJusta ->pure(purea)
Notice how we had to give an explicit type to our function h: This is
because can't infer our constraint. You will always need to
explicitly type the received Read a unless the Dictc argument to Flay has
been explicitly by other means (like in the definition of trivial', where
we don't have to explicitly type Dict because c ~ according to
the top level signature of Trivialtrivial'). Using the TypeApplications GHC
extension might make things easier:
fooMaybeToIdentityIO :: FooMaybe->IO(FooIdentity) fooMaybeToIdentityIO = flayFoo @Read (\Dict-> \caseNothing->fmappurepromptJusta ->pure(purea))
Example using this in GHCi:
> fooMaybeToIdentityIO foo1 Missing value! Replacement?TrueFoo (Identity1) (IdentityTrue)
> fooMaybeToIdentityIO foo2 Foo (Identity2) (IdentityTrue)
Of course, as in our previous examples, Identity here could have
generalized to any Applicative. We just fixed it to Identity as an
example.
You can mention as many constraints as you need in c as long as c has
kind k -> (where Constraintk is the kind of f's argument). You can
always group together many constraints as a single new one in order to
achieve this. For example, if you want to require both Show and Read on
your target types, then you can introduce the following ShowAndRead class,
and use that as your c.
class (Showa,Reada) => ShowAndRead a instance (Showa,Reada) => ShowAndRead a
This is such a common scenario that the Flay module exports All, a
Constraint you can use to apply many Constraints at once. For example,
instead of introducing ShowAndRead, we could use
as our All '[Show, Read]c argument to Flay, and the net result would be the same.
Example 4: collect'
See the documentation for collect'. To sum up: for any given Flay, we can
collect all of the Flay's targets into a Monoid, without knowing anything
about the targets themselves beyond the fact that they satisfy a particular
constraint.
Flayable
class Flayable (c :: k -> Constraint) s t (f :: k -> Type) (g :: k -> Type) | s -> f, t -> g, s g -> t, t f -> s where Source #
Default Flay implementation for s and t.
When defining Flayable instances, you should leave c, f, and g
fully polymomrphic, as these are the most useful types of Flayabless.
If s and t are instances of Generic, then gflay can be used as
default implementation for flay. For example, provided the following
datatype and its Generic instance:
data Foo f = Foo (fInt) (fBool) deriving (Generic)
Then the following Flayable instance would get a default implementation for
flay:
instance (cInt, cBool) =>Flayablec (Foo f) (Foo g) f g
But actually, this library exports an OVERLAPPABLE instance that covers
datatypes like Foo above. That is, datatypes parametrized by some type
constructor where that type constructor wraps each of the immediate children
fields. So
most times you don't even need to write the Flayable instance yourself.
That is, a for Flayable c (r f) (r g) f gr types parametrized by a
type-constructor, such as Foo, having Generic instances.
In cases where you do need to define the Flayable instance yourself, you'll
notice that constraints applying c to every immediate child field type will
bubble up, such as (c in the example above. This module
exports the Int, c Bool)FieldsF constraint that can be used to reduce that boilerplate
for datatypes that implement Generic, tackling all of the fields at once.
That is, the Flayable instance for Foo above could have been written like
this:
instanceFieldsFc Foo =>Flayablec (Foo f) (Foo g) f g
Minimal complete definition
Nothing
Instances
| GFlay c (r f) (r g) f g => Flayable (c :: k -> Constraint) (r f) (r g) (f :: k -> Type) (g :: k -> Type) Source # | All datatypes parametrized over some type constructor data Foo f = Foo (f This is an |
| GFlay' c (GPumped (Rep s) f) (GPumped (Rep s) g) f g => Flayable (c :: Type -> Constraint) (Pump s f) (Pump s g) (f :: Type -> Type) (g :: Type -> Type) Source # | |
type family Flayable1 (c :: k -> Constraint) (r :: (k -> Type) -> Type) :: Constraint where ... Source #
Flayable1 is Flayable specialized for the common case of s ~ r f and
t ~ r g. The rationale for introducing this seemingly redundant constraint
is that Flayable1 is less verbose than Flayable.
In other words, if we had QuantifiedConstraints, then Flayable1 would be
something like:
Flayable1c r == forall (f :: k ->Type) (g :: k ->Type).Flayablec (r f) (r g) f g
Equations
| Flayable1 c r = Flayable1_ c r |
Generics
gflay :: GFlay c s t f g => Flay (c :: k -> Constraint) s t (f :: k -> Type) (g :: k -> Type) Source #
type GFlay (c :: k -> Constraint) s t (f :: k -> Type) (g :: k -> Type) = (GFlay' c (Rep s) (Rep t) f g, Generic s, Generic t) Source #
Convenient Constraint for satisfying the requirements of gflay.
Utils
type family All (cs :: [k -> Constraint]) (x :: k) :: Constraint where ... Source #
Ensure that x satisfies all of the constraints listed in cs.
class Trivial (a :: k) Source #
Constraint trivially satisfied by every type.
This can be used as the c parameter to Flay or Flayable in case you are
not interested in observing the values inside f.
trivial :: forall m s t f g. (Applicative m, Flayable Trivial s t f g) => (forall a. Trivial a => f a -> m (g a)) -> s -> m t Source #
trivial1 :: forall m f g r. (Applicative m, Flayable1 Trivial r) => (forall a. Trivial a => f a -> m (g a)) -> r f -> m (r g) Source #
trivial' :: forall m c s t f g. Applicative m => Flay c s t f g -> (forall a. Trivial a => f a -> m (g a)) -> s -> m t Source #
You can use trivial' if you don't care about the c argument to Flay.
This implies that you won't be able to observe the a in forall a. f a,
all you can do with such a is pass it around.
forall (fl ::FlayTrivials t f g) (h ::Applicativem =>DictTrivial-> f a -> m (g a)).trivial'fl h == fl (consth)
collect :: (Monoid b, Flayable c s t f (Const ())) => (forall a. Dict (c a) -> f a -> b) -> s -> b Source #
collect' :: Monoid b => Flay c s t f (Const ()) -> (forall a. Dict (c a) -> f a -> b) -> s -> b Source #
zip :: forall c s1 s2 t1 t2 t3 f g h m. (Monad m, Typeable f, Flayable Typeable s1 t1 f (Const ()), Flayable Typeable s2 t2 g (Product f g), Flayable c t2 t3 (Product f g) h) => (forall x. Dict (c x) -> f x -> g x -> m (h x)) -> s1 -> s2 -> m (Maybe t3) Source #
zip1 :: forall c s f g h m. (Monad m, Typeable f, Flayable1 c s, Flayable1 Typeable s) => (forall x. Dict (c x) -> f x -> g x -> m (h x)) -> s f -> s g -> m (Maybe (s h)) Source #
Zip two Flayable1s together.
Example pairing two of the Foo values seen elsewhere in this file.
> let foo1 =Foo(Identity0) (IdentityFalse) > ::FooIdentity> let foo2 =Foo(Just1)Nothing> ::FooMaybe>zip1((Dict::Dict(Trivialx)) a b ->pure(Paira b)) foo1 foo2 > ::Applicativem => m (Maybe(Foo(ProductIdentityMaybe)))Just(Foo(Pair(Identity0) (Just1)) (Pair(IdentityFalse)Nothing)) >zip1((Dict::Dict(Showx)) (Identitya) yb -> case yb of >Nothing->pure(Const(showa)) >Justb ->pure(Const(show(a, b))) ) > foo1 foo2 > ::Applicativem => m (Maybe(Foo (ConstString)))Just(Foo (Const"(0,1)") (Const"False"))
Returns Nothing in case the indivual target types do not match.
unsafeZip :: forall c s1 s2 t1 t2 t3 f g h m. (Monad m, Typeable f) => Flay Typeable s1 t1 f (Const ()) -> Flay Typeable s2 t2 g (Product f g) -> Flay c t2 t3 (Product f g) h -> (forall x. Dict (c x) -> f x -> g x -> m (h x)) -> s1 -> s2 -> m (Maybe t3) Source #
Witness that a is a terminal object. That is, that a can always be
constructed out of thin air.
Minimal complete definition
class GTerminal (f :: Type -> Type) Source #
Minimal complete definition
gterminal
Pump & Dump
Wrapper allowing a Generic non Flayable type to become Flayable.
Most datatypes that can have useful Flayable instances are often
parametrized by a type constructor f :: k -> , and have all or some of
their fields wrapped in said Typef, like so:
data Foo f = Foo (fInt) (fBool)
However, that kind of representation is not that common, and it can sometimes
be unconfortable to use, particularly if f ~ due to the
necessary wrapping and unwrapping of values. In Haskell, it's more common to
use a representation like the following for records (or sums):Identity
data Bar = BarIntBoolderiving (Generic)
The problem with that representation, however, is that it prevents us to
operate on the individual fields as enabled by Flay.
Pump is a wrapper that converts types like Bar into types like Foo. In
our concrete case, is isomorphic to Pump Bar f. But more
importantly, Foo f automatically gets a Pump Bar fFlayable instance of its
own, allowing you to use flay to operate on as you would
operate on Pump Bar f.Foo f
To construct a Pump you use pump, and to remove the Pump wrapper you
use dump, which satisfy the following identity law:
dumpid.pumppure==pure
Pump relies on Haskell's Generics, which is why we derived
Generic for our Bar above. If Bar didn't have a Generic instance,
then you wouldn't be able to use Pump and would be better served by a
manually written functions converting Bar to Foo and back.
Keep in mind that will only add Pump s ff wrappers to the immediate
children fields of s (which could itself be a sum type or a product type),
but it won't recurse into the fields and add f wrappers to them.
Very contrived and verbose example using all of pump, dump and flay:
-- | Replaces all of the fields of the given Bar with valuesReadfrom --stdin, if possible. qux :: Bar ->IO(EitherStringBar) qux bar0 = do let pbar0 ::PumpBarIdentitypbar0 =pumpIdentitybar0 let h ::Dict(Reada) ->Identitya ->IO(Maybea) hDict(Identity_) =fmapreadMaybegetLinepbar1 ::PumpBarMaybe<-flayh pbar0 -- We convert theMaybes toEitherjust for demonstration purposes. -- Usingdumpidwould have been enough to make this function -- return aMaybeBar. let ebar1 ::EitherStringBarebar1 =dump(maybe(Left"Bad")Right) pbar1 pure ebar1
Or, written in a less verbose manner:
qux :: Bar ->IO(EitherStringBar) qux bar =fmap(dump(maybe(Left"Bad")Right)) (flay@Read((Dict(Identity_) ->fmapreadMaybegetLine) (pumpIdentitybar)
We can use qux in GHCi as follows:
> qux (Bar 0 False) not a number not a bool Left "Bad" > qux (Bar 0 False) 1 True Right (Bar 1 True)
type GPump s f = (Generic s, GPump' (Rep s) f) Source #
Convenient Constraint for satisfying the requirements of pump and
dump.
Arguments
| :: (GPump s f, Applicative m) | |
| => (forall a. f a -> m a) | How to remove the |
| -> Pump s f | |
| -> m s |
Miscellaneous
type Fields c s = GFields c (Rep s) Source #
Ensure that all of the immeditate children fields of s satisfy c.
For example, in a datatype like the following:
data Bar = BarIntBool
The Fields constraint behaves like this:
Fieldsc Bar == (cInt, cBool)
Fields can be used to remove boilerplate from contexts, since c
will need to be mentioned just once, rather than once per type of field. This
is particularly useful in the case of datatypes as Foo below, intended to
be used with Flay:
data Foo f = Foo (fInt) (fBool)
The problem with types shaped like Foo is that deriving some useful
instances for them, like Show, involves a lot of boilerplate.
For one, the usual deriving ( statement doesn't work, and you
need to rely on the Show)StandaloneDeriving GHC extension. But even that's not
enough, since you need to ensure that Show constrains the individual field
types as well. That is:
deriving instance (Show(fInt),Show(fBool)) =>Show(Foo f)
This works, but hopefully you can see how this can become very verbose when
you have more than a two or three datatypes in your fields. Instead, provided
we derive Generic for Foo, we can use Fields to remove that
boilerplate. That is:
data Foo f = Foo (fInt) (fBool) deriving (Generic) deriving instanceFieldsShow(Foo f) =>Show(Foo f)
type family GFields (c :: kc -> Constraint) (s :: ks -> Type) :: Constraint where ... Source #
Like Fields, but s is expected to be a Rep.
This Constraint ensures that c is satsfieds by all of the K1 types
appearing in s, which is expected to be one of the various Generic
representation types.
type family FieldsF (c :: k -> Constraint) (r :: (k -> Type) -> Type) :: Constraint where ... Source #
This is like Fields, but it targets only field types that are wrapped by
some type-constructor f.
That is, for all a in s f such that f a is an immediate children of s
f, then c a must be satisfied.
FieldsF can be used to remove boilerplate from contexts, since c
will need to be mentioned just once, rather than once per type of field. This
is particularly useful in the case of datatypes as Foo below, intended to
be used with Flay:
data Foo f = Foo (fInt) (fBool)
If, for example, you intend to implement a
instance, then constraints Flayable c (Foo f) (Foo g) f gc and Intc will propagate. However,
instead of writing Bool(c , you can write Int, c Bool)
and achieve the same, which will reduce boilerplate significantly in cases
where the number of types contained in FieldsF c Foof is larger. That is:
forall (c ::Type->Constraint).FieldsFcFoo== (cInt, cBool)
Notice that FieldsF only works with types of kind (k -> such as
Type) -> TypeFoo. That is, types that are parametrized by a type constructor.
Equations
| FieldsF c r = FieldsF_ c r |
type family GFieldsF (c :: k -> Constraint) (s :: ks -> Type) (f :: k -> Type) :: Constraint where ... Source #
Like FieldsF, but s is expected to be a Rep, and the type-constructor
f expected to wrap all of the field targets we want to constraint with c
should be given explicitly.
This Constraint ensures that c is satsfieds by all of the K1 types
appearing in s that are wrapped by f.
Re-exports
Values of type capture a dictionary for a constraint of type Dict pp.
e.g.
Dict::Dict(EqInt)
captures a dictionary that proves we have an:
instanceEqInt
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 Methods 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) | |
| c => Boring (Dict c) | |
Defined in Data.Constraint | |
| NFData (Dict c) | |
Defined in Data.Constraint | |
| Eq (Dict a) | |
| Ord (Dict a) | |