ap-normalize-0.1.0.0: Self-normalizing applicative expressions

Safe HaskellSafe
LanguageHaskell2010

ApNormalize

Contents

Description

Normalizing applicative functors

Normalize applicative expressions by simplifying intermediate pure and (<$>) and reassociating (<*>).

This works by transforming the underlying applicative functor into one whose operations (pure, (<$>), (<*>)) reassociate themselves by inlining and beta-reduction.

It relies entirely on GHC's simplifier. No rewrite rules, no Template Haskell, no plugins.

Example

In the following traversal, one of the actions is pure b, which can be simplified in principle, but only assuming the applicative functor laws. As far as GHC is concerned, pure, (<$>), and (<*>) are completely opaque because f is abstract, so it cannot simplify this expression.

data Example a = Example a Bool [a] (Example a)

traverseE :: Applicative f => (a -> f b) -> Example a -> f (Example b)
traverseE go (Example a b c d) =
  Example
    <$> go a
    <*> pure b
    <*> traverse go c
    <*> traverseE go d
  -- 1 <$>, 3 <*>

Using this library, we can compose actions in a specialized applicative functor Aps f, keeping the code in roughly the same structure. In the following snippet, identifiers exported by the library are highlighted.

traverseE :: Applicative f => (a -> f b) -> Example a -> f (Example b)
traverseE go (Example a b c d) =
  Example
    <$>^ go a
    <*>  pure b
    <*>^ traverse go c
    <*>^ traverseE go d
    & lowerAps
  -- 1 <$>, 3 <*>

GHC simplifies that traversal to the following, using only two combinators in total.

traverseE :: Applicative f => (a -> f b) -> Example a -> f (Example b)
traverseE go (Example a b c d) =
  liftA2 (\a' -> Example a' b)
    (go a)
    (traverse go c)
    <*> traverseE go d
  -- 1 liftA2, 1 <*>

The following example with a tree-shaped structure also reduces to the same list-shaped expression above.

traverseE :: Applicative f => (a -> f b) -> Example a -> f (Example b)
traverseE go (Example a b c d) =
  (\((a', b'), (c', d')) -> Example a' b' c' d')
    <$> ((,) <$> ((,) <$>^ go a
                      <*>  pure b)
             <*> ((,) <$>^ traverse go c
                      <*>^ traverseE go d))
    & lowerAps
  -- 4 <$>, 3 <*>

Such structure occurs when using an intermediate definition (which itself uses the applicative operators) as the right operand of (<$>) or (<*>). This could also be found in a naive generic implementation of traverse using GHC.Generics.

Usage

The main idea is to compose applicative actions not directly in your applicative functor f, but in a transformed one Aps f.

  • Send actions from f into Aps f using liftAps.
  • pure actions lift themselves already: pure x can be specialized to both f and Aps f.
  • Compose actions in Aps f using applicative combinators such as (<$>), (<*>), and liftA2.
  • Move back from Aps f to f using lowerAps.

The shorthands (<$>^) and (<*>^) can be used instead of (<$>) and (<*>) with a neighboring liftAps.

Definitions in Aps f should not be recursive, since this relies on inlining, and recursive functions are not inlined by GHC.

Synopsis

Interface

data Aps f a Source #

An applicative functor transformer which accumulates f-actions (things of type f x) in a normal form.

It constructs a value of type f a with the following syntactic invariant. It depends on the number of f-actions a1 ... an composing it, which are delimited using liftAps:

  • Zero action: pure x
  • One action: f <$> a1
  • Two or more actions: liftA2 f a1 a2 <*> a3 <*> ... <*> an
Instances
Functor (Aps f) Source # 
Instance details

Defined in ApNormalize.Aps

Methods

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

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

Applicative f => Applicative (Aps f) Source # 
Instance details

Defined in ApNormalize.Aps

Methods

pure :: a -> Aps f a #

(<*>) :: Aps f (a -> b) -> Aps f a -> Aps f b #

liftA2 :: (a -> b -> c) -> Aps f a -> Aps f b -> Aps f c #

(*>) :: Aps f a -> Aps f b -> Aps f b #

(<*) :: Aps f a -> Aps f b -> Aps f a #

(<$>^) :: (a -> b) -> f a -> Aps f b infixl 4 Source #

f <$>^ u :: Aps f b is a delayed representation of f <$> u :: f b, so that it can be fused with other applicative operations.

f <$>^ u is a shorthand for f <$> liftAps u.

(<*>^) :: Applicative f => Aps f (a -> b) -> f a -> Aps f b infixl 4 Source #

u <*>^ v appends an f-action v to the right of an (Aps f)-action u.

u <*>^ v is a shorthand for u <*> liftAps v.

liftAps :: f a -> Aps f a Source #

Lift an f-action into Aps f.

lowerAps :: Applicative f => Aps f a -> f a Source #

Lower an f-action from Aps f.

Reexported from Data.Function

For convenience, to append ... & lowerAps to the end of an applicative expression.

(&) :: a -> (a -> b) -> b infixl 1 #

& is a reverse application operator. This provides notational convenience. Its precedence is one higher than that of the forward application operator $, which allows & to be nested in $.

>>> 5 & (+1) & show
"6"

Since: base-4.8.0.0