flay-0.4: Work generically on your datatype without knowing its shape nor its contents.

Safe HaskellNone
LanguageHaskell2010

Flay

Contents

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

Documentation

type Flay (c :: k -> Constraint) s t (f :: k -> *) (g :: k -> *) = forall m. Applicative m => (forall (a :: k). Dict (c a) -> f a -> m (g a)) -> s -> m t Source #

Flay c s t f g allows converting s 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 :: Flay c s t f g).
   fl (const pure)  ==  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 Dict (c a) -> instead of c a => because the latter is often not enough to satisfy the type checker. With this approach, one must explicitly pattern match on the Dict (c a) constructor in order to bring the 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:

data Foo f = Foo (f Int) (f Bool)

deriving instance (Show (f Int), Show (f Bool)) => Show (Foo f)
flayFoo :: (Applicative m, c Int, c Bool) => Flay c (Foo f) (Foo g) f g
flayFoo h (Foo a b) = Foo <$> h Dict a <*> h Dict b
foo1 :: Foo Maybe
foo1 = Foo (Just 1) Nothing
foo2 :: Foo Maybe
foo2 = Foo (Just 2) (Just True)

It is possible to remove the uncertainty of the fields in Foo perhaps being empty (Nothing) by converting Foo Maybe to Foo Identity. However, we can't just write a function of type Foo Maybe -> Foo Identity because we have the possiblity of some of the fields being Nothing, like in foo1. Instead, we are looking for a function Foo Maybe -> Maybe (Foo Identity) which will result on 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 :: Foo Maybe -> Maybe (Foo Identity)
fooMaybeToIdentity (Foo a b) = Foo <$> fmap pure a <*> fmap pure b

Example using this in GHCi:

> fooMaybeToIdentity foo1
Nothing
> fooMaybeToIdentity foo2
Just (Foo (Identity 2) (Identity True))

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 :: (Applicative m, Applicative g) => Foo m -> m (Foo g)
fooMToG (Foo a b) = Foo <$> fmap pure a <*> fmap pure b

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 (Either String))
Just (Foo (Right 2) (Right True))

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 :: (Applicative m, Applicative g) => Foo m -> m (Foo g)
fooMToG = trivial' flayFoo (fmap pure)

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 :: (Applicative m, Applicative g) => Flay Trivial m s t m g -> s -> m s
flayMToG fl = trivial' fl (fmap pure)

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 Identity represents the presence of two values Int and Char, Foo Maybe represents their potential absence, Foo [] represents the potential for zero or more Ints and Chars, Foo (Const x) represent the presence of two values of type x, and Foo IO represents two IO 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 Trivial (Foo m) (Foo g) m g when it was used in flayMToG. 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 Maybe to a Foo (Either String), prompting the user for the Left side of that Either whenever the original target value is missing.

prompt :: IO String
prompt = do
  putStr "Missing value! Error message? "
  getLine
fooMaybeToEitherIO :: Foo Maybe -> IO (Foo (Either String))
fooMaybeToEitherIO = trivial' flayFoo $ \case
   Nothing -> fmap Left prompt
   Just x -> pure (Right x)

Using this in GHCi:

> fooMaybeToEitherIO foo1
Missing value! Error message? Nooooo!!!!!
Foo (Right 1) (Left "Nooooo!!!!!")
> fooMaybeToEitherIO foo2
Foo (Right 2) (Right True)

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 :: Read x => IO x
prompt = do
  putStr "Missing value! Replacement? "
  readLn

Notice how prompt now has a Read x constraint. In order to be able to use the result of prompt as a replacement for our missing values in Foo Maybe, we will have to mention Read 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 :: Foo Maybe -> IO (Foo Identity)
fooMaybeToIdentityIO = flayFoo h
  where h :: Dict (Read a) -> Maybe a -> IO (Identity a)
        h Dict = \case
            Nothing -> fmap pure prompt
            Just a -> pure (pure a)

Notice how we had to give an explicit type to our function h: This is because can't infer our Read a constraint. You will always need to explicitly type the received Dict unless the c 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 ~ Trivial according to the top level signature of trivial'). Using the TypeApplications GHC extension might make things easier:

fooMaybeToIdentityIO :: Foo Maybe -> IO (Foo Identity)
fooMaybeToIdentityIO = flayFoo @Read (\Dict -> \case
    Nothing -> fmap pure prompt
    Just a -> pure (pure a))

Example using this in GHCi:

