Skip to content

Commit

Permalink
distributed documentation, code cleanup in prep for released
Browse files Browse the repository at this point in the history
  • Loading branch information
ekmett committed Aug 6, 2012
1 parent 88a17d4 commit 2c83346
Show file tree
Hide file tree
Showing 11 changed files with 123 additions and 250 deletions.
125 changes: 6 additions & 119 deletions lens.cabal
Expand Up @@ -13,124 +13,11 @@ copyright: Copyright (C) 2012 Edward A. Kmett
synopsis: Lenses, Folds and Traversals
description:
The combinators in @Control.Lens@ provide a highly generic toolbox for composing
families of getters, folds, traversals, setters and lenses.
.
/Getter/
.
A @'Getter' a c@ is just any function @(a -> c)@, which we've flipped into continuation
passing style, @(c -> r) -> a -> r@ and decorated with a renamed 'Const' to obtain
.
> newtype Accessor r a = Accessor r
.
to obtain
.
> type Getting r a b c d = (c -> Accessor r d) -> a -> Accessor r b
.
If we restrict access to knowledge about the type 'r' and can work for any d and b, we get:
.
> type Getter a c = forall r b d. Getting r a b c d
.
(NB: We actually hide the use of 'Accessor' behind a class 'Gettable' to error messages from
type class resolution rather than at unification time, where they are much uglier).
.
> type Getter a c = forall f b d. Gettable f => (c -> f d) -> a -> f b
.
Everything you can do with a function, you can do with a 'Getter', but note that because of the
continuation passing style @(.)@ composes them in the opposite order.
.
Since it is only a function, every 'Getter' obviously only retrieves a single value for a given
input.
.
/Fold/
.
A @'Fold' a c@ is a generalization of something 'Foldable'. It allows you to
extract multiple results from a container. A 'Foldable' container can be
characterized by the behavior of @foldMap :: (Foldable t, Monoid m) => (c -> m) -> t c -> m@.
Since we want to be able to work with monomorphic containers, we generalize this signature to
@forall m. 'Monoid' m => (c -> m) -> a -> m@, and then decorate it with 'Const' to obtain
.
> type Fold a c = forall m b d. Monoid m => Getting m a b c d
.
Every 'Getter' is a valid 'Fold' that simply doesn't use the 'Monoid' it is passed.
.
Everything you can do with a 'Foldable' container, you can with with a 'Fold' and there are
combinators that generalize the usual 'Foldable' operations in @Control.Lens@.
.
/Traversal/
.
A @'Traversal' a b c d@ is a generalization of 'traverse' from 'Traversable'. It allows
you to traverse over a structure and change out its contents with monadic or
applicative side-effects. Starting from
@'traverse' :: ('Traversable' t, 'Applicative' f) => (c -> f d) -> t c -> f (t d)@,
we monomorphize the contents and result to obtain
.
> type Traversal a b c d = forall f. Applicative f => (c -> f d) -> a -> f b
.
While a 'Traversal' isn't quite a 'Fold', it _can_ be used for 'Getting' like a 'Fold', because
given a 'Monoid' @m@, we have an 'Applicative' for @('Const' m)@.
.
Everything you can do with a 'Traversable' container, you can with with a 'Traversal', and there
are combinators that generalize the usual 'Traversable' operations in @Control.Lens@.
.
/Setter/
.
A @'Setter' a b c d@ is a generalization of 'fmap' from 'Functor'. It allows you to map into a
structure and change out the contents, but it isn't strong enough to allow you to
enumerate those contents. Starting with @fmap :: 'Functor' f => (c -> d) -> f c -> f d@
we monomorphize the type to obtain @(c -> d) -> a -> b@ and then decorate it with 'Identity' to obtain
.
> type Setter a b c d = (c -> Identity d) -> a -> Identity b
.
Every 'Traversal' is a valid 'Setter', since 'Identity' is 'Applicative'.
.
Everything you can do with a 'Functor', you can do with a 'Setter', and there are combinators that
generalize the usual 'Functor' operations in @Control.Lens@.
.
/Lens/
.
A @'Lens' a b c d@ is a purely functional reference.
.
While a 'Traversal' could be used for 'Getting' like a valid 'Fold', it wasn't a valid 'Getter'.
To make the 'Applicative' for 'Const' it required a 'Monoid' for the argument we passed it, which
a 'Getter' doesn't recieve.
.
However, the instance of 'Functor' for 'Const' requires no such thing. If we weaken the type
requirement from 'Applicative' to 'Functor' for 'Traversal', we obtain
.
> type Lens a b c d = forall f. Functor f => (c -> f d) -> a -> f b
.
Every 'Lens' is a valid 'Setter', choosing @f@ = 'Identity'.
.
Every 'Lens' can be used for 'Getting' like a 'Fold' that doesn't use the 'Monoid' it is passed.
.
Every 'Lens' is a valid 'Traversal' that only uses the 'Functor' part of the 'Applicative' it is supplied.
.
Every 'Lens' can be used for 'Getting' like a valid 'Getter', choosing @f@ = 'Const' @r@ for an appropriate @r@
.
Since every 'Lens' can be used for 'Getting' like a valid 'Getter' it follows that it must view exactly one
element in the structure.
.
The lens laws follow from this property and the desire for it to act like a 'Functor' when used as a 'Setter'.
.
/Isomorphisms and Iso/
.
Control.Isomorphic provides easy overloading of function application for isomorphisms and @Iso a b c d@ uses it
to form isomorphism families that can be composed with other isomorphisms and with lenses, setters, folds,
traversals and getters.
.
> type Iso a b c d = forall k f. (Isomorphic k, Functor f) => k (c -> f d) (a -> f b)
.
/Composition/
.
Note that all of these types are type aliases, and you can compose these lenses with mere function compositon.
.
This is a generalization of the well-known trick for @(.).(.)@ or @fmap.fmap@, and their less well-known cousins
@foldMap.foldMap@ @traverse.traverse@. It follows because each one is a function between values of type @(x -> f y)@
and the composition takes the intersection of supplied functionality for you automatically!
families of getters, folds, isomorphisms, traversals, setters and lenses and their indexed variants.
.
/Lens Families/
.
For a longer description of why you should care about lenses, and an overview of why we use 4
For a longer description of why you should care about lens families, and an overview of why we use 4
parameters a, b, c, and d instead of just 2, see <http://comonad.com/reader/2012/mirrored-lenses/>.
.
Sometimes you won't need the flexibility those extra parameters afford you and you can use
Expand All @@ -151,9 +38,9 @@ description:
.
/Deriving Lenses/
.
You can derive lenses automatically for many data types using 'Control.Lens.TH', and if a
container is fully characterized by its lenses, you can use 'Control.Lens.Representable' to
automatically derive 'Functor', 'Applicative', 'Monad', and 'Derivable'.
You can derive lenses automatically for many data types using 'makeLenses', and if a
container is fully characterized by its lenses, you can use 'Representable' to
automatically derive 'Functor', 'Applicative', 'Monad', and 'Distributive'.

