freer-indexed-0.1.0.0: Freer indexed monad for type-level resource-aware effectual operations.

Copyright(c) Evgeny Poberezkin
LicenseBSD3
Maintainerevgeny@poberezkin.com
Stabilityexperimental
Portabilitynon-portable
Safe HaskellSafe
LanguageHaskell2010

Control.XApplicative

Contents

Description

This module describes an intermediate type class between a functor and an indexed monad XMonad - an indexed applicative.

Synopsis

XApplicative

class (forall p q. Functor (f p q)) => XApplicative f where Source #

A poly-kinded type-parameterized (indexed) functor with application, with operations to

  • embed pure expressions (xpure), and
  • sequence computations and combine their results (<*>: and xliftA2).

These functors have kind r -> r -> Type -> Type, where the kind equality of the of the first and the second type parameters is implied from chaining.

A minimal complete definition must include implementations of xpure and of either <*>: or xliftA2. If it defines both, then they must behave the same as their default definitions:

(<*>:) = xliftA2 id
liftA2 f x y = f <$> x <*>: y

The definition must satisfy the same laws as Applicative:

Identity
xpure id <*>: v = v
Composition
xpure (.) <*>: u <*>: v <*>: w = u <*>: (v <*>: w)
Homomorphism
xpure f <*>: xpure x = xpure (f x)
Interchange
u <*>: xpure y = xpure ($ y) <*>: u

The other methods have the following default definitions:

The Functor instance for f p q will satisfy

If f is also an XMonad, it should satisfy

Minimal complete definition

xpure, ((<*>:) | xliftA2)

Methods

xpure :: a -> f p p a Source #

Lift a value.

(<*>:) :: f p q (a -> b) -> f q r a -> f p r b infixl 4 Source #

Sequential application.

xliftA2 :: (a -> b -> c) -> f p q a -> f q r b -> f p r c Source #

Lift a binary function to type-parameterized actions.

If fmap is an expensive operation, it is likely better to use xliftA2 than to fmap over the structure and then use <*>:.

(*>:) :: f p q a -> f q r b -> f p r b infixl 4 Source #

Sequence actions, discarding the value of the first argument.

(<*:) :: f p q a -> f q r b -> f p r a infixl 4 Source #

Sequence actions, discarding the value of the second argument.

Instances
XApplicative (XFree f :: k -> k -> Type -> Type) Source # 
Instance details

Defined in Control.XFreer

Methods

xpure :: a -> XFree f p p a Source #

(<*>:) :: XFree f p q (a -> b) -> XFree f q r a -> XFree f p r b Source #

xliftA2 :: (a -> b -> c) -> XFree f p q a -> XFree f q r b -> XFree f p r c Source #

(*>:) :: XFree f p q a -> XFree f q r b -> XFree f p r b Source #

(<*:) :: XFree f p q a -> XFree f q r b -> XFree f p r a Source #

Functions

(<**>:) :: XApplicative f => f p q a -> f q r (a -> b) -> f p r b infixl 4 Source #

A variant of <*>: with the arguments reversed.

xliftA :: XApplicative f => (a -> b) -> f p q a -> f p q b Source #

Lift a function to actions. This function may be used as a value for fmap in a Functor instance.

xliftA3 :: XApplicative f => (a -> b -> c -> d) -> f p q a -> f q r b -> f r l c -> f p l d Source #

Lift a ternary function to actions.