X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=Data%2FTraversable.hs;h=28fa761b98347955a6bbf64e5c4d089f2a01634f;hb=e74a10138daf9fd70888a1841bd6cc93b9cca9f2;hp=cafd7577abbd166b5e293e62e5d55684455bec3c;hpb=e2723a042968e1e947a038bf472a5aefb121376f;p=ghc-base.git diff --git a/Data/Traversable.hs b/Data/Traversable.hs index cafd757..28fa761 100644 --- a/Data/Traversable.hs +++ b/Data/Traversable.hs @@ -31,6 +31,8 @@ module Data.Traversable ( Traversable(..), for, forM, + mapAccumL, + mapAccumR, fmapDefault, foldMapDefault, ) where @@ -41,6 +43,14 @@ import Control.Applicative import Data.Foldable (Foldable()) import Data.Monoid (Monoid) +#if defined(__GLASGOW_HASKELL__) +import GHC.Arr +#elif defined(__HUGS__) +import Hugs.Array +#elif defined(__NHC__) +import Array +#endif + -- | Functors representing data structures that can be traversed from -- left to right. -- @@ -52,7 +62,7 @@ import Data.Monoid (Monoid) -- -- a suitable instance would be -- --- > instance Traversable Tree +-- > instance Traversable Tree where -- > traverse f Empty = pure Empty -- > traverse f (Leaf x) = Leaf <$> f x -- > traverse f (Node l k r) = Node <$> traverse f l <*> f k <*> traverse f r @@ -93,15 +103,19 @@ class (Functor t, Foldable t) => Traversable t where -- instances for Prelude types instance Traversable Maybe where - traverse f Nothing = pure Nothing + traverse _ Nothing = pure Nothing traverse f (Just x) = Just <$> f x instance Traversable [] where + {-# INLINE traverse #-} -- so that traverse can fuse traverse f = Prelude.foldr cons_f (pure []) where cons_f x ys = (:) <$> f x <*> ys mapM = Prelude.mapM +instance Ix i => Traversable (Array i) where + traverse f arr = listArray (bounds arr) `fmap` traverse f (elems arr) + -- general functions -- | 'for' is 'traverse' with its arguments flipped. @@ -114,6 +128,48 @@ forM :: (Traversable t, Monad m) => t a -> (a -> m b) -> m (t b) {-# INLINE forM #-} forM = flip mapM +-- left-to-right state transformer +newtype StateL s a = StateL { runStateL :: s -> (s, a) } + +instance Functor (StateL s) where + fmap f (StateL k) = StateL $ \ s -> + let (s', v) = k s in (s', f v) + +instance Applicative (StateL s) where + pure x = StateL (\ s -> (s, x)) + StateL kf <*> StateL kv = StateL $ \ s -> + let (s', f) = kf s + (s'', v) = kv s' + in (s'', f v) + +-- |The 'mapAccumL' function behaves like a combination of 'fmap' +-- and 'foldl'; it applies a function to each element of a structure, +-- passing an accumulating parameter from left to right, and returning +-- a final value of this accumulator together with the new structure. +mapAccumL :: Traversable t => (a -> b -> (a, c)) -> a -> t b -> (a, t c) +mapAccumL f s t = runStateL (traverse (StateL . flip f) t) s + +-- right-to-left state transformer +newtype StateR s a = StateR { runStateR :: s -> (s, a) } + +instance Functor (StateR s) where + fmap f (StateR k) = StateR $ \ s -> + let (s', v) = k s in (s', f v) + +instance Applicative (StateR s) where + pure x = StateR (\ s -> (s, x)) + StateR kf <*> StateR kv = StateR $ \ s -> + let (s', v) = kv s + (s'', f) = kf s' + in (s'', f v) + +-- |The 'mapAccumR' function behaves like a combination of 'fmap' +-- and 'foldr'; it applies a function to each element of a structure, +-- passing an accumulating parameter from right to left, and returning +-- a final value of this accumulator together with the new structure. +mapAccumR :: Traversable t => (a -> b -> (a, c)) -> a -> t b -> (a, t c) +mapAccumR f s t = runStateR (traverse (StateR . flip f) t) s + -- | This function may be used as a value for `fmap` in a `Functor` instance. fmapDefault :: Traversable t => (a -> b) -> t a -> t b fmapDefault f = getId . traverse (Id . f)