build-type: Simple
tested-with: GHC == 7.4.1
Expand All @@ -168,7 +55,7 @@ library
base >= 4.3 && < 5,
containers >= 0.4.2 && < 0.6,
mtl >= 2.0.1 && < 2.2,
template-haskell >= 2.4 && < 2.8,
template-haskell >= 2.4 && < 2.8,
transformers >= 0.3 && < 0.4

exposed-modules: Control.Exception.Lens
Expand Down
43 changes: 28 additions & 15 deletions src/Control/Lens/Fold.hs
@@ -1,8 +1,5 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE Rank2Types #-}
{-# LANGUAGE LiberalTypeSynonyms #-}
{-# LANGUAGE FlexibleContexts #-}
-----------------------------------------------------------------------------
-- |
-- Module : Control.Lens.Fold
Expand All @@ -12,26 +9,36 @@
-- Stability : provisional
-- Portability : Rank2Types
--
-- A @'Fold' a c@ is a generalization of something 'Foldable'. It allows you to
-- extract multiple results from a container. A 'Foldable' container can be
-- characterized by the behavior of @foldMap :: (Foldable t, Monoid m) => (c -> m) -> t c -> m@.
-- Since we want to be able to work with monomorphic containers, we generalize this signature to
-- @forall m. 'Monoid' m => (c -> m) -> a -> m@, and then decorate it with 'Const' to obtain
--
-- > type Fold a c = forall m b d. Monoid m => Getting m a b c d
--
-- Every 'Getter' is a valid 'Fold' that simply doesn't use the 'Monoid' it is passed.
--
-- Everything you can do with a 'Foldable' container, you can with with a 'Fold' and there are
-- combinators that generalize the usual 'Foldable' operations in @Control.Lens@.
----------------------------------------------------------------------------
module Control.Lens.Fold
(
-- * Folds
Fold

-- ** Building Folds
, folds
, folding
, folded
, unfolded
, iterated
, filtered
-- , reversed
, reversed
, repeated
, replicated
, cycled
, takingWhile
, droppingWhile

-- ** Folding
, foldMapOf, foldOf
, foldrOf, foldlOf
Expand All @@ -56,8 +63,10 @@ module Control.Lens.Fold
) where

import Control.Applicative as Applicative
import Control.Applicative.Backwards
import Control.Lens.Getter
import Control.Lens.Internal
import Control.Lens.Type
import Control.Monad
import Data.Foldable as Foldable
import Data.Maybe
Expand Down Expand Up @@ -151,17 +160,21 @@ filtered :: Monoid r => (c -> Bool) -> Getting r a b c d -> Getting r a b c d
filtered p l f = l $ \c -> if p c then f c else Accessor mempty
{-# INLINE filtered #-}

{-
-- | Obtain a 'Fold' by reversing the order of traversal for a 'Lens', 'Iso', 'Getter', 'Fold' or 'Traversal'.
-- | This allows you to 'traverse' the elements of a 'Traversal' in the
-- opposite order.
--
-- It can also be used to reverse a 'Fold' (or 'Getter') and produce a 'Fold'
-- (or 'Getter').
--
-- Of course, reversing a 'Lens', 'Iso' or 'Getter' has no effect.
reversed :: Getting (Dual r) a b c d -> Getting r a b c d
reversed l f = Accessor . getDual . runAccessor . l (Accesor . Dual . runAccessor . f)
-- This requires at least a 'Traversal' (or 'Lens') and can produce a
-- 'Traversal' (or 'Lens') in turn.
--
-- A 'reversed' 'Iso' is the same 'Iso'. If you reverse the direction of
-- the isomorphism use 'from' instead.
reversed :: LensLike (Backwards f) a b c d -> LensLike f a b c d
reversed l f = forwards . l (Backwards . f)
-- reversed l f = Accessor . getDual . runAccessor . l (Accesor . Dual . runAccessor . f)
{-# INLINE reversed #-}
-}

--taking :: Int -> Getting (Taking m) a b c d -> Getting m a b c d
--dropping :: Int -> Getting (Dropping m) a b c d -> Getting m a b c d

-- | Obtain a 'Fold' by taking elements from another 'Fold', 'Lens', 'Iso', 'Getter' or 'Traversal' while a predicate holds.
--
Expand Down
21 changes: 7 additions & 14 deletions src/Control/Lens/Getter.hs
@@ -1,7 +1,4 @@
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE Rank2Types #-}
{-# LANGUAGE LiberalTypeSynonyms #-}
{-# LANGUAGE FlexibleContexts #-}
-----------------------------------------------------------------------------
-- |
-- Module : Control.Lens.Getter
Expand Down Expand Up @@ -53,6 +50,7 @@ module Control.Lens.Getter

import Control.Applicative
import Control.Applicative.Backwards
import Control.Lens.Internal
import Control.Monad.Reader.Class as Reader
import Control.Monad.State.Class as State
import Data.Functor.Compose
Expand All @@ -72,17 +70,6 @@ infixr 0 ^$
-- there are no lens laws that can be applied to it.
--
-- Moreover, a 'Getter' can be used directly as a 'Fold', since it just ignores the 'Monoid'.
--
-- In practice the @b@ and @d@ are left dangling and unused, and as such is no real point in
-- using a @'Simple' 'Getter'@.
--
-- > type Getter a c = forall r. Applicative m => LensLike f a b c d
--
-- A simpler version of this type would be
--
-- > type BadGetter a c = LensLike (Const r) a b c d
--
-- but then a 'Getter' would not be able to compose with many combinators.
type Getter a c = forall f b d. Gettable f => (c -> f d) -> a -> f b

-- | Build a 'Getter' from an arbitrary Haskell function.
Expand Down Expand Up @@ -124,6 +111,12 @@ instance Gettable f => Gettable (Backwards f) where
instance (Functor f, Gettable g) => Gettable (Compose f g) where
coerce = Compose . fmap coerce . getCompose

instance Gettable f => Gettable (ElementOf f) where
coerce (ElementOf m) = ElementOf $ \i -> case m i of
Searching _ _ -> NotFound "coerced while searching"
Found j as -> Found j (coerce as)
NotFound s -> NotFound s

-- | Used instead of Const to report 'no instance of (Settable Accessor)' when
-- attempting to misuse a 'Setter' as a 'Getter'.
newtype Accessor r a = Accessor { runAccessor :: r }
Expand Down
13 changes: 9 additions & 4 deletions src/Control/Lens/Internal.hs
Expand Up @@ -124,26 +124,31 @@ getMax (Max a) = Just a
data ElementOfResult f a
= Searching {-# UNPACK #-} !Int a
| Found {-# UNPACK #-} !Int (f a)
| NotFound String

instance Functor f => Functor (ElementOfResult f) where
fmap f (Searching i a) = Searching i (f a)
fmap f (Found i as) = Found i (fmap f as)
fmap _ (NotFound e) = NotFound e

-- | Used to find the nth element of a 'Traversal'.
data ElementOf f a = ElementOf { getElementOf :: Int -> ElementOfResult f a }

instance Functor f => Functor (ElementOf f) where
fmap f (ElementOf m) = ElementOf $ \i -> case m i of
Searching j a -> Searching j (f a)
Found j as -> Found j (fmap f as)
Found j as -> Found j (fmap f as)
NotFound e -> NotFound e

instance Functor f => Applicative (ElementOf f) where
pure a = ElementOf $ \i -> Searching i a
ElementOf mf <*> ElementOf ma = ElementOf $ \i -> case mf i of
Found j ff -> case ma j of
Found _ _ -> error "elementOf: found multiple results"
Found _ _ -> NotFound "multiple results"
Searching k a -> Found k (fmap ($a) ff)
NotFound e -> NotFound e
Searching j f -> case ma j of
Found k as -> Found k (fmap f as)
Found k as -> Found k (fmap f as)
Searching k a -> Searching k (f a)

NotFound e -> NotFound e
NotFound e -> NotFound e
3 changes: 0 additions & 3 deletions src/Control/Lens/Representable.hs
@@ -1,5 +1,4 @@
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeOperators #-}
-----------------------------------------------------------------------------
-- |
-- Module : Control.Lens.Representable
Expand All @@ -19,8 +18,6 @@
-- Consider the following example.
--
-- > import Control.Lens
-- > import Control.Lens.Representable
-- > import Control.Lens.TH
-- > import Data.Distributive
--
-- > data Pair a = Pair { _x :: a, _y :: a }
Expand Down

0 comments on commit 2c83346

Please sign in to comment.