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