add Traversable generalizations of mapAccumL and mapAccumR (#2461)
[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  :  libraries@haskell.org
8 -- Stability   :  experimental
9 -- Portability :  portable
10 --
11 -- Class of data structures that can be traversed from left to right,
12 -- performing an action on each element.
13 --
14 -- See also
15 --
16 --  * /Applicative Programming with Effects/,
17 --    by Conor McBride and Ross Paterson, online at
18 --    <http://www.soi.city.ac.uk/~ross/papers/Applicative.html>.
19 --
20 --  * /The Essence of the Iterator Pattern/,
21 --    by Jeremy Gibbons and Bruno Oliveira,
22 --    in /Mathematically-Structured Functional Programming/, 2006, and online at
23 --    <http://web.comlab.ox.ac.uk/oucl/work/jeremy.gibbons/publications/#iterator>.
24 --
25 -- Note that the functions 'mapM' and 'sequence' generalize "Prelude"
26 -- functions of the same names from lists to any 'Traversable' functor.
27 -- To avoid ambiguity, either import the "Prelude" hiding these names
28 -- or qualify uses of these function names with an alias for this module.
29
30 module Data.Traversable (
31         Traversable(..),
32         for,
33         forM,
34         mapAccumL,
35         mapAccumR,
36         fmapDefault,
37         foldMapDefault,
38         ) where
39
40 import Prelude hiding (mapM, sequence, foldr)
41 import qualified Prelude (mapM, foldr)
42 import Control.Applicative
43 import Data.Foldable (Foldable())
44 import Data.Monoid (Monoid)
45
46 -- | Functors representing data structures that can be traversed from
47 -- left to right.
48 --
49 -- Minimal complete definition: 'traverse' or 'sequenceA'.
50 --
51 -- Instances are similar to 'Functor', e.g. given a data type
52 --
53 -- > data Tree a = Empty | Leaf a | Node (Tree a) a (Tree a)
54 --
55 -- a suitable instance would be
56 --
57 -- > instance Traversable Tree
58 -- >    traverse f Empty = pure Empty
59 -- >    traverse f (Leaf x) = Leaf <$> f x
60 -- >    traverse f (Node l k r) = Node <$> traverse f l <*> f k <*> traverse f r
61 --
62 -- This is suitable even for abstract types, as the laws for '<*>'
63 -- imply a form of associativity.
64 --
65 -- The superclass instances should satisfy the following:
66 --
67 --  * In the 'Functor' instance, 'fmap' should be equivalent to traversal
68 --    with the identity applicative functor ('fmapDefault').
69 --
70 --  * In the 'Foldable' instance, 'Data.Foldable.foldMap' should be
71 --    equivalent to traversal with a constant applicative functor
72 --    ('foldMapDefault').
73 --
74 class (Functor t, Foldable t) => Traversable t where
75         -- | Map each element of a structure to an action, evaluate
76         -- these actions from left to right, and collect the results.
77         traverse :: Applicative f => (a -> f b) -> t a -> f (t b)
78         traverse f = sequenceA . fmap f
79
80         -- | Evaluate each action in the structure from left to right,
81         -- and collect the results.
82         sequenceA :: Applicative f => t (f a) -> f (t a)
83         sequenceA = traverse id
84
85         -- | Map each element of a structure to a monadic action, evaluate
86         -- these actions from left to right, and collect the results.
87         mapM :: Monad m => (a -> m b) -> t a -> m (t b)
88         mapM f = unwrapMonad . traverse (WrapMonad . f)
89
90         -- | Evaluate each monadic action in the structure from left to right,
91         -- and collect the results.
92         sequence :: Monad m => t (m a) -> m (t a)
93         sequence = mapM id
94
95 -- instances for Prelude types
96
97 instance Traversable Maybe where
98         traverse f Nothing = pure Nothing
99         traverse f (Just x) = Just <$> f x
100
101 instance Traversable [] where
102         traverse f = Prelude.foldr cons_f (pure [])
103           where cons_f x ys = (:) <$> f x <*> ys
104
105         mapM = Prelude.mapM
106
107 -- general functions
108
109 -- | 'for' is 'traverse' with its arguments flipped.
110 for :: (Traversable t, Applicative f) => t a -> (a -> f b) -> f (t b)
111 {-# INLINE for #-}
112 for = flip traverse
113
114 -- | 'forM' is 'mapM' with its arguments flipped.
115 forM :: (Traversable t, Monad m) => t a -> (a -> m b) -> m (t b)
116 {-# INLINE forM #-}
117 forM = flip mapM
118
119 -- left-to-right state transformer
120 newtype StateL s a = StateL { runStateL :: s -> (s, a) }
121
122 instance Functor (StateL s) where
123         fmap f (StateL k) = StateL $ \ s ->
124                 let (s', v) = k s in (s', f v)
125
126 instance Applicative (StateL s) where
127         pure x = StateL (\ s -> (s, x))
128         StateL kf <*> StateL kv = StateL $ \ s ->
129                 let (s', f) = kf s
130                     (s'', v) = kv s'
131                 in (s'', f v)
132
133 -- |The 'mapAccumL' function behaves like a combination of 'fmap'
134 -- and 'foldl'; it applies a function to each element of a structure,
135 -- passing an accumulating parameter from left to right, and returning
136 -- a final value of this accumulator together with the new structure.
137 mapAccumL :: Traversable t => (a -> b -> (a, c)) -> a -> t b -> (a, t c)
138 mapAccumL f s t = runStateL (traverse (StateL . flip f) t) s
139
140 -- right-to-left state transformer
141 newtype StateR s a = StateR { runStateR :: s -> (s, a) }
142
143 instance Functor (StateR s) where
144         fmap f (StateR k) = StateR $ \ s ->
145                 let (s', v) = k s in (s', f v)
146
147 instance Applicative (StateR s) where
148         pure x = StateR (\ s -> (s, x))
149         StateR kf <*> StateR kv = StateR $ \ s ->
150                 let (s', v) = kv s
151                     (s'', f) = kf s'
152                 in (s'', f v)
153
154 -- |The 'mapAccumR' function behaves like a combination of 'fmap'
155 -- and 'foldr'; it applies a function to each element of a structure,
156 -- passing an accumulating parameter from right to left, and returning
157 -- a final value of this accumulator together with the new structure.
158 mapAccumR :: Traversable t => (a -> b -> (a, c)) -> a -> t b -> (a, t c)
159 mapAccumR f s t = runStateR (traverse (StateR . flip f) t) s
160
161 -- | This function may be used as a value for `fmap` in a `Functor` instance.
162 fmapDefault :: Traversable t => (a -> b) -> t a -> t b
163 fmapDefault f = getId . traverse (Id . f)
164
165 -- | This function may be used as a value for `Data.Foldable.foldMap`
166 -- in a `Foldable` instance.
167 foldMapDefault :: (Traversable t, Monoid m) => (a -> m) -> t a -> m
168 foldMapDefault f = getConst . traverse (Const . f)
169
170 -- local instances
171
172 newtype Id a = Id { getId :: a }
173
174 instance Functor Id where
175         fmap f (Id x) = Id (f x)
176
177 instance Applicative Id where
178         pure = Id
179         Id f <*> Id x = Id (f x)