Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Control.Applicative.Trans.FreeAp
Description
Applicative
functor transformers, like monad transformers, for free.
Synopsis
- data ApT f g x
- toFree :: ApT f Identity a -> Ap f a
- fromFree :: Ap f a -> ApT f Identity a
- transApT :: (forall a. f a -> f' a) -> ApT f g b -> ApT f' g b
- hoistApT :: (forall a. g a -> g' a) -> ApT f g b -> ApT f g' b
- liftF :: Applicative g => f x -> ApT f g x
- liftT :: g x -> ApT f g x
- appendApT :: (a -> b -> c -> x) -> ApT f g a -> f b -> ApT f g c -> ApT f g x
- foldApT :: forall f g h x. Applicative h => (forall a. f a -> h a) -> (forall a. g a -> h a) -> ApT f g x -> h x
- foldApT_ :: forall f g m x. Semigroup m => (forall a. f a -> m) -> (forall a. g a -> m) -> ApT f g x -> m
- fjoinApTLeft :: forall f g x. ApT f (ApT f g) x -> ApT f g x
- fjoinApTRight :: Applicative g => ApT (ApT f g) g x -> ApT f g x
- data ApIx f g where
- fromIx :: Functor g => ApIx f g -> ApT f g Int
- indices :: forall f g x. (Traversable f, Traversable g) => ApT f g x -> ApIx f g
- reconstruct :: (HasCallStack, Foldable f, Foldable g, Functor g) => ApIx f g -> [x] -> ApT f g x
Documentation
is a "free" "applicative transformer", in the same sense
ApT
f
is a free monad transformer.FreeT
f
"Applicative transformer"
Being an "applicative transformer" means these two things:
- Applying
ApT f
to an applicative functorg
constructs a new applicative functorApT f g
. Using
liftT
, you can lift an action ofg
to the action ofApT f g
.liftT :: g x -> ApT f g x
liftT
is an applicative transformation. In other words,liftT
preservespure
and
:<*>
liftT (pure x) = pure x liftT (x <*> y) = liftT x <*> liftT y
"Free" applicative transformer
It's the "free" applicative transformer. It means ApT f g
is the special, the most universal
one among various applicative functors which can lift f
and g
into them.
ApT f g
has a way to lift any value off a
into an action ofApT f g a
.liftF :: (Applicative g) => f a -> ApT f g a
Because
ApT f g
is also an applicative transformer ong
, it has a way to liftg
too.liftT :: g x -> ApT f g x
Suppose another applicative functor
h
is capable of lifting bothf
andg
toh
.fh :: f a -> h a gh :: g a -> h a
ApT f g
is the universal applicative among them. There'sfoldApT
to construct the applicative transformation fromApT f g
toh
, without losing how to liftf
andg
.foldApT :: forall f g h x. Applicative h => (forall a. f a -> h a) -> (forall a. g a -> h a) -> ApT f g x -> h x foldApT fh gh :: forall x. ApT f g x -> h x foldApT fh gh . liftF = fh foldApT fh gh . liftT = gh
ApT f g
contains no extra data that are not from liftingf
and/org
then combining them together byApplicative
operation<*>
.It means any applicative transformation
run :: forall a. ApT f g a -> h a
which satisfiesrun . liftF = fh
andrun . liftT = gh
is equivalent tofoldApT fh gh
.
Instances
(Foldable f, Foldable g) => Foldable (ApT f g) Source # | |
Defined in Control.Applicative.Trans.FreeAp Methods fold :: Monoid m => ApT f g m -> m # foldMap :: Monoid m => (a -> m) -> ApT f g a -> m # foldMap' :: Monoid m => (a -> m) -> ApT f g a -> m # foldr :: (a -> b -> b) -> b -> ApT f g a -> b # foldr' :: (a -> b -> b) -> b -> ApT f g a -> b # foldl :: (b -> a -> b) -> b -> ApT f g a -> b # foldl' :: (b -> a -> b) -> b -> ApT f g a -> b # foldr1 :: (a -> a -> a) -> ApT f g a -> a # foldl1 :: (a -> a -> a) -> ApT f g a -> a # elem :: Eq a => a -> ApT f g a -> Bool # maximum :: Ord a => ApT f g a -> a # minimum :: Ord a => ApT f g a -> a # | |
(Eq1 f, Eq1 g) => Eq1 (ApT f g) Source # | |
(Ord1 f, Ord1 g) => Ord1 (ApT f g) Source # | |
Defined in Control.Applicative.Trans.FreeAp | |
(Traversable f, Show (f Int), Traversable g, Show (g Int)) => Show1 (ApT f g) Source # | |
(Traversable f, Traversable g) => Traversable (ApT f g) Source # | |
Defined in Control.Applicative.Trans.FreeAp | |
Applicative g => Applicative (ApT f g) Source # | |
Functor g => Functor (ApT f g) Source # | |
(Traversable f, Show (f Int), Traversable g, Show (g Int), Show a) => Show (ApT f g a) Source # | |
(Eq1 f, Eq1 g, Eq a) => Eq (ApT f g a) Source # | |
(Ord1 f, Ord1 g, Ord a) => Ord (ApT f g a) Source # | |
Defined in Control.Applicative.Trans.FreeAp |
transApT :: (forall a. f a -> f' a) -> ApT f g b -> ApT f' g b Source #
Lift any natural transformation (forall a. f a -> f' a)
to
an applicative transformation (forall b. ApT f g b -> ApT f' g b)
.
hoistApT :: (forall a. g a -> g' a) -> ApT f g b -> ApT f g' b Source #
Lift an applicative transformation (forall a. g a -> g' a)
to
an applicative transformation (forall b. ApT f g b -> ApT f g' b)
.
liftF :: Applicative g => f x -> ApT f g x Source #
Lift an uninterpreted action f x
to ApT f g x
appendApT :: (a -> b -> c -> x) -> ApT f g a -> f b -> ApT f g c -> ApT f g x Source #
Equivalent to the following definition, but is faster and doesn't require Applicative g
constraint.
appendApT x prefix fb postfix = x <$> prefix <*> liftF fb <*> postfix
foldApT :: forall f g h x. Applicative h => (forall a. f a -> h a) -> (forall a. g a -> h a) -> ApT f g x -> h x Source #
foldApT_ :: forall f g m x. Semigroup m => (forall a. f a -> m) -> (forall a. g a -> m) -> ApT f g x -> m Source #
Perform a monoidal analysis over ApT f g
value.
This is equivalent to use foldApT
with the applicative
,
except Const
mm
doesn't need to be a Monoid
but just a Semigroup
.
fjoinApTLeft :: forall f g x. ApT f (ApT f g) x -> ApT f g x Source #
Collapsing ApT
nested left-to-right.
fjoinApTRight :: Applicative g => ApT (ApT f g) g x -> ApT f g x Source #
Collapsing ApT
nested right-to-left.
Printable value indicating "shape" of ApT f g
functor.
If you forget the data of elements from ApT f g x
, and leave numbers indicating
which index these data was in the ApT f g
, that is ApIx f g
.
>>>
xFn = (\a b c -> if a then show b else c)
>>>
x = ApT xFn [True, False] [10, 20] (PureT ["Moo"])
>>>
toList x
["10", "20", "Moo", "Moo"]
A value of type ApIx [] []
corresponding to x
represents it was made from the three lists
of length 2,2,1
each. In ApIx f g
values, instead of having the original contents, they contain
Int
values to conveniently calculate the indices of the value in toList x
.
>>>
indices x
ApIx [0, 2] [0, 1] (PureIx [0])
fromIx :: Functor g => ApIx f g -> ApT f g Int Source #
Turn a shape value ApIx f g
to the actual ApT f g Int
value
containing indices.
indices :: forall f g x. (Traversable f, Traversable g) => ApT f g x -> ApIx f g Source #
Extract only a shape from ApT f g x
and make it ApIx f g
.
reconstruct :: (HasCallStack, Foldable f, Foldable g, Functor g) => ApIx f g -> [x] -> ApT f g x Source #
Construct an ApT f g x
value from a shape ApIx f g
and a list of values.
For any u :: ApT f g x
, the following property holds.
reconstruct (indices u) (toList u) == u
reconstruct shape xs
raises error
if the length of list xs
does not match
the length calculated from shape
.