{-# LANGUAGE DeriveTraversable #-}{-# LANGUAGE FlexibleInstances #-}{-# LANGUAGE NoImplicitPrelude #-}{-# LANGUAGE ScopedTypeVariables #-}{-# LANGUAGE StandaloneDeriving #-}{-# LANGUAGE Trustworthy #-}{-# LANGUAGE TypeOperators #-}------------------------------------------------------------------------------- |-- Module : Data.Traversable-- Copyright : Conor McBride and Ross Paterson 2005-- License : BSD-style (see the LICENSE file in the distribution)---- Maintainer : libraries@haskell.org-- Stability : experimental-- Portability : portable---- Class of data structures that can be traversed from left to right,-- performing an action on each element.---- See also---- * \"Applicative Programming with Effects\",-- by Conor McBride and Ross Paterson,-- /Journal of Functional Programming/ 18:1 (2008) 1-13, online at-- <http://www.soi.city.ac.uk/~ross/papers/Applicative.html>.---- * \"The Essence of the Iterator Pattern\",-- by Jeremy Gibbons and Bruno Oliveira,-- in /Mathematically-Structured Functional Programming/, 2006, online at-- <http://web.comlab.ox.ac.uk/oucl/work/jeremy.gibbons/publications/#iterator>.---- * \"An Investigation of the Laws of Traversals\",-- by Mauro Jaskelioff and Ondrej Rypacek,-- in /Mathematically-Structured Functional Programming/, 2012, online at-- <http://arxiv.org/pdf/1202.2919>.-------------------------------------------------------------------------------moduleData.Traversable(-- * The 'Traversable' classTraversable (..),-- * Utility functionsfor ,forM ,mapAccumL ,mapAccumR ,-- * General definitions for superclass methodsfmapDefault ,foldMapDefault ,)where-- It is convenient to use 'Const' here but this means we must-- define a few instances here which really belong in Control.ApplicativeimportControl.Applicative (Const (..),ZipList (..))importData.Coerce importData.Either (Either (..))importData.Foldable (Foldable )importData.Functor importData.Functor.Identity (Identity (..))importData.Functor.Utils (StateL (..),StateR (..))importData.Monoid (Dual (..),Sum (..),Product (..),First (..),Last (..),Alt (..),Ap (..))importData.Ord (Down (..))importData.Proxy (Proxy (..))importGHC.Arr importGHC.Base (Applicative (..),Monad (..),Monoid ,Maybe (..),NonEmpty (..),($) ,(.) ,id ,flip )importGHC.Generics importqualifiedGHC.List asList(foldr )-- | Functors representing data structures that can be traversed from-- left to right.---- A definition of 'traverse' must satisfy the following laws:---- [Naturality]-- @t . 'traverse' f = 'traverse' (t . f)@-- for every applicative transformation @t@---- [Identity]-- @'traverse' 'Identity' = 'Identity'@---- [Composition]-- @'traverse' ('Data.Functor.Compose.Compose' . 'fmap' g . f)-- = 'Data.Functor.Compose.Compose' . 'fmap' ('traverse' g) . 'traverse' f@---- A definition of 'sequenceA' must satisfy the following laws:---- [Naturality]-- @t . 'sequenceA' = 'sequenceA' . 'fmap' t@-- for every applicative transformation @t@---- [Identity]-- @'sequenceA' . 'fmap' 'Identity' = 'Identity'@---- [Composition]-- @'sequenceA' . 'fmap' 'Data.Functor.Compose.Compose'-- = 'Data.Functor.Compose.Compose' . 'fmap' 'sequenceA' . 'sequenceA'@---- where an /applicative transformation/ is a function---- @t :: (Applicative f, Applicative g) => f a -> g a@---- preserving the 'Applicative' operations, i.e.---- @-- t ('pure' x) = 'pure' x-- t (f '<*>' x) = t f '<*>' t x-- @---- and the identity functor 'Identity' and composition functors-- 'Data.Functor.Compose.Compose' are from "Data.Functor.Identity" and-- "Data.Functor.Compose".---- A result of the naturality law is a purity law for 'traverse'---- @'traverse' 'pure' = 'pure'@---- (The naturality law is implied by parametricity and thus so is the-- purity law [1, p15].)---- Instances are similar to 'Functor', e.g. given a data type---- > data Tree a = Empty | Leaf a | Node (Tree a) a (Tree a)---- a suitable instance would be---- > 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---- This is suitable even for abstract types, as the laws for '<*>'-- imply a form of associativity.---- The superclass instances should satisfy the following:---- * In the 'Functor' instance, 'fmap' should be equivalent to traversal-- with the identity applicative functor ('fmapDefault').---- * In the 'Foldable' instance, 'Data.Foldable.foldMap' should be-- equivalent to traversal with a constant applicative functor-- ('foldMapDefault').---- References:-- [1] The Essence of the Iterator Pattern, Jeremy Gibbons and Bruno C. d. S. Oliveiraclass(Functor t ,Foldable t )=>Traversable t where{-# MINIMALtraverse |sequenceA #-}-- | Map each element of a structure to an action, evaluate these actions-- from left to right, and collect the results. For a version that ignores-- the results see 'Data.Foldable.traverse_'.traverse ::Applicative f =>(a ->f b )->t a ->f (t b ){-# INLINEtraverse #-}-- See Note [Inline default methods]traverse a -> f b
f =t (f b) -> f (t b)
forall (t :: * -> *) (f :: * -> *) a.
(Traversable t, Applicative f) =>
t (f a) -> f (t a)
sequenceA (t (f b) -> f (t b)) -> (t a -> t (f b)) -> t a -> f (t b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> f b) -> t a -> t (f b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> f b
f -- | Evaluate each action in the structure from left to right, and-- collect the results. For a version that ignores the results-- see 'Data.Foldable.sequenceA_'.sequenceA ::Applicative f =>t (f a )->f (t a ){-# INLINEsequenceA #-}-- See Note [Inline default methods]sequenceA =(f a -> f a) -> t (f a) -> f (t a)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse f a -> f a
forall a. a -> a
id -- | Map each element of a structure to a monadic action, evaluate-- these actions from left to right, and collect the results. For-- a version that ignores the results see 'Data.Foldable.mapM_'.mapM ::Monad m =>(a ->m b )->t a ->m (t b ){-# INLINEmapM #-}-- See Note [Inline default methods]mapM =(a -> m b) -> t a -> m (t b)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse -- | Evaluate each monadic action in the structure from left to-- right, and collect the results. For a version that ignores the-- results see 'Data.Foldable.sequence_'.sequence ::Monad m =>t (m a )->m (t a ){-# INLINEsequence #-}-- See Note [Inline default methods]sequence =t (m a) -> m (t a)
forall (t :: * -> *) (f :: * -> *) a.
(Traversable t, Applicative f) =>
t (f a) -> f (t a)
sequenceA {- Note [Inline default methods]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
Consider
 class ... => Traversable t where
 ...
 mapM :: Monad m => (a -> m b) -> t a -> m (t b)
 mapM = traverse -- Default method
 instance Traversable [] where
 {-# INLINE traverse #-}
 traverse = ...code for traverse on lists ...
This gives rise to a list-instance of mapM looking like this
 $fTraversable[]_$ctraverse = ...code for traverse on lists...
 {-# INLINE $fTraversable[]_$ctraverse #-}
 $fTraversable[]_$cmapM = $fTraversable[]_$ctraverse
Now the $ctraverse obediently inlines into the RHS of $cmapM, /but/
that's all! We get
 $fTraversable[]_$cmapM = ...code for traverse on lists...
with NO INLINE pragma! This happens even though 'traverse' had an
INLINE pragma because the author knew it should be inlined pretty
vigorously.
Indeed, it turned out that the rhs of $cmapM was just too big to
inline, so all uses of mapM on lists used a terribly inefficient
dictionary-passing style, because of its 'Monad m =>' type. Disaster!
Solution: add an INLINE pragma on the default method:
 class ... => Traversable t where
 ...
 mapM :: Monad m => (a -> m b) -> t a -> m (t b)
 {-# INLINE mapM #-} -- VERY IMPORTANT!
 mapM = traverse
-}-- instances for Prelude types-- | @since 2.01instanceTraversable Maybe wheretraverse :: (a -> f b) -> Maybe a -> f (Maybe b)
traverse a -> f b
_Maybe a
Nothing =Maybe b -> f (Maybe b)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe b
forall a. Maybe a
Nothing traverse a -> f b
f (Just a
x )=b -> Maybe b
forall a. a -> Maybe a
Just (b -> Maybe b) -> f b -> f (Maybe b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
x -- | @since 2.01instanceTraversable []where{-# INLINEtraverse #-}-- so that traverse can fusetraverse :: (a -> f b) -> [a] -> f [b]
traverse a -> f b
f =(a -> f [b] -> f [b]) -> f [b] -> [a] -> f [b]
forall a b. (a -> b -> b) -> b -> [a] -> b
List.foldr a -> f [b] -> f [b]
cons_f ([b] -> f [b]
forall (f :: * -> *) a. Applicative f => a -> f a
pure [])wherecons_f :: a -> f [b] -> f [b]
cons_f a
x f [b]
ys =(b -> [b] -> [b]) -> f b -> f [b] -> f [b]
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (:)(a -> f b
f a
x )f [b]
ys -- | @since 4.9.0.0instanceTraversable NonEmpty wheretraverse :: (a -> f b) -> NonEmpty a -> f (NonEmpty b)
traverse a -> f b
f ~(a
a :| [a]
as )=(b -> [b] -> NonEmpty b) -> f b -> f [b] -> f (NonEmpty b)
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 b -> [b] -> NonEmpty b
forall a. a -> [a] -> NonEmpty a
(:|) (a -> f b
f a
a )((a -> f b) -> [a] -> f [b]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse a -> f b
f [a]
as )-- | @since 4.7.0.0instanceTraversable (Either a )wheretraverse :: (a -> f b) -> Either a a -> f (Either a b)
traverse a -> f b
_(Left a
x )=Either a b -> f (Either a b)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (a -> Either a b
forall a b. a -> Either a b
Left a
x )traverse a -> f b
f (Right a
y )=b -> Either a b
forall a b. b -> Either a b
Right (b -> Either a b) -> f b -> f (Either a b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
y -- | @since 4.7.0.0instanceTraversable ((,)a )wheretraverse :: (a -> f b) -> (a, a) -> f (a, b)
traverse a -> f b
f (a
x ,a
y )=(,)a
x (b -> (a, b)) -> f b -> f (a, b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
y -- | @since 2.01instanceIx i =>Traversable (Array i )wheretraverse :: (a -> f b) -> Array i a -> f (Array i b)
traverse a -> f b
f Array i a
arr =(i, i) -> [b] -> Array i b
forall i e. Ix i => (i, i) -> [e] -> Array i e
listArray (Array i a -> (i, i)
forall i e. Array i e -> (i, i)
bounds Array i a
arr )([b] -> Array i b) -> f [b] -> f (Array i b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` (a -> f b) -> [a] -> f [b]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse a -> f b
f (Array i a -> [a]
forall i e. Array i e -> [e]
elems Array i a
arr )-- | @since 4.7.0.0instanceTraversable Proxy wheretraverse :: (a -> f b) -> Proxy a -> f (Proxy b)
traverse a -> f b
_Proxy a
_=Proxy b -> f (Proxy b)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Proxy b
forall k (t :: k). Proxy t
Proxy {-# INLINEtraverse #-}sequenceA :: Proxy (f a) -> f (Proxy a)
sequenceA Proxy (f a)
_=Proxy a -> f (Proxy a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Proxy a
forall k (t :: k). Proxy t
Proxy {-# INLINEsequenceA #-}mapM :: (a -> m b) -> Proxy a -> m (Proxy b)
mapM a -> m b
_Proxy a
_=Proxy b -> m (Proxy b)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Proxy b
forall k (t :: k). Proxy t
Proxy {-# INLINEmapM #-}sequence :: Proxy (m a) -> m (Proxy a)
sequence Proxy (m a)
_=Proxy a -> m (Proxy a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Proxy a
forall k (t :: k). Proxy t
Proxy {-# INLINEsequence #-}-- | @since 4.7.0.0instanceTraversable (Const m )wheretraverse :: (a -> f b) -> Const m a -> f (Const m b)
traverse a -> f b
_(Const m
m )=Const m b -> f (Const m b)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Const m b -> f (Const m b)) -> Const m b -> f (Const m b)
forall a b. (a -> b) -> a -> b
$ m -> Const m b
forall k a (b :: k). a -> Const a b
Const m
m -- | @since 4.8.0.0instanceTraversable Dual wheretraverse :: (a -> f b) -> Dual a -> f (Dual b)
traverse a -> f b
f (Dual a
x )=b -> Dual b
forall a. a -> Dual a
Dual (b -> Dual b) -> f b -> f (Dual b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
x -- | @since 4.8.0.0instanceTraversable Sum wheretraverse :: (a -> f b) -> Sum a -> f (Sum b)
traverse a -> f b
f (Sum a
x )=b -> Sum b
forall a. a -> Sum a
Sum (b -> Sum b) -> f b -> f (Sum b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
x -- | @since 4.8.0.0instanceTraversable Product wheretraverse :: (a -> f b) -> Product a -> f (Product b)
traverse a -> f b
f (Product a
x )=b -> Product b
forall a. a -> Product a
Product (b -> Product b) -> f b -> f (Product b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
x -- | @since 4.8.0.0instanceTraversable First wheretraverse :: (a -> f b) -> First a -> f (First b)
traverse a -> f b
f (First Maybe a
x )=Maybe b -> First b
forall a. Maybe a -> First a
First (Maybe b -> First b) -> f (Maybe b) -> f (First b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (a -> f b) -> Maybe a -> f (Maybe b)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse a -> f b
f Maybe a
x -- | @since 4.8.0.0instanceTraversable Last wheretraverse :: (a -> f b) -> Last a -> f (Last b)
traverse a -> f b
f (Last Maybe a
x )=Maybe b -> Last b
forall a. Maybe a -> Last a
Last (Maybe b -> Last b) -> f (Maybe b) -> f (Last b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (a -> f b) -> Maybe a -> f (Maybe b)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse a -> f b
f Maybe a
x -- | @since 4.12.0.0instance(Traversable f )=>Traversable (Alt f )wheretraverse :: (a -> f b) -> Alt f a -> f (Alt f b)
traverse a -> f b
f (Alt f a
x )=f b -> Alt f b
forall k (f :: k -> *) (a :: k). f a -> Alt f a
Alt (f b -> Alt f b) -> f (f b) -> f (Alt f b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (a -> f b) -> f a -> f (f b)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse a -> f b
f f a
x -- | @since 4.12.0.0instance(Traversable f )=>Traversable (Ap f )wheretraverse :: (a -> f b) -> Ap f a -> f (Ap f b)
traverse a -> f b
f (Ap f a
x )=f b -> Ap f b
forall k (f :: k -> *) (a :: k). f a -> Ap f a
Ap (f b -> Ap f b) -> f (f b) -> f (Ap f b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (a -> f b) -> f a -> f (f b)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse a -> f b
f f a
x -- | @since 4.9.0.0instanceTraversable ZipList wheretraverse :: (a -> f b) -> ZipList a -> f (ZipList b)
traverse a -> f b
f (ZipList [a]
x )=[b] -> ZipList b
forall a. [a] -> ZipList a
ZipList ([b] -> ZipList b) -> f [b] -> f (ZipList b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (a -> f b) -> [a] -> f [b]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse a -> f b
f [a]
x -- | @since 4.9.0.0derivinginstanceTraversable Identity -- Instances for GHC.Generics-- | @since 4.9.0.0instanceTraversable U1 wheretraverse :: (a -> f b) -> U1 a -> f (U1 b)
traverse a -> f b
_U1 a
_=U1 b -> f (U1 b)
forall (f :: * -> *) a. Applicative f => a -> f a
pure U1 b
forall k (p :: k). U1 p
U1 {-# INLINEtraverse #-}sequenceA :: U1 (f a) -> f (U1 a)
sequenceA U1 (f a)
_=U1 a -> f (U1 a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure U1 a
forall k (p :: k). U1 p
U1 {-# INLINEsequenceA #-}mapM :: (a -> m b) -> U1 a -> m (U1 b)
mapM a -> m b
_U1 a
_=U1 b -> m (U1 b)
forall (f :: * -> *) a. Applicative f => a -> f a
pure U1 b
forall k (p :: k). U1 p
U1 {-# INLINEmapM #-}sequence :: U1 (m a) -> m (U1 a)
sequence U1 (m a)
_=U1 a -> m (U1 a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure U1 a
forall k (p :: k). U1 p
U1 {-# INLINEsequence #-}-- | @since 4.9.0.0derivinginstanceTraversable V1 -- | @since 4.9.0.0derivinginstanceTraversable Par1 -- | @since 4.9.0.0derivinginstanceTraversable f =>Traversable (Rec1 f )-- | @since 4.9.0.0derivinginstanceTraversable (K1 i c )-- | @since 4.9.0.0derivinginstanceTraversable f =>Traversable (M1 i c f )-- | @since 4.9.0.0derivinginstance(Traversable f ,Traversable g )=>Traversable (f :+: g )-- | @since 4.9.0.0derivinginstance(Traversable f ,Traversable g )=>Traversable (f :*: g )-- | @since 4.9.0.0derivinginstance(Traversable f ,Traversable g )=>Traversable (f :.: g )-- | @since 4.9.0.0derivinginstanceTraversable UAddr -- | @since 4.9.0.0derivinginstanceTraversable UChar -- | @since 4.9.0.0derivinginstanceTraversable UDouble -- | @since 4.9.0.0derivinginstanceTraversable UFloat -- | @since 4.9.0.0derivinginstanceTraversable UInt -- | @since 4.9.0.0derivinginstanceTraversable UWord -- Instance for Data.Ord-- | @since 4.12.0.0derivinginstanceTraversable Down -- general functions-- | 'for' is 'traverse' with its arguments flipped. For a version-- that ignores the results see 'Data.Foldable.for_'.for ::(Traversable t ,Applicative f )=>t a ->(a ->f b )->f (t b ){-# INLINEfor #-}for :: t a -> (a -> f b) -> f (t b)
for =((a -> f b) -> t a -> f (t b)) -> t a -> (a -> f b) -> f (t b)
forall a b c. (a -> b -> c) -> b -> a -> c
flip (a -> f b) -> t a -> f (t b)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse -- | 'forM' is 'mapM' with its arguments flipped. For a version that-- ignores the results see 'Data.Foldable.forM_'.forM ::(Traversable t ,Monad m )=>t a ->(a ->m b )->m (t b ){-# INLINEforM #-}forM :: t a -> (a -> m b) -> m (t b)
forM =((a -> m b) -> t a -> m (t b)) -> t a -> (a -> m b) -> m (t b)
forall a b c. (a -> b -> c) -> b -> a -> c
flip (a -> m b) -> t a -> m (t b)
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM -- |The 'mapAccumL' function behaves like a combination of 'fmap'-- and 'Data.Foldable.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 :: (a -> b -> (a, c)) -> a -> t b -> (a, t c)
mapAccumL a -> b -> (a, c)
f a
s t b
t =StateL a (t c) -> a -> (a, t c)
forall s a. StateL s a -> s -> (s, a)
runStateL ((b -> StateL a c) -> t b -> StateL a (t c)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse ((a -> (a, c)) -> StateL a c
forall s a. (s -> (s, a)) -> StateL s a
StateL ((a -> (a, c)) -> StateL a c)
-> (b -> a -> (a, c)) -> b -> StateL a c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> b -> (a, c)) -> b -> a -> (a, c)
forall a b c. (a -> b -> c) -> b -> a -> c
flip a -> b -> (a, c)
f )t b
t )a
s -- |The 'mapAccumR' function behaves like a combination of 'fmap'-- and 'Data.Foldable.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 :: (a -> b -> (a, c)) -> a -> t b -> (a, t c)
mapAccumR a -> b -> (a, c)
f a
s t b
t =StateR a (t c) -> a -> (a, t c)
forall s a. StateR s a -> s -> (s, a)
runStateR ((b -> StateR a c) -> t b -> StateR a (t c)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse ((a -> (a, c)) -> StateR a c
forall s a. (s -> (s, a)) -> StateR s a
StateR ((a -> (a, c)) -> StateR a c)
-> (b -> a -> (a, c)) -> b -> StateR a c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> b -> (a, c)) -> b -> a -> (a, c)
forall a b c. (a -> b -> c) -> b -> a -> c
flip a -> b -> (a, c)
f )t b
t )a
s -- | This function may be used as a value for `fmap` in a `Functor`-- instance, provided that 'traverse' is defined. (Using-- `fmapDefault` with a `Traversable` instance defined only by-- 'sequenceA' will result in infinite recursion.)---- @-- 'fmapDefault' f ≡ 'runIdentity' . 'traverse' ('Identity' . f)-- @fmapDefault ::forallt a b .Traversable t =>(a ->b )->t a ->t b {-# INLINEfmapDefault #-}-- See Note [Function coercion] in Data.Functor.Utils.fmapDefault :: (a -> b) -> t a -> t b
fmapDefault =((a -> Identity b) -> t a -> Identity (t b))
-> (a -> b) -> t a -> t b
coerce((a -> Identity b) -> t a -> Identity (t b)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse ::(a ->Identity b )->t a ->Identity (t b ))-- | This function may be used as a value for `Data.Foldable.foldMap`-- in a `Foldable` instance.---- @-- 'foldMapDefault' f ≡ 'getConst' . 'traverse' ('Const' . f)-- @foldMapDefault ::forallt m a .(Traversable t ,Monoid m )=>(a ->m )->t a ->m {-# INLINEfoldMapDefault #-}-- See Note [Function coercion] in Data.Functor.Utils.foldMapDefault :: (a -> m) -> t a -> m
foldMapDefault =((a -> Const m ()) -> t a -> Const m (t ()))
-> (a -> m) -> t a -> m
coerce((a -> Const m ()) -> t a -> Const m (t ())
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse ::(a ->Const m ())->t a ->Const m (t ()))

AltStyle によって変換されたページ (->オリジナル) /