> fooMaybeToIdentityIO foo1
Missing value! Replacement? True
Foo (Identity 1) (Identity True)
> fooMaybeToIdentityIO foo2
Foo (Identity 2) (Identity True)

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 -> Constraint (where k 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 (Show a, Read a) => ShowAndRead a
instance (Show a, Read a) => 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 All '[Show, Read] as our 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 -> *) (g :: k -> *) | 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 (f Int) (f Bool)
  deriving (Generic)

Then the following Flayable instance would get a default implementation for flay:

instance (c Int, c Bool) => Flayable c (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 Flayable c (r f) (r g) f g for r 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 Int, c Bool) in the example above. This module exports the 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:

instance FieldsF c Foo => Flayable c (Foo f) (Foo g) f g

Notice that flay can be defined in terms of flay1 as well.

Methods

flay :: Flay c s t f g Source #

flay :: GFlay c s t f g => Flay c s t f g Source #

Instances
GFlay c (r f) (r g) f g => Flayable (c :: k -> Constraint) (r f) (r g) (f :: k -> *) (g :: k -> *) Source #

All datatypes parametrized over some type constructor f :: k -> * that have a Generic instance get a Flayable instance for free. For example:

data Foo f = Foo (f Int) (f Bool)
  deriving (Generic)

This is an OVERLAPPABLE instance, meaning that you can provide a different instance for your Generic datatype, if necessary.

Instance details

Methods

flay :: Flay c (r f) (r g) f g Source #

GFlay' c (GPumped (Rep s) f) (GPumped (Rep s) g) f g => Flayable (c :: * -> Constraint) (Pump s f) (Pump s g) (f :: * -> *) (g :: * -> *) Source # 
Instance details

Methods

flay :: Flay c (Pump s f) (Pump s g) f g Source #

type family Flayable1 (c :: k -> Constraint) (r :: (k -> *) -> *) :: 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:

Flayable1 c r
   ==  forall (f :: k -> *) (g :: k -> *).
          Flayable c (r f) (r g) f g

Equations

Flayable1 c r = Flayable1_ c r 

flay1 :: forall c r f g. Flayable1 c r => Flay c (r f) (r g) f g Source #

Like flay, but specialized to work on Flayable1.

Generics

gflay :: GFlay c s t f g => Flay (c :: k -> Constraint) s t (f :: k -> *) (g :: k -> *) Source #

type GFlay (c :: k -> Constraint) s t (f :: k -> *) (g :: k -> *) = (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.

Equations

All (c ': cs) x = (c x, All cs x) 
All '[] _ = () 

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.

Instances
Trivial (a :: k) Source # 
Instance details

trivialize :: forall c s t f g. Flay c s t f g -> Flay Trivial s t f g Source #

Given a Flay for any constraint c obtain a Flay for a Trivial constraint.

trivial Source #

Arguments

:: (Applicative m, Flayable Trivial s t f g) 
=> (forall a. Trivial a => f a -> m (g a)) 
-> s 
-> m t 

Like trivial', but works on a Flayable instead of taking an explicit Flay.

trivial = trivial' flay

trivial1 Source #

Arguments

:: (Applicative m, Flayable1 Trivial r) 
=> (forall a. Trivial a => f a -> m (g a)) 
-> r f 
-> m (r g) 

Like trivial', but works on a Flayable1 instead of taking an explicit Flay.

trivial = trivial' flay1

trivial' Source #

Arguments

:: Applicative m 
=> Flay c s t f g 
-> (forall a. Trivial a => f a -> m (g a)) 
-> s 
-> m t 

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 :: Flay Trivial s t f g)
       (h :: Applicative m => Dict Trivial -> f a -> m (g a)).
trivial' fl h  == fl (const h)

collect Source #

Arguments

:: (Monoid b, Flayable c s t f (Const ())) 
=> (forall a. Dict (c a) -> f a -> b) 
-> s 
-> b 

Like collect', but works on a Flayable instead of an explicit Flay.

collect1 Source #

Arguments

:: (Monoid b, Flayable1 c r) 
=> (forall a. Dict (c a) -> f a -> b) 
-> r f 
-> b 

Like collect', but works on a Flayable1 instead of an explicit Flay.

collect' Source #

Arguments

:: Monoid b 
=> Flay c s t f (Const ()) 
-> (forall a. Dict (c a) -> f a -> b) 
-> s 
-> b 

Collect all of the f a of the given Flay into a Monoid b.

Example usage, given Foo and flayFoo examples given in the documentation for Flay:

> collect' flayFoo
      (\(Dict :: Dict (Show a)) (Identity (a :: a)) -> [show a])
      (Foo (pure 4) (pure True))
["4","True"]

zip Source #

Arguments

:: (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) 

Zip two Flayables together.

zip is like zip1, but for Flayables.

Returns Nothing in case the indivual target types do not match.

Note: zip is safer but less general than unsafeZip.

zip1 Source #

Arguments

:: (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)) 

Zip two Flayable1s together.

Example pairing two of the Foo values seen elsewhere in this file.

> let foo1 = Foo (Identity 0) (Identity False)
>   :: Foo Identity

> let foo2 = Foo (Just 1) Nothing
>   :: Foo Maybe

> zip1 ((Dict :: Dict (Trivial x)) a b -> Pair a b) foo1 foo2
>   :: Foo (Product Identity Maybe)
Foo (Pair (Identity 0) (Just 1)) (Pair (Identity False) Nothing)

> zip1 ((Dict :: Dict (Show x)) (Identity a) yb -> case yb of
>           Nothing -> Const (show a)
>           Just b  -> Const (show (a, b)) )
>      foo1 foo2
>   :: Foo (Const String)
Foo (Const "(0,1)") (Const "False")

Returns Nothing in case the indivual target types do not match.

Note: zip1 is safer but less general than unsafeZip.

unsafeZip Source #

Arguments

:: (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) 

Unsafe version of zip that doesn't guarantee that the given Flays target the same values. zip and zip1 make this function safe by simply using flay or flay1 three times.

Returns Nothing in case the indivual target types do not match.

class Terminal a Source #

Witness that a is a terminal object. That is, that a can always be constructed out of thin air.

Minimal complete definition

terminal

Instances
Terminal () Source # 
Instance details

Methods

terminal :: () Source #

(Generic a, GTerminal (Rep a)) => Terminal a Source # 
Instance details

Methods

terminal :: a Source #

Terminal (Const () a) Source # 
Instance details

Methods

terminal :: Const () a Source #

class GTerminal (f :: * -> *) Source #

Minimal complete definition

gterminal

Instances
GTerminal (U1 :: * -> *) Source # 
Instance details

Methods

gterminal :: U1 p

Terminal x => GTerminal (K1 i x :: * -> *) Source # 
Instance details

Methods

gterminal :: K1 i x p

(GTerminal l, GTerminal r) => GTerminal (l :*: r) Source # 
Instance details

Methods

gterminal :: (l :*: r) p

GTerminal f => GTerminal (M1 i c f) Source # 
Instance details

Methods

gterminal :: M1 i c f p

Pump & Dump

data Pump s f Source #

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 f, like so:

data Foo f = Foo (f Int) (f Bool)

However, that kind of representation is not that common, and it can sometimes be unconfortable to use, particularly if f ~ Identity 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):

