comments for Applicative and Traversable
[ghc-base.git] / Data / Traversable.hs
1 -----------------------------------------------------------------------------
2 -- |
3 -- Module      :  Data.Traversable
4 -- Copyright   :  Conor McBride and Ross Paterson 2005
5 -- License     :  BSD-style (see the LICENSE file in the distribution)
6 --
7 -- Maintainer  :  ross@soi.city.ac.uk
8 -- Stability   :  experimental
9 -- Portability :  portable
10 --
11 -- Class of data structures that can be traversed from left to right.
12 --
13 -- See also
14 --
15 --  * /Applicative Programming with Effects/,
16 --    by Conor McBride and Ross Paterson, online at
17 --    <http://www.soi.city.ac.uk/~ross/papers/Applicative.html>.
18 --
19 --  * /The Essence of the Iterator Pattern/,
20 --    by Jeremy Gibbons and Bruno Oliveira,
21 --    in /Mathematically-Structured Functional Programming/, 2006, and online at
22 --    <http://web.comlab.ox.ac.uk/oucl/work/jeremy.gibbons/publications/#iterator>.
23
24 module Data.Traversable (
25         Traversable(..),
26         fmapDefault,
27         foldMapDefault,
28         ) where
29
30 import Prelude hiding (mapM, sequence)
31 import qualified Prelude (mapM)
32 import Control.Applicative
33 import Data.Foldable (Foldable)
34 import Data.Monoid (Monoid)
35 import Data.Array
36
37 -- | Functors representing data structures that can be traversed from
38 -- left to right.
39 --
40 -- Minimal complete definition: 'traverse' or 'sequenceA'.
41 --
42 -- Instances are similar to 'Functor', e.g. given a data type
43 --
44 -- > data Tree a = Empty | Leaf a | Node (Tree a) a (Tree a)
45 --
46 -- a suitable instance would be
47 --
48 -- > instance Traversable Tree
49 -- >    traverse f Empty = pure Empty
50 -- >    traverse f (Leaf x) = Leaf <$> f x
51 -- >    traverse f (Node l k r) = Node <$> traverse f l <*> f k <*> traverse f r
52 --
53 -- This is suitable even for abstract types, as the laws for '<*>'
54 -- imply a form of associativity.
55 --
56 -- The superclass instances should satisfy the following:
57 --
58 --  * In the 'Functor' instance, 'fmap' should be equivalent to traversal
59 --    with the identity applicative functor ('fmapDefault').
60 --
61 --  * In the 'Foldable' instance, 'Data.Foldable.foldMap' should be
62 --    equivalent to traversal with a constant applicative functor
63 --    ('foldMapDefault').
64 --
65 class (Functor t, Foldable t) => Traversable t where
66         -- | Map each element of a structure to an action, evaluate
67         -- these actions from left to right, and collect the results.
68         traverse :: Applicative f => (a -> f b) -> t a -> f (t b)
69         traverse f = sequenceA . fmap f
70
71         -- | Evaluate each action in the structure from left to right,
72         -- and collect the results.
73         sequenceA :: Applicative f => t (f a) -> f (t a)
74         sequenceA = traverse id
75
76         -- | Map each element of a structure to an monadic action, evaluate
77         -- these actions from left to right, and collect the results.
78         mapM :: Monad m => (a -> m b) -> t a -> m (t b)
79         mapM f = unwrapMonad . traverse (WrapMonad . f)
80
81         -- | Evaluate each monadic action in the structure from left to right,
82         -- and collect the results.
83         sequence :: Monad m => t (m a) -> m (t a)
84         sequence = mapM id
85
86 -- instances for Prelude types
87
88 instance Traversable Maybe where
89         traverse f Nothing = pure Nothing
90         traverse f (Just x) = Just <$> f x
91
92 instance Traversable [] where
93         traverse f = foldr cons_f (pure [])
94           where cons_f x ys = (:) <$> f x <*> ys
95
96         mapM = Prelude.mapM
97
98 instance Ix i => Traversable (Array i) where
99         traverse f arr = listArray (bounds arr) <$> traverse f (elems arr)
100
101 -- general functions
102
103 -- | This function may be used as a value for `fmap` in a `Functor` instance.
104 fmapDefault :: Traversable t => (a -> b) -> t a -> t b
105 fmapDefault f = getId . traverse (Id . f)
106
107 -- | This function may be used as a value for `Data.Foldable.foldMap`
108 -- in a `Foldable` instance.
109 foldMapDefault :: (Traversable t, Monoid m) => (a -> m) -> t a -> m
110 foldMapDefault f = getConst . traverse (Const . f)
111
112 -- local instances
113
114 newtype Id a = Id { getId :: a }
115
116 instance Functor Id where
117         fmap f (Id x) = Id (f x)
118
119 instance Applicative Id where
120         pure = Id
121         Id f <*> Id x = Id (f x)