{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}
module GHC.Internal.Data.Traversable (
Traversable(..),
for,
forM,
forAccumM,
mapAccumL,
mapAccumR,
mapAccumM,
fmapDefault,
foldMapDefault,
) where
import GHC.Internal.Data.Coerce
import GHC.Internal.Data.Either ( Either(..) )
import GHC.Internal.Data.Foldable
import GHC.Internal.Data.Functor
import GHC.Internal.Data.Functor.Const ( Const(..) )
import GHC.Internal.Data.Functor.Identity ( Identity(..) )
import GHC.Internal.Data.Functor.Utils ( StateL(..), StateR(..), StateT(..), (#.) )
import GHC.Internal.Data.Monoid ( Dual(..), Sum(..), Product(..),
First(..), Last(..), Alt(..), Ap(..) )
import GHC.Internal.Data.Ord ( Down(..) )
import GHC.Internal.Data.Proxy ( Proxy(..) )
import GHC.Internal.Arr
import GHC.Internal.Base ( Applicative(..), Monad(..), Monoid, Maybe(..), NonEmpty(..),
($), (.), id, flip )
import GHC.Internal.Generics
import qualified GHC.Internal.List as List ( foldr )
import GHC.Tuple (Solo (..))
class (Functor t, Foldable t) => Traversable t where
{-# MINIMAL traverse | sequenceA #-}
traverse :: Applicative f => (a -> f b) -> t a -> f (t b)
{-# INLINE traverse #-}
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)
forall (f :: * -> *) a. 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 a b. (a -> b) -> t a -> t b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> f b
f
sequenceA :: Applicative f => t (f a) -> f (t a)
{-# INLINE sequenceA #-}
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)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b)
traverse f a -> f a
forall a. a -> a
id
mapM :: Monad m => (a -> m b) -> t a -> m (t b)
{-# INLINE mapM #-}
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)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b)
traverse
sequence :: Monad m => t (m a) -> m (t a)
{-# INLINE sequence #-}
sequence = t (m a) -> m (t a)
forall (t :: * -> *) (f :: * -> *) a.
(Traversable t, Applicative f) =>
t (f a) -> f (t a)
forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a)
sequenceA
instance Traversable Maybe where
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Maybe a -> f (Maybe b)
traverse a -> f b
_ Maybe a
Nothing = Maybe b -> f (Maybe b)
forall a. a -> f a
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
instance Traversable [] where
{-# INLINE traverse #-}
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(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 a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure [])
where cons_f :: a -> f [b] -> f [b]
cons_f a
x f [b]
ys = (b -> [b] -> [b]) -> f b -> f [b] -> f [b]
forall a b c. (a -> b -> c) -> f a -> f b -> f c
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
instance Traversable NonEmpty where
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(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 a b c. (a -> b -> c) -> f a -> f b -> f c
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)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse a -> f b
f [a]
as)
instance Traversable (Either a) where
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(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 a. a -> f a
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
deriving instance Traversable Solo
instance Traversable ((,) a) where
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(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
instance Ix i => Traversable (Array i) where
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(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 a b. (a -> b) -> f a -> f 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)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse a -> f b
f (Array i a -> [a]
forall i e. Array i e -> [e]
elems Array i a
arr)
instance Traversable Proxy where
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Proxy a -> f (Proxy b)
traverse a -> f b
_ Proxy a
_ = Proxy b -> f (Proxy b)
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Proxy b
forall {k} (t :: k). Proxy t
Proxy
{-# INLINE traverse #-}
sequenceA :: forall (f :: * -> *) a. Applicative f => Proxy (f a) -> f (Proxy a)
sequenceA Proxy (f a)
_ = Proxy a -> f (Proxy a)
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Proxy a
forall {k} (t :: k). Proxy t
Proxy
{-# INLINE sequenceA #-}
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Proxy a -> m (Proxy b)
mapM a -> m b
_ Proxy a
_ = Proxy b -> m (Proxy b)
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Proxy b
forall {k} (t :: k). Proxy t
Proxy
{-# INLINE mapM #-}
sequence :: forall (m :: * -> *) a. Monad m => Proxy (m a) -> m (Proxy a)
sequence Proxy (m a)
_ = Proxy a -> m (Proxy a)
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Proxy a
forall {k} (t :: k). Proxy t
Proxy
{-# INLINE sequence #-}
instance Traversable (Const m) where
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(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 a. a -> f a
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
instance Traversable Dual where
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(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
instance Traversable Sum where
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(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
instance Traversable Product where
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(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
instance Traversable First where
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(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)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Maybe a -> f (Maybe b)
traverse a -> f b
f Maybe a
x
instance Traversable Last where
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(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)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Maybe a -> f (Maybe b)
traverse a -> f b
f Maybe a
x
instance (Traversable f) => Traversable (Alt f) where
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(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)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> f a -> f (f b)
traverse a -> f b
f f a
x
instance (Traversable f) => Traversable (Ap f) where
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(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)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> f a -> f (f b)
traverse a -> f b
f f a
x
deriving instance Traversable Identity
instance Traversable U1 where
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> U1 a -> f (U1 b)
traverse a -> f b
_ U1 a
_ = U1 b -> f (U1 b)
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure U1 b
forall k (p :: k). U1 p
U1
{-# INLINE traverse #-}
sequenceA :: forall (f :: * -> *) a. Applicative f => U1 (f a) -> f (U1 a)
sequenceA U1 (f a)
_ = U1 a -> f (U1 a)
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure U1 a
forall k (p :: k). U1 p
U1
{-# INLINE sequenceA #-}
mapM :: forall (m :: * -> *) a b. Monad m => (a -> m b) -> U1 a -> m (U1 b)
mapM a -> m b
_ U1 a
_ = U1 b -> m (U1 b)
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure U1 b
forall k (p :: k). U1 p
U1
{-# INLINE mapM #-}
sequence :: forall (m :: * -> *) a. Monad m => U1 (m a) -> m (U1 a)
sequence U1 (m a)
_ = U1 a -> m (U1 a)
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure U1 a
forall k (p :: k). U1 p
U1
{-# INLINE sequence #-}
deriving instance Traversable V1
deriving instance Traversable Par1
deriving instance Traversable f => Traversable (Rec1 f)
deriving instance Traversable (K1 i c)
deriving instance Traversable f => Traversable (M1 i c f)
deriving instance (Traversable f, Traversable g) => Traversable (f :+: g)
deriving instance (Traversable f, Traversable g) => Traversable (f :*: g)
deriving instance (Traversable f, Traversable g) => Traversable (f :.: g)
deriving instance Traversable UAddr
deriving instance Traversable UChar
deriving instance Traversable UDouble
deriving instance Traversable UFloat
deriving instance Traversable UInt
deriving instance Traversable UWord
deriving instance Traversable Down
for :: (Traversable t, Applicative f) => t a -> (a -> f b) -> f (t b)
{-# INLINE for #-}
for :: forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
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)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b)
traverse
forM :: (Traversable t, Monad m) => t a -> (a -> m b) -> m (t b)
{-# INLINE forM #-}
forM :: forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
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)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> t a -> m (t b)
mapM
mapAccumL :: forall t s a b. Traversable t
=> (s -> a -> (s, b)) -> s -> t a -> (s, t b)
mapAccumL :: forall (t :: * -> *) s a b.
Traversable t =>
(s -> a -> (s, b)) -> s -> t a -> (s, t b)
mapAccumL s -> a -> (s, b)
f s
s t a
t = ((a -> StateL s b) -> t a -> StateL s (t b))
-> (a -> s -> (s, b)) -> t a -> s -> (s, t b)
forall a b. Coercible a b => a -> b
coerce (forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse @t @(StateL s) @a @b) ((s -> a -> (s, b)) -> a -> s -> (s, b)
forall a b c. (a -> b -> c) -> b -> a -> c
flip s -> a -> (s, b)
f) t a
t s
s
mapAccumR :: forall t s a b. Traversable t
=> (s -> a -> (s, b)) -> s -> t a -> (s, t b)
mapAccumR :: forall (t :: * -> *) s a b.
Traversable t =>
(s -> a -> (s, b)) -> s -> t a -> (s, t b)
mapAccumR s -> a -> (s, b)
f s
s t a
t = ((a -> StateR s b) -> t a -> StateR s (t b))
-> (a -> s -> (s, b)) -> t a -> s -> (s, t b)
forall a b. Coercible a b => a -> b
coerce (forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse @t @(StateR s) @a @b) ((s -> a -> (s, b)) -> a -> s -> (s, b)
forall a b c. (a -> b -> c) -> b -> a -> c
flip s -> a -> (s, b)
f) t a
t s
s
mapAccumM
:: forall m t s a b. (Monad m, Traversable t)
=> (s -> a -> m (s, b))
-> s -> t a -> m (s, t b)
mapAccumM :: forall (m :: * -> *) (t :: * -> *) s a b.
(Monad m, Traversable t) =>
(s -> a -> m (s, b)) -> s -> t a -> m (s, t b)
mapAccumM s -> a -> m (s, b)
f s
s t a
t = ((a -> StateT s m b) -> t a -> StateT s m (t b))
-> (a -> StateT s m b) -> t a -> s -> m (s, t b)
forall a b. Coercible a b => a -> b
coerce (forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM @t @(StateT s m) @a @b) ((s -> m (s, b)) -> StateT s m b
forall s (m :: * -> *) a. (s -> m (s, a)) -> StateT s m a
StateT ((s -> m (s, b)) -> StateT s m b)
-> (a -> s -> m (s, b)) -> a -> StateT s m b
forall b c a. Coercible b c => (b -> c) -> (a -> b) -> a -> c
#. (s -> a -> m (s, b)) -> a -> s -> m (s, b)
forall a b c. (a -> b -> c) -> b -> a -> c
flip s -> a -> m (s, b)
f) t a
t s
s
forAccumM
:: (Monad m, Traversable t)
=> s -> t a -> (s -> a -> m (s, b)) -> m (s, t b)
{-# INLINE forAccumM #-}
forAccumM :: forall (m :: * -> *) (t :: * -> *) s a b.
(Monad m, Traversable t) =>
s -> t a -> (s -> a -> m (s, b)) -> m (s, t b)
forAccumM s
s t a
t s -> a -> m (s, b)
f = (s -> a -> m (s, b)) -> s -> t a -> m (s, t b)
forall (m :: * -> *) (t :: * -> *) s a b.
(Monad m, Traversable t) =>
(s -> a -> m (s, b)) -> s -> t a -> m (s, t b)
mapAccumM s -> a -> m (s, b)
f s
s t a
t
fmapDefault :: forall t a b . Traversable t
=> (a -> b) -> t a -> t b
{-# INLINE fmapDefault #-}
fmapDefault :: forall (t :: * -> *) a b. Traversable t => (a -> b) -> t a -> t b
fmapDefault = ((a -> Identity b) -> t a -> Identity (t b))
-> (a -> b) -> t a -> t b
forall a b. Coercible a b => a -> b
coerce (forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse @t @Identity @a @b)
foldMapDefault :: forall t m a . (Traversable t, Monoid m)
=> (a -> m) -> t a -> m
{-# INLINE foldMapDefault #-}
foldMapDefault :: forall (t :: * -> *) m a.
(Traversable t, Monoid m) =>
(a -> m) -> t a -> m
foldMapDefault = ((a -> Const m ()) -> t a -> Const m (t ()))
-> (a -> m) -> t a -> m
forall a b. Coercible a b => a -> b
coerce (forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse @t @(Const m) @a @())