af04e51f3a735b4a6a6f1382332c5d29de5b399e
[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 #if defined(__GLASGOW_HASKELL__)
47 import GHC.Arr
48 #elif defined(__HUGS__)
49 import Hugs.Array
50 #elif defined(__NHC__)
51 import Array
52 #endif
53
54 -- | Functors representing data structures that can be traversed from
55 -- left to right.
56 --
57 -- Minimal complete definition: 'traverse' or 'sequenceA'.
58 --
59 -- Instances are similar to 'Functor', e.g. given a data type
60 --
61 -- > data Tree a = Empty | Leaf a | Node (Tree a) a (Tree a)
62 --
63 -- a suitable instance would be
64 --
65 -- > instance Traversable Tree where
66 -- >    traverse f Empty = pure Empty
67 -- >    traverse f (Leaf x) = Leaf <$> f x
68 -- >    traverse f (Node l k r) = Node <$> traverse f l <*> f k <*> traverse f r
69 --
70 -- This is suitable even for abstract types, as the laws for '<*>'
71 -- imply a form of associativity.
72 --
73 -- The superclass instances should satisfy the following:
74 --
75 --  * In the 'Functor' instance, 'fmap' should be equivalent to traversal
76 --    with the identity applicative functor ('fmapDefault').
77 --
78 --  * In the 'Foldable' instance, 'Data.Foldable.foldMap' should be
79 --    equivalent to traversal with a constant applicative functor
80 --    ('foldMapDefault').
81 --
82 class (Functor t, Foldable t) => Traversable t where
83     -- | Map each element of a structure to an action, evaluate
84     -- these actions from left to right, and collect the results.
85     traverse :: Applicative f => (a -> f b) -> t a -> f (t b)
86     traverse f = sequenceA . fmap f
87
88     -- | Evaluate each action in the structure from left to right,
89     -- and collect the results.
90     sequenceA :: Applicative f => t (f a) -> f (t a)
91     sequenceA = traverse id
92
93     -- | Map each element of a structure to a monadic action, evaluate
94     -- these actions from left to right, and collect the results.
95     mapM :: Monad m => (a -> m b) -> t a -> m (t b)
96     mapM f = unwrapMonad . traverse (WrapMonad . f)
97
98     -- | Evaluate each monadic action in the structure from left to right,
99     -- and collect the results.
100     sequence :: Monad m => t (m a) -> m (t a)
101     sequence = mapM id
102
103 -- instances for Prelude types
104
105 instance Traversable Maybe where
106     traverse _ Nothing = pure Nothing
107     traverse f (Just x) = Just <$> f x
108
109 instance Traversable [] where
110     {-# INLINE traverse #-} -- so that traverse can fuse
111     traverse f = Prelude.foldr cons_f (pure [])
112       where cons_f x ys = (:) <$> f x <*> ys
113
114     mapM = Prelude.mapM
115
116 instance Ix i => Traversable (Array i) where
117     traverse f arr = listArray (bounds arr) `fmap` traverse f (elems arr)
118
119 -- general functions
120
121 -- | 'for' is 'traverse' with its arguments flipped.
122 for :: (Traversable t, Applicative f) => t a -> (a -> f b) -> f (t b)
123 {-# INLINE for #-}
124 for = flip traverse
125
126 -- | 'forM' is 'mapM' with its arguments flipped.
127 forM :: (Traversable t, Monad m) => t a -> (a -> m b) -> m (t b)
128 {-# INLINE forM #-}
129 forM = flip mapM
130
131 -- left-to-right state transformer
132 newtype StateL s a = StateL { runStateL :: s -> (s, a) }
133
134 instance Functor (StateL s) where
135     fmap f (StateL k) = StateL $ \ s -> let (s', v) = k s in (s', f v)
136
137 instance Applicative (StateL s) where
138     pure x = StateL (\ s -> (s, x))
139     StateL kf <*> StateL kv = StateL $ \ s ->
140         let (s', f) = kf s
141             (s'', v) = kv s'
142         in (s'', f v)
143
144 -- |The 'mapAccumL' function behaves like a combination of 'fmap'
145 -- and 'foldl'; it applies a function to each element of a structure,
146 -- passing an accumulating parameter from left to right, and returning
147 -- a final value of this accumulator together with the new structure.
148 mapAccumL :: Traversable t => (a -> b -> (a, c)) -> a -> t b -> (a, t c)
149 mapAccumL f s t = runStateL (traverse (StateL . flip f) t) s
150
151 -- right-to-left state transformer
152 newtype StateR s a = StateR { runStateR :: s -> (s, a) }
153
154 instance Functor (StateR s) where
155     fmap f (StateR k) = StateR $ \ s -> let (s', v) = k s in (s', f v)
156
157 instance Applicative (StateR s) where
158     pure x = StateR (\ s -> (s, x))
159     StateR kf <*> StateR kv = StateR $ \ s ->
160         let (s', v) = kv s
161             (s'', f) = kf s'
162         in (s'', f v)
163
164 -- |The 'mapAccumR' function behaves like a combination of 'fmap'
165 -- and 'foldr'; it applies a function to each element of a structure,
166 -- passing an accumulating parameter from right to left, and returning
167 -- a final value of this accumulator together with the new structure.
168 mapAccumR :: Traversable t => (a -> b -> (a, c)) -> a -> t b -> (a, t c)
169 mapAccumR f s t = runStateR (traverse (StateR . flip f) t) s
170
171 -- | This function may be used as a value for `fmap` in a `Functor` instance.
172 fmapDefault :: Traversable t => (a -> b) -> t a -> t b
173 {-# INLINE fmapDefault #-}
174 fmapDefault f = getId . traverse (Id . f)
175
176 -- | This function may be used as a value for `Data.Foldable.foldMap`
177 -- in a `Foldable` instance.
178 foldMapDefault :: (Traversable t, Monoid m) => (a -> m) -> t a -> m
179 foldMapDefault f = getConst . traverse (Const . f)
180
181 -- local instances
182
183 newtype Id a = Id { getId :: a }
184
185 instance Functor Id where
186     fmap f (Id x) = Id (f x)
187
188 instance Applicative Id where
189     pure = Id
190     Id f <*> Id x = Id (f x)