data Bar = Bar Int Bool
  deriving (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, Pump Bar f is isomorphic to Foo f. But more importantly, Pump Bar f automatically gets a Flayable instance of its own, allowing you to use flay to operate on Pump Bar f as you would operate on Foo f.

To construct a Pump you use pump, and to remove the Pump wrapper you use dump, which satisfy the following identity law:

dump id . pump pure  ==  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 Pump s f will only add f 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 values Read from
-- stdin, if possible.
qux :: Bar -> IO (Either String Bar)
qux bar0 = do
   let pbar0 :: Pump Bar Identity
       pbar0 = pump Identity bar0
   let h :: Dict (Read a) -> Identity a -> IO (Maybe a)
       h Dict (Identity _) = fmap readMaybe getLine
   pbar1 :: Pump Bar Maybe <- flay h pbar0
   -- We convert the Maybes to Either just for demonstration purposes.
   -- Using dump id would have been enough to make this function
   -- return a Maybe Bar.
   let ebar1 :: Either String Bar
       ebar1 = dump (maybe (Left "Bad") Right) pbar1
   pure ebar1

Or, written in a less verbose manner:

qux :: Bar -> IO (Either String Bar)
qux bar = fmap (dump (maybe (Left "Bad") Right))
               (flay @Read
                     ((Dict (Identity _) -> fmap readMaybe getLine)
                     (pump Identity bar)

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)
Instances
GFlay' c (GPumped (Rep s) f) (GPumped (Rep s) g) f g => Flayable (c :: * -> Constraint) (Pump s f) (Pump s g) (f :: * -> *) (g :: * -> *) Source # 
Instance details

Methods

flay :: Flay c (Pump s f) (Pump s g) f g Source #

type GPump s f = (Generic s, GPump' (Rep s) f) Source #

Convenient Constraint for satisfying the requirements of pump and dump.

pump Source #

Arguments

:: GPump s f 
=> (forall x. x -> f x)

How to wrap in f each individual child field of s.

-> s 
-> Pump s f 

Wrap s in Pump so that it can be flayed.

See the documentation for Pump for more details.

dump Source #

Arguments

:: (GPump s f, Applicative m) 
=> (forall a. f a -> m a)

How to remove the f wrapper from every child field of Pump s f.

-> Pump s f 
-> m s 

Remove the Pump wraper around s.

See the documentation for Pump for more details.

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 = Bar Int Bool

The Fields constraint behaves like this:

Fields c Bar  ==  (c Int, c Bool)

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 (f Int) (f Bool)

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 (Show) statement doesn't work, and you need to rely on the 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 (f Int), Show (f Bool)) => 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 (f Int) (f Bool)
  deriving (Generic)

deriving instance Fields Show (Foo f) => Show (Foo f)

type family GFields (c :: kc -> Constraint) (s :: ks -> *) :: 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.

Equations

GFields _ V1 = () 
GFields _ U1 = () 
GFields c (K1 _ a) = c a 
GFields c (M1 _ _ s) = GFields c s 
GFields c (sl :*: sr) = (GFields c sl, GFields c sr) 
GFields c (sl :+: sr) = (GFields c sl, GFields c sr) 

type family FieldsF (c :: k -> Constraint) (r :: (k -> *) -> *) :: 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 (f Int) (f Bool)

If, for example, you intend to implement a Flayable c (Foo f) (Foo g) f g instance, then constraints c Int and c Bool will propagate. However, instead of writing (c Int, c Bool), you can write FieldsF c Foo and achieve the same, which will reduce boilerplate significantly in cases where the number of types contained in f is larger. That is:

forall (c :: * -> Constraint).
   FieldsF c Foo  ==  (c Int, c Bool)

Notice that FieldsF only works with types of kind (k -> *) -> * such as Foo. 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 -> *) (f :: k -> *) :: 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.

Equations

GFieldsF _ V1 _ = () 
GFieldsF _ U1 _ = () 
GFieldsF c (K1 _ (f a)) f = c a 
GFieldsF c (K1 _ _) f = () 
GFieldsF c (M1 _ _ s) f = GFieldsF c s f 
GFieldsF c (sl :*: sr) f = (GFieldsF c sl f, GFieldsF c sr f) 
GFieldsF c (sl :+: sr) f = (GFieldsF c sl f, GFieldsF c sr f) 

Re-exports

data Dict a where #

Values of type Dict p capture a dictionary for a constraint of type p.

e.g.

Dict :: Dict (Eq Int)

captures a dictionary that proves we have an:

instance Eq 'Int

Pattern matching on the Dict constructor will bring this instance into scope.

Constructors

Dict :: Dict a 
Instances
a :=> (Read (Dict a)) 
Instance details

Methods

ins :: a :- Read (Dict a) #

a :=> (Monoid (Dict a)) 
Instance details

Methods

ins :: a :- Monoid (Dict a) #

a :=> (Enum (Dict a)) 
Instance details

Methods

ins :: a :- Enum (Dict a) #

a :=> (Bounded (Dict a)) 
Instance details

Methods

ins :: a :- Bounded (Dict a) #

() :=> (Eq (Dict a)) 
Instance details

Methods

ins :: () :- Eq (Dict a) #

() :=> (Ord (Dict a)) 
Instance details

Methods

ins :: () :- Ord (Dict a) #

() :=> (Show (Dict a)) 
Instance details

Methods

ins :: () :- Show (Dict a) #

() :=> (Semigroup (Dict a)) 
Instance details

Methods

ins :: () :- Semigroup (Dict a) #

a => Bounded (Dict a) 
Instance details

Methods

minBound :: Dict a #

maxBound :: Dict a #

a => Enum (Dict a) 
Instance details

Methods

succ :: Dict a -> Dict a #

pred :: Dict a -> Dict a #

toEnum :: Int -> Dict a #

fromEnum :: Dict a -> Int #

enumFrom :: Dict a -> [Dict a] #

enumFromThen :: Dict a -> Dict a -> [Dict a] #

enumFromTo :: Dict a -> Dict a -> [Dict a] #

enumFromThenTo :: Dict a -> Dict a -> Dict a -> [Dict a] #

Eq (Dict a) 
Instance details

Methods

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

(/=) :: Dict a -> Dict a -> Bool #

(Typeable p, p) => Data (Dict p) 
Instance details

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 :: (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) #

Ord (Dict a) 
Instance details

Methods

compare :: Dict a -> Dict a -> Ordering #

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

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

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

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

max :: Dict a -> Dict a -> Dict a #

min :: Dict a -> Dict a -> Dict a #

a => Read (Dict a) 
Instance details
Show (Dict a) 
Instance details

Methods

showsPrec :: Int -> Dict a -> ShowS #

show :: Dict a -> String #

showList :: [Dict a] -> ShowS #

Semigroup (Dict a) 
Instance details

Methods

(<>) :: Dict a -> Dict a -> Dict a #

sconcat :: NonEmpty (Dict a) -> Dict a #

stimes :: Integral b => b -> Dict a -> Dict a #

a => Monoid (Dict a) 
Instance details

Methods

mempty :: Dict a #

mappend :: Dict a -> Dict a -> Dict a #

mconcat :: [Dict a] -> Dict a #

NFData (Dict c) 
Instance details

Methods

rnf :: Dict c -> () #