free-applicative-t-0.1.0.0: Free Applicative Transformer
Safe HaskellSafe-Inferred
LanguageHaskell2010

Control.Applicative.Trans.FreeAp

Description

Applicative functor transformers, like monad transformers, for free.

Synopsis

Documentation

data ApT f g x Source #

ApT f is a "free" "applicative transformer", in the same sense FreeT f is a free monad transformer.

"Applicative transformer"

Being an "applicative transformer" means these two things:

  • Applying ApT f to an applicative functor g constructs a new applicative functor ApT f g.
  • Using liftT, you can lift an action of g to the action of ApT f g.

    liftT :: g x -> ApT f g x

    liftT is an applicative transformation. In other words, liftT preserves pure 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 of f a into an action of ApT f g a.

    liftF :: (Applicative g) => f a -> ApT f g a

    Because ApT f g is also an applicative transformer on g, it has a way to lift g too.

    liftT :: g x -> ApT f g x
  • Suppose another applicative functor h is capable of lifting both f and g to h.

    fh :: f a -> h a
    gh :: g a -> h a

    ApT f g is the universal applicative among them. There's foldApT to construct the applicative transformation from ApT f g to h, without losing how to lift f and g.

    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 lifting f and/or g then combining them together by Applicative operation <*>.

    It means any applicative transformation run :: forall a. ApT f g a -> h a which satisfies run . liftF = fh and run . liftT = gh is equivalent to foldApT fh gh.

Constructors

PureT (g x) 
forall a b c. ApT (a -> b -> c -> x) (g a) (f b) (ApT f g c) 

Instances

Instances details
(Foldable f, Foldable g) => Foldable (ApT f g) Source # 
Instance details

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 #

toList :: ApT f g a -> [a] #

null :: ApT f g a -> Bool #

length :: ApT f g a -> Int #

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 #

sum :: Num a => ApT f g a -> a #

product :: Num a => ApT f g a -> a #

(Eq1 f, Eq1 g) => Eq1 (ApT f g) Source # 
Instance details

Defined in Control.Applicative.Trans.FreeAp

Methods

liftEq :: (a -> b -> Bool) -> ApT f g a -> ApT f g b -> Bool #

(Ord1 f, Ord1 g) => Ord1 (ApT f g) Source # 
Instance details

Defined in Control.Applicative.Trans.FreeAp

Methods

liftCompare :: (a -> b -> Ordering) -> ApT f g a -> ApT f g b -> Ordering #

(Traversable f, Show (f Int), Traversable g, Show (g Int)) => Show1 (ApT f g) Source # 
Instance details

Defined in Control.Applicative.Trans.FreeAp

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> ApT f g a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [ApT f g a] -> ShowS #

(Traversable f, Traversable g) => Traversable (ApT f g) Source # 
Instance details

Defined in Control.Applicative.Trans.FreeAp

Methods

traverse :: Applicative f0 => (a -> f0 b) -> ApT f g a -> f0 (ApT f g b) #

sequenceA :: Applicative f0 => ApT f g (f0 a) -> f0 (ApT f g a) #

mapM :: Monad m => (a -> m b) -> ApT f g a -> m (ApT f g b) #

sequence :: Monad m => ApT f g (m a) -> m (ApT f g a) #

Applicative g => Applicative (ApT f g) Source # 
Instance details

Defined in Control.Applicative.Trans.FreeAp

Methods

pure :: a -> ApT f g a #

(<*>) :: ApT f g (a -> b) -> ApT f g a -> ApT f g b #

liftA2 :: (a -> b -> c) -> ApT f g a -> ApT f g b -> ApT f g c #

(*>) :: ApT f g a -> ApT f g b -> ApT f g b #

(<*) :: ApT f g a -> ApT f g b -> ApT f g a #

Functor g => Functor (ApT f g) Source # 
Instance details

Defined in Control.Applicative.Trans.FreeAp

Methods

fmap :: (a -> b) -> ApT f g a -> ApT f g b #

(<$) :: a -> ApT f g b -> ApT f g a #

(Traversable f, Show (f Int), Traversable g, Show (g Int), Show a) => Show (ApT f g a) Source # 
Instance details

Defined in Control.Applicative.Trans.FreeAp

Methods

showsPrec :: Int -> ApT f g a -> ShowS #

show :: ApT f g a -> String #

showList :: [ApT f g a] -> ShowS #

(Eq1 f, Eq1 g, Eq a) => Eq (ApT f g a) Source # 
Instance details

Defined in Control.Applicative.Trans.FreeAp

Methods

(==) :: ApT f g a -> ApT f g a -> Bool #

(/=) :: ApT f g a -> ApT f g a -> Bool #

(Ord1 f, Ord1 g, Ord a) => Ord (ApT f g a) Source # 
Instance details

Defined in Control.Applicative.Trans.FreeAp

Methods

compare :: ApT f g a -> ApT f g a -> Ordering #

(<) :: ApT f g a -> ApT f g a -> Bool #

(<=) :: ApT f g a -> ApT f g a -> Bool #

(>) :: ApT f g a -> ApT f g a -> Bool #

(>=) :: ApT f g a -> ApT f g a -> Bool #

max :: ApT f g a -> ApT f g a -> ApT f g a #

min :: ApT f g a -> ApT f g a -> ApT f g a #

toFree :: ApT f Identity a -> Ap f a Source #

When the base applicative is Identity, ApT f Identity is the free applicative Ap.

fromFree :: Ap f a -> ApT f Identity a Source #

Inverse of toFree.

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

liftT :: g x -> ApT f g x Source #

Lift an applicative action g 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 #

Interpret ApT f g into an applicative h.

When g is an Applicative and gh :: forall a. g a -> h a is an applicative transformation, foldApT fh gh is an applicative transformation too.

foldApT satisfy the following equations with liftF and liftT.

foldApT fh gh . liftF = fh
foldApT fh gh . liftT = gh

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 Const m, except m 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.

data ApIx f g where Source #

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])

Constructors

PureIx :: g Int -> ApIx f g 
ApIx :: g Int -> f Int -> ApIx f g -> ApIx f g 

Instances

Instances details
(Show (f Int), Show (g Int)) => Show (ApIx f g) Source # 
Instance details

Defined in Control.Applicative.Trans.FreeAp

Methods

showsPrec :: Int -> ApIx f g -> ShowS #

show :: ApIx f g -> String #

showList :: [ApIx f g] -> ShowS #

(Eq (f Int), Eq (g Int)) => Eq (ApIx f g) Source # 
Instance details

Defined in Control.Applicative.Trans.FreeAp

Methods

(==) :: ApIx f g -> ApIx f g -> Bool #

(/=) :: ApIx f g -> ApIx f g -> Bool #

(Ord (f Int), Ord (g Int)) => Ord (ApIx f g) Source # 
Instance details

Defined in Control.Applicative.Trans.FreeAp

Methods

compare :: ApIx f g -> ApIx f g -> Ordering #

(<) :: ApIx f g -> ApIx f g -> Bool #

(<=) :: ApIx f g -> ApIx f g -> Bool #

(>) :: ApIx f g -> ApIx f g -> Bool #

(>=) :: ApIx f g -> ApIx f g -> Bool #

max :: ApIx f g -> ApIx f g -> ApIx f g #

min :: ApIx f g -> ApIx f g -> ApIx f g #

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.