add Data.Foldable.{for_,forM_} and Data.Traversable.{for,forM}
[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 -- 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         fmapDefault,
35         foldMapDefault,
36         ) where
37
38 import Prelude hiding (mapM, sequence, foldr)
39 import qualified Prelude (mapM, foldr)
40 import Control.Applicative
41 import Data.Foldable (Foldable())
42 import Data.Monoid (Monoid)
43 import Data.Array
44
45 -- | Functors representing data structures that can be traversed from
46 -- left to right.
47 --
48 -- Minimal complete definition: 'traverse' or 'sequenceA'.
49 --
50 -- Instances are similar to 'Functor', e.g. given a data type
51 --
52 -- > data Tree a = Empty | Leaf a | Node (Tree a) a (Tree a)
53 --
54 -- a suitable instance would be
55 --
56 -- > instance Traversable Tree
57 -- >    traverse f Empty = pure Empty
58 -- >    traverse f (Leaf x) = Leaf <$> f x
59 -- >    traverse f (Node l k r) = Node <$> traverse f l <*> f k <*> traverse f r
60 --
61 -- This is suitable even for abstract types, as the laws for '<*>'
62 -- imply a form of associativity.
63 --
64 -- The superclass instances should satisfy the following:
65 --
66 --  * In the 'Functor' instance, 'fmap' should be equivalent to traversal
67 --    with the identity applicative functor ('fmapDefault').
68 --
69 --  * In the 'Foldable' instance, 'Data.Foldable.foldMap' should be
70 --    equivalent to traversal with a constant applicative functor
71 --    ('foldMapDefault').
72 --
73 class (Functor t, Foldable t) => Traversable t where
74         -- | Map each element of a structure to an action, evaluate
75         -- these actions from left to right, and collect the results.
76         traverse :: Applicative f => (a -> f b) -> t a -> f (t b)
77         traverse f = sequenceA . fmap f
78
79         -- | Evaluate each action in the structure from left to right,
80         -- and collect the results.
81         sequenceA :: Applicative f => t (f a) -> f (t a)
82         sequenceA = traverse id
83
84         -- | Map each element of a structure to an monadic action, evaluate
85         -- these actions from left to right, and collect the results.
86         mapM :: Monad m => (a -> m b) -> t a -> m (t b)
87         mapM f = unwrapMonad . traverse (WrapMonad . f)
88
89         -- | Evaluate each monadic action in the structure from left to right,
90         -- and collect the results.
91         sequence :: Monad m => t (m a) -> m (t a)
92         sequence = mapM id
93
94 -- instances for Prelude types
95
96 instance Traversable Maybe where
97         traverse f Nothing = pure Nothing
98         traverse f (Just x) = Just <$> f x
99
100 instance Traversable [] where
101         traverse f = Prelude.foldr cons_f (pure [])
102           where cons_f x ys = (:) <$> f x <*> ys
103
104         mapM = Prelude.mapM
105
106 instance Ix i => Traversable (Array i) where
107         traverse f arr = listArray (bounds arr) <$> traverse f (elems arr)
108
109 -- general functions
110
111 -- | 'for' is 'traverse' with its arguments flipped.
112 for :: (Traversable t, Applicative f) => t a -> (a -> f b) -> f (t b)
113 {-# INLINE for #-}
114 for = flip traverse
115
116 -- | 'forM' is 'mapM' with its arguments flipped.
117 forM :: (Traversable t, Monad m) => t a -> (a -> m b) -> m (t b)
118 {-# INLINE forM #-}
119 forM = flip mapM
120
121 -- | This function may be used as a value for `fmap` in a `Functor` instance.
122 fmapDefault :: Traversable t => (a -> b) -> t a -> t b
123 fmapDefault f = getId . traverse (Id . f)
124
125 -- | This function may be used as a value for `Data.Foldable.foldMap`
126 -- in a `Foldable` instance.
127 foldMapDefault :: (Traversable t, Monoid m) => (a -> m) -> t a -> m
128 foldMapDefault f = getConst . traverse (Const . f)
129
130 -- local instances
131
132 newtype Id a = Id { getId :: a }
133
134 instance Functor Id where
135         fmap f (Id x) = Id (f x)
136
137 instance Applicative Id where
138         pure = Id
139         Id f <*> Id x = Id (f x)