{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE EmptyCase #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE LinearTypes #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_HADDOCK hide #-}
module Data.Functor.Linear.Internal.Traversable
(
Traversable (..),
genericTraverse,
GTraversable,
mapM,
sequenceA,
for,
forM,
mapAccumL,
mapAccumR,
)
where
import qualified Control.Functor.Linear.Internal.Class as Control
import qualified Control.Functor.Linear.Internal.Instances as Control
import Control.Functor.Linear.Internal.Kan
import qualified Control.Functor.Linear.Internal.State as Control
import Data.Functor.Const
import qualified Data.Functor.Linear.Internal.Applicative as Data
import qualified Data.Functor.Linear.Internal.Functor as Data
import GHC.Types (Multiplicity (..))
import Generics.Linear
import Prelude.Linear.Internal
import Prelude (Either (..), Maybe (..))
class (Data.Functor t) => Traversable t where
{-# MINIMAL traverse | sequence #-}
traverse :: (Control.Applicative f) => (a %1 -> f b) -> t a %1 -> f (t b)
{-# INLINE traverse #-}
traverse a %1 -> f b
f t a
x = forall (t :: * -> *) (f :: * -> *) a.
(Traversable t, Applicative f) =>
t (f a) %1 -> f (t a)
sequence (forall (f :: * -> *) a b. Functor f => (a %1 -> b) -> f a %1 -> f b
Data.fmap a %1 -> f b
f t a
x)
sequence :: (Control.Applicative f) => t (f a) %1 -> f (t a)
{-# INLINE sequence #-}
sequence = forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a %1 -> f b) -> t a %1 -> f (t b)
traverse forall a (q :: Multiplicity). a %q -> a
id
mapM :: (Traversable t, Control.Monad m) => (a %1 -> m b) -> t a %1 -> m (t b)
mapM :: forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a %1 -> m b) -> t a %1 -> m (t b)
mapM = forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a %1 -> f b) -> t a %1 -> f (t b)
traverse
{-# INLINE mapM #-}
sequenceA :: (Traversable t, Control.Applicative f) => t (f a) %1 -> f (t a)
sequenceA :: forall (t :: * -> *) (f :: * -> *) a.
(Traversable t, Applicative f) =>
t (f a) %1 -> f (t a)
sequenceA = forall (t :: * -> *) (f :: * -> *) a.
(Traversable t, Applicative f) =>
t (f a) %1 -> f (t a)
sequence
{-# INLINE sequenceA #-}
for :: (Traversable t, Control.Applicative f) => t a %1 -> (a %1 -> f b) -> f (t b)
for :: forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
t a %1 -> (a %1 -> f b) -> f (t b)
for t a
t a %1 -> f b
f = forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a %1 -> f b) -> t a %1 -> f (t b)
traverse a %1 -> f b
f t a
t
{-# INLINE for #-}
forM :: (Traversable t, Control.Monad m) => t a %1 -> (a %1 -> m b) -> m (t b)
forM :: forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a %1 -> (a %1 -> m b) -> m (t b)
forM = forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
t a %1 -> (a %1 -> f b) -> f (t b)
for
{-# INLINE forM #-}
mapAccumL :: (Traversable t) => (a %1 -> b %1 -> (a, c)) -> a %1 -> t b %1 -> (a, t c)
mapAccumL :: forall (t :: * -> *) a b c.
Traversable t =>
(a %1 -> b %1 -> (a, c)) -> a %1 -> t b %1 -> (a, t c)
mapAccumL a %1 -> b %1 -> (a, c)
f a
s t b
t = forall a b. (a, b) %1 -> (b, a)
swap forall a b (p :: Multiplicity) (q :: Multiplicity).
(a %p -> b) %q -> a %p -> b
$ forall s a. State s a %1 -> s %1 -> (a, s)
Control.runState (forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a %1 -> f b) -> t a %1 -> f (t b)
traverse (\b
b -> forall (m :: * -> *) s a.
Applicative m =>
(s %1 -> (a, s)) %1 -> StateT s m a
Control.state forall a b (p :: Multiplicity) (q :: Multiplicity).
(a %p -> b) %q -> a %p -> b
$ \a
i -> forall a b. (a, b) %1 -> (b, a)
swap forall a b (p :: Multiplicity) (q :: Multiplicity).
(a %p -> b) %q -> a %p -> b
$ a %1 -> b %1 -> (a, c)
f a
i b
b) t b
t) a
s
mapAccumR :: (Traversable t) => (a %1 -> b %1 -> (a, c)) -> a %1 -> t b %1 -> (a, t c)
mapAccumR :: forall (t :: * -> *) a b c.
Traversable t =>
(a %1 -> b %1 -> (a, c)) -> a %1 -> t b %1 -> (a, t c)
mapAccumR a %1 -> b %1 -> (a, c)
f a
s t b
t = forall a b. (a, b) %1 -> (b, a)
swap forall a b (p :: Multiplicity) (q :: Multiplicity).
(a %p -> b) %q -> a %p -> b
$ forall s a. StateR s a %1 -> s %1 -> (a, s)
runStateR (forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a %1 -> f b) -> t a %1 -> f (t b)
traverse (\b
b -> forall s a. (s %1 -> (a, s)) -> StateR s a
StateR forall a b (p :: Multiplicity) (q :: Multiplicity).
(a %p -> b) %q -> a %p -> b
$ \a
i -> forall a b. (a, b) %1 -> (b, a)
swap forall a b (p :: Multiplicity) (q :: Multiplicity).
(a %p -> b) %q -> a %p -> b
$ a %1 -> b %1 -> (a, c)
f a
i b
b) t b
t) a
s
swap :: (a, b) %1 -> (b, a)
swap :: forall a b. (a, b) %1 -> (b, a)
swap (a
x, b
y) = (b
y, a
x)
newtype StateR s a = StateR (s %1 -> (a, s))
deriving (forall a b. (a %1 -> b) -> StateR s a %1 -> StateR s b
forall s a b. (a %1 -> b) -> StateR s a %1 -> StateR s b
forall (f :: * -> *).
(forall a b. (a %1 -> b) -> f a %1 -> f b) -> Functor f
fmap :: forall a b. (a %1 -> b) -> StateR s a %1 -> StateR s b
$cfmap :: forall s a b. (a %1 -> b) -> StateR s a %1 -> StateR s b
Data.Functor, forall s. Functor (StateR s)
forall a. a -> StateR s a
forall s a. a -> StateR s a
forall a b. StateR s (a %1 -> b) %1 -> StateR s a %1 -> StateR s b
forall s a b.
StateR s (a %1 -> b) %1 -> StateR s a %1 -> StateR s b
forall a b c.
(a %1 -> b %1 -> c) -> StateR s a %1 -> StateR s b %1 -> StateR s c
forall s a b c.
(a %1 -> b %1 -> c) -> StateR s a %1 -> StateR s b %1 -> StateR s c
forall (f :: * -> *).
Functor f
-> (forall a. a -> f a)
-> (forall a b. f (a %1 -> b) %1 -> f a %1 -> f b)
-> (forall a b c. (a %1 -> b %1 -> c) -> f a %1 -> f b %1 -> f c)
-> Applicative f
liftA2 :: forall a b c.
(a %1 -> b %1 -> c) -> StateR s a %1 -> StateR s b %1 -> StateR s c
$cliftA2 :: forall s a b c.
(a %1 -> b %1 -> c) -> StateR s a %1 -> StateR s b %1 -> StateR s c
<*> :: forall a b. StateR s (a %1 -> b) %1 -> StateR s a %1 -> StateR s b
$c<*> :: forall s a b.
StateR s (a %1 -> b) %1 -> StateR s a %1 -> StateR s b
pure :: forall a. a -> StateR s a
$cpure :: forall s a. a -> StateR s a
Data.Applicative) via Control.Data (StateR s)
runStateR :: StateR s a %1 -> s %1 -> (a, s)
runStateR :: forall s a. StateR s a %1 -> s %1 -> (a, s)
runStateR (StateR s %1 -> (a, s)
f) = s %1 -> (a, s)
f
instance Control.Functor (StateR s) where
fmap :: forall a b. (a %1 -> b) %1 -> StateR s a %1 -> StateR s b
fmap a %1 -> b
f (StateR s %1 -> (a, s)
x) = forall s a. (s %1 -> (a, s)) -> StateR s a
StateR forall a b (p :: Multiplicity) (q :: Multiplicity).
(a %p -> b) %q -> a %p -> b
$ (\(a
a, s
s') -> (a %1 -> b
f a
a, s
s')) forall b c a (q :: Multiplicity) (m :: Multiplicity)
(n :: Multiplicity).
(b %1 -> c) %q -> (a %1 -> b) %m -> a %n -> c
. s %1 -> (a, s)
x
instance Control.Applicative (StateR s) where
pure :: forall a. a %1 -> StateR s a
pure a
x = forall s a. (s %1 -> (a, s)) -> StateR s a
StateR forall a b (p :: Multiplicity) (q :: Multiplicity).
(a %p -> b) %q -> a %p -> b
$ \s
s -> (a
x, s
s)
StateR s %1 -> (a %1 -> b, s)
f <*> :: forall a b. StateR s (a %1 -> b) %1 -> StateR s a %1 -> StateR s b
<*> StateR s %1 -> (a, s)
x = forall s a. (s %1 -> (a, s)) -> StateR s a
StateR (forall a b s. (a, (a %1 -> b, s)) %1 -> (b, s)
go forall b c a (q :: Multiplicity) (m :: Multiplicity)
(n :: Multiplicity).
(b %1 -> c) %q -> (a %1 -> b) %m -> a %n -> c
. forall (f :: * -> *) a b.
Functor f =>
(a %1 -> b) %1 -> f a %1 -> f b
Control.fmap s %1 -> (a %1 -> b, s)
f forall b c a (q :: Multiplicity) (m :: Multiplicity)
(n :: Multiplicity).
(b %1 -> c) %q -> (a %1 -> b) %m -> a %n -> c
. s %1 -> (a, s)
x)
where
go :: (a, (a %1 -> b, s)) %1 -> (b, s)
go :: forall a b s. (a, (a %1 -> b, s)) %1 -> (b, s)
go (a
a, (a %1 -> b
h, s
s'')) = (a %1 -> b
h a
a, s
s'')
instance Traversable [] where
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a %1 -> f b) -> [a] %1 -> f [b]
traverse a %1 -> f b
f = [a] %1 -> f [b]
go
where
go :: [a] %1 -> f [b]
go [] = forall (f :: * -> *) a. Applicative f => a %1 -> f a
Control.pure []
go (a
x : [a]
xs) = forall (f :: * -> *) a b c.
Applicative f =>
(a %1 -> b %1 -> c) %1 -> f a %1 -> f b %1 -> f c
Control.liftA2 (:) (a %1 -> f b
f a
x) ([a] %1 -> f [b]
go [a]
xs)
instance Traversable ((,) a) where
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a %1 -> f b) -> (a, a) %1 -> f (a, b)
traverse = forall (t :: * -> *) (f :: * -> *) a b.
(Generic1 t, GTraversable (Rep1 t), Applicative f) =>
(a %1 -> f b) -> t a %1 -> f (t b)
genericTraverse
instance Traversable ((,,) a b) where
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a %1 -> f b) -> (a, b, a) %1 -> f (a, b, b)
traverse = forall (t :: * -> *) (f :: * -> *) a b.
(Generic1 t, GTraversable (Rep1 t), Applicative f) =>
(a %1 -> f b) -> t a %1 -> f (t b)
genericTraverse
instance Traversable ((,,,) a b c) where
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a %1 -> f b) -> (a, b, c, a) %1 -> f (a, b, c, b)
traverse = forall (t :: * -> *) (f :: * -> *) a b.
(Generic1 t, GTraversable (Rep1 t), Applicative f) =>
(a %1 -> f b) -> t a %1 -> f (t b)
genericTraverse
instance Traversable ((,,,,) a b c d) where
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a %1 -> f b) -> (a, b, c, d, a) %1 -> f (a, b, c, d, b)
traverse = forall (t :: * -> *) (f :: * -> *) a b.
(Generic1 t, GTraversable (Rep1 t), Applicative f) =>
(a %1 -> f b) -> t a %1 -> f (t b)
genericTraverse
instance Traversable Maybe where
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a %1 -> f b) -> Maybe a %1 -> f (Maybe b)
traverse = forall (t :: * -> *) (f :: * -> *) a b.
(Generic1 t, GTraversable (Rep1 t), Applicative f) =>
(a %1 -> f b) -> t a %1 -> f (t b)
genericTraverse
instance Traversable (Const a) where
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a %1 -> f b) -> Const a a %1 -> f (Const a b)
traverse = forall (t :: * -> *) (f :: * -> *) a b.
(Generic1 t, GTraversable (Rep1 t), Applicative f) =>
(a %1 -> f b) -> t a %1 -> f (t b)
genericTraverse
instance Traversable (Either a) where
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a %1 -> f b) -> Either a a %1 -> f (Either a b)
traverse = forall (t :: * -> *) (f :: * -> *) a b.
(Generic1 t, GTraversable (Rep1 t), Applicative f) =>
(a %1 -> f b) -> t a %1 -> f (t b)
genericTraverse
instance Traversable U1 where
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a %1 -> f b) -> U1 a %1 -> f (U1 b)
traverse = forall (t :: * -> *) (f :: * -> *) a b.
(Generic1 t, GTraversable (Rep1 t), Applicative f) =>
(a %1 -> f b) -> t a %1 -> f (t b)
genericTraverse
instance Traversable V1 where
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a %1 -> f b) -> V1 a %1 -> f (V1 b)
traverse = forall (t :: * -> *) (f :: * -> *) a b.
(Generic1 t, GTraversable (Rep1 t), Applicative f) =>
(a %1 -> f b) -> t a %1 -> f (t b)
genericTraverse
instance (Traversable f, Traversable g) => Traversable (f :*: g) where
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a %1 -> f b) -> (:*:) f g a %1 -> f ((:*:) f g b)
traverse = forall (t :: * -> *) (f :: * -> *) a b.
(Generic1 t, GTraversable (Rep1 t), Applicative f) =>
(a %1 -> f b) -> t a %1 -> f (t b)
genericTraverse
instance (Traversable f, Traversable g) => Traversable (f :+: g) where
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a %1 -> f b) -> (:+:) f g a %1 -> f ((:+:) f g b)
traverse = forall (t :: * -> *) (f :: * -> *) a b.
(Generic1 t, GTraversable (Rep1 t), Applicative f) =>
(a %1 -> f b) -> t a %1 -> f (t b)
genericTraverse
instance (Traversable f) => Traversable (M1 i c f) where
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a %1 -> f b) -> M1 i c f a %1 -> f (M1 i c f b)
traverse = forall (t :: * -> *) (f :: * -> *) a b.
(Generic1 t, GTraversable (Rep1 t), Applicative f) =>
(a %1 -> f b) -> t a %1 -> f (t b)
genericTraverse
instance Traversable Par1 where
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a %1 -> f b) -> Par1 a %1 -> f (Par1 b)
traverse = forall (t :: * -> *) (f :: * -> *) a b.
(Generic1 t, GTraversable (Rep1 t), Applicative f) =>
(a %1 -> f b) -> t a %1 -> f (t b)
genericTraverse
instance (Traversable f, Traversable g) => Traversable (f :.: g) where
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a %1 -> f b) -> (:.:) f g a %1 -> f ((:.:) f g b)
traverse = forall (t :: * -> *) (f :: * -> *) a b.
(Generic1 t, GTraversable (Rep1 t), Applicative f) =>
(a %1 -> f b) -> t a %1 -> f (t b)
genericTraverse
instance Traversable (K1 i v) where
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a %1 -> f b) -> K1 i v a %1 -> f (K1 i v b)
traverse = forall (t :: * -> *) (f :: * -> *) a b.
(Generic1 t, GTraversable (Rep1 t), Applicative f) =>
(a %1 -> f b) -> t a %1 -> f (t b)
genericTraverse
instance Traversable UAddr where
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a %1 -> f b) -> UAddr a %1 -> f (UAddr b)
traverse = forall (t :: * -> *) (f :: * -> *) a b.
(Generic1 t, GTraversable (Rep1 t), Applicative f) =>
(a %1 -> f b) -> t a %1 -> f (t b)
genericTraverse
instance Traversable UChar where
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a %1 -> f b) -> UChar a %1 -> f (UChar b)
traverse = forall (t :: * -> *) (f :: * -> *) a b.
(Generic1 t, GTraversable (Rep1 t), Applicative f) =>
(a %1 -> f b) -> t a %1 -> f (t b)
genericTraverse
instance Traversable UDouble where
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a %1 -> f b) -> UDouble a %1 -> f (UDouble b)
traverse = forall (t :: * -> *) (f :: * -> *) a b.
(Generic1 t, GTraversable (Rep1 t), Applicative f) =>
(a %1 -> f b) -> t a %1 -> f (t b)
genericTraverse
instance Traversable UFloat where
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a %1 -> f b) -> UFloat a %1 -> f (UFloat b)
traverse = forall (t :: * -> *) (f :: * -> *) a b.
(Generic1 t, GTraversable (Rep1 t), Applicative f) =>
(a %1 -> f b) -> t a %1 -> f (t b)
genericTraverse
instance Traversable UInt where
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a %1 -> f b) -> UInt a %1 -> f (UInt b)
traverse = forall (t :: * -> *) (f :: * -> *) a b.
(Generic1 t, GTraversable (Rep1 t), Applicative f) =>
(a %1 -> f b) -> t a %1 -> f (t b)
genericTraverse
instance Traversable UWord where
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a %1 -> f b) -> UWord a %1 -> f (UWord b)
traverse = forall (t :: * -> *) (f :: * -> *) a b.
(Generic1 t, GTraversable (Rep1 t), Applicative f) =>
(a %1 -> f b) -> t a %1 -> f (t b)
genericTraverse
class GTraversable t where
gtraverse :: (Control.Applicative f) => (a %1 -> f b) -> t a %1 -> Curried (Yoneda f) (Yoneda f) (t b)
instance (GTraversable t) => GTraversable (M1 i c t) where
gtraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a %1 -> f b)
-> M1 i c t a %1 -> Curried (Yoneda f) (Yoneda f) (M1 i c t b)
gtraverse a %1 -> f b
f (M1 t a
x) = forall a b. Coercible a b => a %1 -> b
lcoerce (forall (t :: * -> *) (f :: * -> *) a b.
(GTraversable t, Applicative f) =>
(a %1 -> f b) -> t a %1 -> Curried (Yoneda f) (Yoneda f) (t b)
gtraverse a %1 -> f b
f t a
x)
{-# INLINE gtraverse #-}
instance (m ~ 'One, GTraversable t) => GTraversable (MP1 m t) where
gtraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a %1 -> f b)
-> MP1 m t a %1 -> Curried (Yoneda f) (Yoneda f) (MP1 m t b)
gtraverse a %1 -> f b
f (MP1 t a
x) = forall (f :: * -> *) a b.
Functor f =>
(a %1 -> b) %1 -> f a %1 -> f b
Control.fmap forall {k} (b :: k -> *) (c :: k) (a :: Multiplicity).
b c %a -> MP1 a b c
MP1 (forall (t :: * -> *) (f :: * -> *) a b.
(GTraversable t, Applicative f) =>
(a %1 -> f b) -> t a %1 -> Curried (Yoneda f) (Yoneda f) (t b)
gtraverse a %1 -> f b
f t a
x)
{-# INLINE gtraverse #-}
instance GTraversable Par1 where
gtraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a %1 -> f b)
-> Par1 a %1 -> Curried (Yoneda f) (Yoneda f) (Par1 b)
gtraverse a %1 -> f b
f (Par1 a
x) = forall a b. Coercible a b => a %1 -> b
lcoerce (forall (f :: * -> *) a.
Applicative f =>
f a %1 -> Curried (Yoneda f) (Yoneda f) a
liftCurriedYonedaC (a %1 -> f b
f a
x))
{-# INLINE gtraverse #-}
instance (GTraversable f, Traversable g) => GTraversable (f :.: g) where
gtraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a %1 -> f b)
-> (:.:) f g a %1 -> Curried (Yoneda f) (Yoneda f) ((:.:) f g b)
gtraverse a %1 -> f b
f (Comp1 f (g a)
x) = forall a b. Coercible a b => a %1 -> b
lcoerce (forall (t :: * -> *) (f :: * -> *) a b.
(GTraversable t, Applicative f) =>
(a %1 -> f b) -> t a %1 -> Curried (Yoneda f) (Yoneda f) (t b)
gtraverse (forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a %1 -> f b) -> t a %1 -> f (t b)
traverse a %1 -> f b
f) f (g a)
x)
{-# INLINE gtraverse #-}
instance (GTraversable f, GTraversable g) => GTraversable (f :+: g) where
gtraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a %1 -> f b)
-> (:+:) f g a %1 -> Curried (Yoneda f) (Yoneda f) ((:+:) f g b)
gtraverse a %1 -> f b
f (L1 f a
x) = forall k (f :: k -> *) (g :: k -> *) (p :: k). f p -> (:+:) f g p
L1 forall (f :: * -> *) a b.
Functor f =>
(a %1 -> b) %1 -> f a %1 -> f b
Control.<$> forall (t :: * -> *) (f :: * -> *) a b.
(GTraversable t, Applicative f) =>
(a %1 -> f b) -> t a %1 -> Curried (Yoneda f) (Yoneda f) (t b)
gtraverse a %1 -> f b
f f a
x
gtraverse a %1 -> f b
f (R1 g a
x) = forall k (f :: k -> *) (g :: k -> *) (p :: k). g p -> (:+:) f g p
R1 forall (f :: * -> *) a b.
Functor f =>
(a %1 -> b) %1 -> f a %1 -> f b
Control.<$> forall (t :: * -> *) (f :: * -> *) a b.
(GTraversable t, Applicative f) =>
(a %1 -> f b) -> t a %1 -> Curried (Yoneda f) (Yoneda f) (t b)
gtraverse a %1 -> f b
f g a
x
{-# INLINE gtraverse #-}
instance (GTraversable f, GTraversable g) => GTraversable (f :*: g) where
gtraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a %1 -> f b)
-> (:*:) f g a %1 -> Curried (Yoneda f) (Yoneda f) ((:*:) f g b)
gtraverse a %1 -> f b
f (f a
x :*: g a
y) = forall (f :: * -> *) a b c.
Applicative f =>
(a %1 -> b %1 -> c) %1 -> f a %1 -> f b %1 -> f c
Control.liftA2 forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
(:*:) (forall (t :: * -> *) (f :: * -> *) a b.
(GTraversable t, Applicative f) =>
(a %1 -> f b) -> t a %1 -> Curried (Yoneda f) (Yoneda f) (t b)
gtraverse a %1 -> f b
f f a
x) (forall (t :: * -> *) (f :: * -> *) a b.
(GTraversable t, Applicative f) =>
(a %1 -> f b) -> t a %1 -> Curried (Yoneda f) (Yoneda f) (t b)
gtraverse a %1 -> f b
f g a
y)
{-# INLINE gtraverse #-}
instance GTraversable (K1 i c) where
gtraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a %1 -> f b)
-> K1 i c a %1 -> Curried (Yoneda f) (Yoneda f) (K1 i c b)
gtraverse a %1 -> f b
_ (K1 c
c) = forall (f :: * -> *) a. Applicative f => a %1 -> f a
Control.pure (forall k i c (p :: k). c -> K1 i c p
K1 c
c)
{-# INLINE gtraverse #-}
instance GTraversable U1 where
gtraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a %1 -> f b) -> U1 a %1 -> Curried (Yoneda f) (Yoneda f) (U1 b)
gtraverse a %1 -> f b
_ U1 a
U1 = forall (f :: * -> *) a. Applicative f => a %1 -> f a
Control.pure forall k (p :: k). U1 p
U1
{-# INLINE gtraverse #-}
instance GTraversable V1 where
gtraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a %1 -> f b) -> V1 a %1 -> Curried (Yoneda f) (Yoneda f) (V1 b)
gtraverse a %1 -> f b
_ V1 a
v = forall (f :: * -> *) a. Applicative f => a %1 -> f a
Control.pure ((\case {}) V1 a
v)
instance GTraversable UAddr where
gtraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a %1 -> f b)
-> UAddr a %1 -> Curried (Yoneda f) (Yoneda f) (UAddr b)
gtraverse a %1 -> f b
_ (UAddr Addr#
x) = forall (f :: * -> *) a. Applicative f => a %1 -> f a
Control.pure (forall k (p :: k). Addr# -> URec (Ptr ()) p
UAddr Addr#
x)
{-# INLINE gtraverse #-}
instance GTraversable UChar where
gtraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a %1 -> f b)
-> UChar a %1 -> Curried (Yoneda f) (Yoneda f) (UChar b)
gtraverse a %1 -> f b
_ (UChar Char#
x) = forall (f :: * -> *) a. Applicative f => a %1 -> f a
Control.pure (forall k (p :: k). Char# -> URec Char p
UChar Char#
x)
{-# INLINE gtraverse #-}
instance GTraversable UDouble where
gtraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a %1 -> f b)
-> UDouble a %1 -> Curried (Yoneda f) (Yoneda f) (UDouble b)
gtraverse a %1 -> f b
_ (UDouble Double#
x) = forall (f :: * -> *) a. Applicative f => a %1 -> f a
Control.pure (forall k (p :: k). Double# -> URec Double p
UDouble Double#
x)
{-# INLINE gtraverse #-}
instance GTraversable UFloat where
gtraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a %1 -> f b)
-> UFloat a %1 -> Curried (Yoneda f) (Yoneda f) (UFloat b)
gtraverse a %1 -> f b
_ (UFloat Float#
x) = forall (f :: * -> *) a. Applicative f => a %1 -> f a
Control.pure (forall k (p :: k). Float# -> URec Float p
UFloat Float#
x)
{-# INLINE gtraverse #-}
instance GTraversable UInt where
gtraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a %1 -> f b)
-> UInt a %1 -> Curried (Yoneda f) (Yoneda f) (UInt b)
gtraverse a %1 -> f b
_ (UInt Int#
x) = forall (f :: * -> *) a. Applicative f => a %1 -> f a
Control.pure (forall k (p :: k). Int# -> URec Int p
UInt Int#
x)
{-# INLINE gtraverse #-}
instance GTraversable UWord where
gtraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a %1 -> f b)
-> UWord a %1 -> Curried (Yoneda f) (Yoneda f) (UWord b)
gtraverse a %1 -> f b
_ (UWord Word#
x) = forall (f :: * -> *) a. Applicative f => a %1 -> f a
Control.pure (forall k (p :: k). Word# -> URec Word p
UWord Word#
x)
{-# INLINE gtraverse #-}
genericTraverse ::
(Generic1 t, GTraversable (Rep1 t), Control.Applicative f) =>
(a %1 -> f b) ->
t a %1 ->
f (t b)
genericTraverse :: forall (t :: * -> *) (f :: * -> *) a b.
(Generic1 t, GTraversable (Rep1 t), Applicative f) =>
(a %1 -> f b) -> t a %1 -> f (t b)
genericTraverse a %1 -> f b
f = forall (f :: * -> *) a. Yoneda f a %1 -> f a
lowerYoneda forall b c a (q :: Multiplicity) (m :: Multiplicity)
(n :: Multiplicity).
(b %1 -> c) %q -> (a %1 -> b) %m -> a %n -> c
. forall (f :: * -> *) (g :: * -> *) a.
Applicative f =>
Curried f g a %1 -> g a
lowerCurriedC forall b c a (q :: Multiplicity) (m :: Multiplicity)
(n :: Multiplicity).
(b %1 -> c) %q -> (a %1 -> b) %m -> a %n -> c
. forall (f :: * -> *) a b.
Functor f =>
(a %1 -> b) %1 -> f a %1 -> f b
Control.fmap forall {k} (f :: k -> *) (p :: k) (m :: Multiplicity).
Generic1 f =>
Rep1 f p %m -> f p
to1 forall b c a (q :: Multiplicity) (m :: Multiplicity)
(n :: Multiplicity).
(b %1 -> c) %q -> (a %1 -> b) %m -> a %n -> c
. forall (t :: * -> *) (f :: * -> *) a b.
(GTraversable t, Applicative f) =>
(a %1 -> f b) -> t a %1 -> Curried (Yoneda f) (Yoneda f) (t b)
gtraverse a %1 -> f b
f forall b c a (q :: Multiplicity) (m :: Multiplicity)
(n :: Multiplicity).
(b %1 -> c) %q -> (a %1 -> b) %m -> a %n -> c
. forall {k} (f :: k -> *) (p :: k) (m :: Multiplicity).
Generic1 f =>
f p %m -> Rep1 f p
from1
{-# INLINE genericTraverse #-}