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