~ubuntu-branches/ubuntu/precise/ghc/precise

« back to all changes in this revision

Viewing changes to libraries/base/Data/Traversable.hs

  • Committer: Bazaar Package Importer
  • Author(s): Joachim Breitner
  • Date: 2011-01-17 12:49:24 UTC
  • Revision ID: james.westby@ubuntu.com-20110117124924-do1pym1jlf5o636m
Tags: upstream-7.0.1
ImportĀ upstreamĀ versionĀ 7.0.1

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
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 ->
 
136
                let (s', v) = k s in (s', f v)
 
137
 
 
138
instance Applicative (StateL s) where
 
139
        pure x = StateL (\ s -> (s, x))
 
140
        StateL kf <*> StateL kv = StateL $ \ s ->
 
141
                let (s', f) = kf s
 
142
                    (s'', v) = kv s'
 
143
                in (s'', f v)
 
144
 
 
145
-- |The 'mapAccumL' function behaves like a combination of 'fmap'
 
146
-- and 'foldl'; it applies a function to each element of a structure,
 
147
-- passing an accumulating parameter from left to right, and returning
 
148
-- a final value of this accumulator together with the new structure.
 
149
mapAccumL :: Traversable t => (a -> b -> (a, c)) -> a -> t b -> (a, t c)
 
150
mapAccumL f s t = runStateL (traverse (StateL . flip f) t) s
 
151
 
 
152
-- right-to-left state transformer
 
153
newtype StateR s a = StateR { runStateR :: s -> (s, a) }
 
154
 
 
155
instance Functor (StateR s) where
 
156
        fmap f (StateR k) = StateR $ \ s ->
 
157
                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` instance.
 
174
fmapDefault :: Traversable t => (a -> b) -> t a -> t b
 
175
fmapDefault f = getId . traverse (Id . f)
 
176
 
 
177
-- | This function may be used as a value for `Data.Foldable.foldMap`
 
178
-- in a `Foldable` instance.
 
179
foldMapDefault :: (Traversable t, Monoid m) => (a -> m) -> t a -> m
 
180
foldMapDefault f = getConst . traverse (Const . f)
 
181
 
 
182
-- local instances
 
183
 
 
184
newtype Id a = Id { getId :: a }
 
185
 
 
186
instance Functor Id where
 
187
        fmap f (Id x) = Id (f x)
 
188
 
 
189
instance Applicative Id where
 
190
        pure = Id
 
191
        Id f <*> Id x = Id (f x)