| Safe Haskell | Safe |
|---|---|
| Language | Haskell2010 |
Flay
Contents
Description
The most commonly used names in this module are intended to be imported unqualified:
import Flay (Flay, Flayable(flay), Dict(Dict))
The rest of the names, qualified:
import qualified Flay
- type Flay c m s t f g = (forall a. Dict (c a) -> f a -> m (g a)) -> s -> m t
- inner :: Flay Trivial Identity s s f f -> s -> s
- outer :: Monad m => Flay Trivial m (m x) (m x) m m -> m x -> m x
- class Flayable c m s t f g | s -> f, t -> g, s g -> t, t f -> s where
- gflay :: (Functor m, GFlay c m s t f g) => Flay c m s t f g
- class (G.Generic s, G.Generic t, GFlay' c m (G.Rep s) (G.Rep t) f g) => GFlay c m s t f g
- class GFlay' c m s t f g where
- class All' cs x => All cs x
- class Trivial a
- trivial :: Flayable Trivial m s t f g => (forall a. Trivial a => f a -> m (g a)) -> s -> m t
- trivial' :: forall m s t f g. Flay Trivial m s t f g -> (forall a. Trivial a => f a -> m (g a)) -> s -> m t
- collect :: (Monoid b, Flayable c (Const b) s t f (Const ())) => (forall a. Dict (c a) -> f a -> b) -> s -> b
- collect' :: Monoid b => Flay c (Const b) s t f (Const ()) -> (forall a. Dict (c a) -> f a -> b) -> s -> b
- data Dict a :: Constraint -> * where
Documentation
type Flay c m s t f g = (forall a. Dict (c a) -> f a -> m (g a)) -> s -> m t Source #
allows converting Flay c m 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 inner identity law (and outer identity law as
well, if the Flay fits the type expected by outer).
When defining Flay values, you should leave c, m, f, and g fully
polymomrphic, as these are the most useful types of Flays.
When using a Flay, m will be required to be a Functor in case the Flay
targets one element, or an Applicative if it targets more than one. There
will be no constraints on the rest of the arguments to Flay.
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 explicitely
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 m s t f g: CoMmon STandard FoG.
Example 1: Removing uncertaininy
Consider the following types and values:
data Foo f = Foo (fInt) (fBool) deriving instance (Show(fInt),Show(fBool)) =>Show(Foo f)
flayFoo :: (Applicativem, cInt, cBool) =>Flayc m (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 constrain 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 escence of Flay: We can work operate 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 m (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 explicitely 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').
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.
inner :: Flay Trivial Identity s s f f -> s -> s Source #
Inner identity law:
(\fl ->runIdentity.trivial'flpure) =id
Flayable
class Flayable c m s t f g | 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, m, f, and g
fully polymomrphic, as these are the most useful types of Flayabless.
Methods
flay :: Flay c m s t f g Source #
If s and g are instances of G.Generic, then flay gets a default
implementation. For example, provided the Foo datatype shown in the
documentation for Flay had a G.Generic instance, then the following
Flayable instance would get a default implementation for flay:
instance (Applicativem, cInt, cBool) =>Flayablec m (Foo f) (Foo g) f g
Notice that while this default definition works for an s having "nested
Flayables", GHC will prompt you for some additional constraints related
to GFlay' in order for it to compile.
flay :: (Functor m, GFlay c m s t f g) => Flay c m s t f g Source #
If s and g are instances of G.Generic, then flay gets a default
implementation. For example, provided the Foo datatype shown in the
documentation for Flay had a G.Generic instance, then the following
Flayable instance would get a default implementation for flay:
instance (Applicativem, cInt, cBool) =>Flayablec m (Foo f) (Foo g) f g
Notice that while this default definition works for an s having "nested
Flayables", GHC will prompt you for some additional constraints related
to GFlay' in order for it to compile.
Generics
class (G.Generic s, G.Generic t, GFlay' c m (G.Rep s) (G.Rep t) f g) => GFlay c m s t f g Source #
Convenience Constraint for satisfying basic GFlay' needs for s and t.
class GFlay' c m s t f g where Source #
Minimal complete definition
Instances
| GFlay' * k c m G.V1 G.V1 f g Source # | |
| (Functor m, GFlay' * k c m s t f g) => GFlay' * k c m (G.Rec1 s) (G.Rec1 t) f g Source # | |
| (Functor m, Flayable c m (f a) (g a) f g) => GFlay' * * c m (G.K1 r (f a)) (G.K1 r (g a)) f g Source # | |
| (Functor m, GFlay' * k c m sl tl f g, GFlay' * k c m sr tr f g) => GFlay' * k c m ((G.:+:) sl sr) ((G.:+:) tl tr) f g Source # | |
| (Applicative m, GFlay' * k c m sl tl f g, GFlay' * k c m sr tr f g) => GFlay' * k c m ((G.:*:) sl sr) ((G.:*:) tl tr) f g Source # | |
| Applicative m => GFlay' * k c m (G.K1 r x) (G.K1 r x) f g Source # | |
| (Functor m, GFlay' * k c m s t f g) => GFlay' * k c m (G.M1 i j s) (G.M1 i j t) f g Source # | |
Utils
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.
Re-exports
data Dict a :: Constraint -> * where #
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:
instance Eq 'Int
Pattern matching on the Dict constructor will bring this instance into scope.
Instances
| a :=> (Read (Dict a)) | |
| a :=> (Monoid (Dict a)) | |
| a :=> (Enum (Dict a)) | |
| a :=> (Bounded (Dict a)) | |
| () :=> (Eq (Dict a)) | |
| () :=> (Ord (Dict a)) | |
| () :=> (Show (Dict a)) | |
| a => Bounded (Dict a) | |
| a => Enum (Dict a) | |
| Eq (Dict a) | |
| (Typeable Constraint p, p) => Data (Dict p) | |
| Ord (Dict a) | |
| a => Read (Dict a) | |
| Show (Dict a) | |
| a => Monoid (Dict a) | |