functor-combinators-0.3.6.0: Tools for functor combinator-based program design
Copyright(c) Justin Le 2019
LicenseBSD3
Maintainerjustin@jle.im
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Functor.Apply.Free

Description

The free Apply. Provides Ap1 and various utility methods. See Ap1 for more details.

Ideally Ap1 would be in the free package. However, it is defined here for now.

Synopsis

Documentation

data Ap1 :: (Type -> Type) -> Type -> Type where Source #

One or more fs convolved with itself.

Essentially:

Ap1 f
    ~ f                            -- one f
  :+: (f `Day` f)          -- two f's
  :+: (f `Day` f `Day` f)           -- three f's
  :+: (f `Day` f `Day` f `Day` f)  -- four f's
  :+: ...                          -- etc.

Useful if you want to promote an f to a situation with "at least one f sequenced with itself".

Mostly useful for its HFunctor and Interpret instance, along with its relationship with Ap and Day.

This is the free Apply --- Basically a "non-empty" Ap.

The construction here is based on Ap, similar to now NonEmpty is built on list.

Constructors

Ap1 :: f a -> Ap f (a -> b) -> Ap1 f b 

Bundled Patterns

pattern DayAp1 :: Day f (Ap f) a -> Ap1 f a

An Ap1 f is just a Day f (Ap f). This bidirectional pattern synonym lets you treat it as such.

Instances

Instances details
HBind Ap1 Source # 
Instance details

Defined in Data.Functor.Apply.Free

Methods

hbind :: forall (f :: k -> Type) (g :: k -> Type). (f ~> Ap1 g) -> Ap1 f ~> Ap1 g Source #

hjoin :: forall (f :: k -> Type). Ap1 (Ap1 f) ~> Ap1 f Source #

Inject Ap1 Source # 
Instance details

Defined in Data.Functor.Apply.Free

Methods

inject :: forall (f :: k -> Type). f ~> Ap1 f Source #

FreeOf Apply Ap1 Source # 
Instance details

Defined in Data.HFunctor.Final

Associated Types

type FreeFunctorBy Ap1 :: (Type -> Type) -> Constraint Source #

Methods

fromFree :: forall (f :: Type -> Type). Ap1 f ~> Final Apply f Source #

toFree :: forall (f :: Type -> Type). FreeFunctorBy Ap1 f => Final Apply f ~> Ap1 f Source #

HFunctor Ap1 Source # 
Instance details

Defined in Data.Functor.Apply.Free

Methods

hmap :: forall (f :: k -> Type) (g :: k -> Type). (f ~> g) -> Ap1 f ~> Ap1 g Source #

Apply f => Interpret Ap1 (f :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Apply.Free

Methods

retract :: Ap1 f ~> f Source #

interpret :: forall (g :: k -> Type). (g ~> f) -> Ap1 g ~> f Source #

HTraversable Ap1 Source # 
Instance details

Defined in Data.Functor.Apply.Free

Methods

htraverse :: forall h f g (a :: k). Applicative h => (forall (x :: k). f x -> h (g x)) -> Ap1 f a -> h (Ap1 g a) Source #

HTraversable1 Ap1 Source # 
Instance details

Defined in Data.Functor.Apply.Free

Methods

htraverse1 :: forall h f g (a :: k). Apply h => (forall (x :: k). f x -> h (g x)) -> Ap1 f a -> h (Ap1 g a) Source #

Functor (Ap1 f) Source # 
Instance details

Defined in Data.Functor.Apply.Free

Methods

fmap :: (a -> b) -> Ap1 f a -> Ap1 f b #

(<$) :: a -> Ap1 f b -> Ap1 f a #

Invariant (Ap1 f) Source #

Since: 0.3.0.0

Instance details

Defined in Data.Functor.Apply.Free

Methods

invmap :: (a -> b) -> (b -> a) -> Ap1 f a -> Ap1 f b #

Apply (Ap1 f) Source # 
Instance details

Defined in Data.Functor.Apply.Free

Methods

(<.>) :: Ap1 f (a -> b) -> Ap1 f a -> Ap1 f b #

(.>) :: Ap1 f a -> Ap1 f b -> Ap1 f b #

(<.) :: Ap1 f a -> Ap1 f b -> Ap1 f a #

liftF2 :: (a -> b -> c) -> Ap1 f a -> Ap1 f b -> Ap1 f c #

type FreeFunctorBy Ap1 Source # 
Instance details

Defined in Data.HFunctor.Final

toAp :: Ap1 f ~> Ap f Source #

An Ap1 is a "non-empty" Ap; this function "forgets" the non-empty property and turns it back into a normal Ap.

fromAp :: Ap f ~> (Identity :+: Ap1 f) Source #

Convert an Ap into an Ap1 if possible. If the Ap was "empty", return the Pure value instead.

liftAp1 :: f ~> Ap1 f Source #

Embed an f into Ap1.

retractAp1 :: Apply f => Ap1 f ~> f Source #

Extract the f out of the Ap1.

retractAp1 . liftAp1 == id

runAp1 :: Apply g => (f ~> g) -> Ap1 f ~> g Source #

Interpret an Ap f into some Apply context g.