{-# 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 = t (f b) %1 -> f (t b)
forall (t :: * -> *) (f :: * -> *) a.
(Traversable t, Applicative f) =>
t (f a) %1 -> f (t a)
forall (f :: * -> *) a. Applicative f => t (f a) %1 -> f (t a)
sequence ((a %1 -> f b) -> t a %1 -> t (f b)
forall a b. (a %1 -> b) -> t a %1 -> t b
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 = (f a %1 -> f a) -> t (f a) %1 -> f (t a)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a %1 -> f b) -> t a %1 -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a %1 -> f b) -> t a %1 -> f (t b)
traverse f a %1 -> f a
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 = (a %1 -> m b) -> t a %1 -> m (t b)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a %1 -> f b) -> t a %1 -> f (t b)
forall (f :: * -> *) a b.
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 = t (f a) %1 -> f (t a)
forall (t :: * -> *) (f :: * -> *) a.
(Traversable t, Applicative f) =>
t (f a) %1 -> f (t a)
forall (f :: * -> *) a. 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 = (a %1 -> f b) -> t a %1 -> f (t b)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a %1 -> f b) -> t a %1 -> f (t b)
forall (f :: * -> *) a b.
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 = t a %1 -> (a %1 -> m b) -> m (t b)
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 = (t c, a) %1 -> (a, t c)
forall a b. (a, b) %1 -> (b, a)
swap ((t c, a) %1 -> (a, t c)) -> (t c, a) %1 -> (a, t c)
forall a b (p :: Multiplicity) (q :: Multiplicity).
(a %p -> b) %q -> a %p -> b
$ State a (t c) %1 -> a %1 -> (t c, a)
forall s a. State s a %1 -> s %1 -> (a, s)
Control.runState ((b %1 -> StateT a Identity c) -> t b %1 -> State a (t c)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a %1 -> f b) -> t a %1 -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a %1 -> f b) -> t a %1 -> f (t b)
traverse (\b
b -> (a %1 -> (c, a)) %1 -> StateT a Identity c
forall (m :: * -> *) s a.
Applicative m =>
(s %1 -> (a, s)) %1 -> StateT s m a
Control.state ((a %1 -> (c, a)) %1 -> StateT a Identity c)
-> (a %1 -> (c, a)) %1 -> StateT a Identity c
forall a b (p :: Multiplicity) (q :: Multiplicity).
(a %p -> b) %q -> a %p -> b
$ \a
i -> (a, c) %1 -> (c, a)
forall a b. (a, b) %1 -> (b, a)
swap ((a, c) %1 -> (c, a)) -> (a, c) %1 -> (c, a)
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 = (t c, a) %1 -> (a, t c)
forall a b. (a, b) %1 -> (b, a)
swap ((t c, a) %1 -> (a, t c)) -> (t c, a) %1 -> (a, t c)
forall a b (p :: Multiplicity) (q :: Multiplicity).
(a %p -> b) %q -> a %p -> b
$ StateR a (t c) %1 -> a %1 -> (t c, a)
forall s a. StateR s a %1 -> s %1 -> (a, s)
runStateR ((b %1 -> StateR a c) -> t b %1 -> StateR a (t c)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a %1 -> f b) -> t a %1 -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a %1 -> f b) -> t a %1 -> f (t b)
traverse (\b
b -> (a %1 -> (c, a)) -> StateR a c
forall s a. (s %1 -> (a, s)) -> StateR s a
StateR ((a %1 -> (c, a)) %1 -> StateR a c)
-> (a %1 -> (c, a)) %1 -> StateR a c
forall a b (p :: Multiplicity) (q :: Multiplicity).
(a %p -> b) %q -> a %p -> b
$ \a
i -> (a, c) %1 -> (c, a)
forall a b. (a, b) %1 -> (b, a)
swap ((a, c) %1 -> (c, a)) -> (a, c) %1 -> (c, a)
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)
-> Functor (StateR s)
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
$cfmap :: forall s a b. (a %1 -> b) -> StateR s a %1 -> StateR s b
fmap :: forall a b. (a %1 -> b) -> StateR s a %1 -> StateR s b
Data.Functor, Functor (StateR s)
Functor (StateR s) =>
(forall a. a -> StateR s a)
-> (forall 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)
-> Applicative (StateR s)
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
$cpure :: forall s a. a -> StateR s a
pure :: forall a. a -> StateR s a
$c<*> :: forall s a b.
StateR s (a %1 -> b) %1 -> StateR s a %1 -> StateR s b
<*> :: forall a b. StateR s (a %1 -> b) %1 -> StateR s a %1 -> StateR s b
$cliftA2 :: forall s a b c.
(a %1 -> b %1 -> c) -> StateR s a %1 -> StateR s b %1 -> StateR s c
liftA2 :: forall a b c.
(a %1 -> b %1 -> c) -> StateR s a %1 -> StateR s b %1 -> StateR s c
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) = (s %1 -> (b, s)) -> StateR s b
forall s a. (s %1 -> (a, s)) -> StateR s a
StateR ((s %1 -> (b, s)) %1 -> StateR s b)
-> (s %1 -> (b, s)) %1 -> StateR s b
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')) ((a, s) %1 -> (b, s)) %1 -> (s %1 -> (a, s)) %1 -> s %1 -> (b, 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 = (s %1 -> (a, s)) -> StateR s a
forall s a. (s %1 -> (a, s)) -> StateR s a
StateR ((s %1 -> (a, s)) %1 -> StateR s a)
-> (s %1 -> (a, s)) %1 -> StateR s a
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 = (s %1 -> (b, s)) -> StateR s b
forall s a. (s %1 -> (a, s)) -> StateR s a
StateR ((a, (a %1 -> b, s)) %1 -> (b, s)
forall a b s. (a, (a %1 -> b, s)) %1 -> (b, s)
go ((a, (a %1 -> b, s)) %1 -> (b, s))
-> (s %1 -> (a, (a %1 -> b, s))) %1 -> s %1 -> (b, 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 %1 -> b, s)) %1 -> (a, s) %1 -> (a, (a %1 -> b, s))
forall a b. (a %1 -> b) %1 -> (a, a) %1 -> (a, b)
forall (f :: * -> *) a b.
Functor f =>
(a %1 -> b) %1 -> f a %1 -> f b
Control.fmap s %1 -> (a %1 -> b, s)
f ((a, s) %1 -> (a, (a %1 -> b, s)))
%1 -> (s %1 -> (a, s)) %1 -> s %1 -> (a, (a %1 -> b, 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)
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 [] = [b] %1 -> f [b]
forall a. a %1 -> f a
forall (f :: * -> *) a. Applicative f => a %1 -> f a
Control.pure []
go (a
x : [a]
xs) = (b %1 -> [b] %1 -> [b]) %1 -> f b %1 -> f [b] %1 -> f [b]
forall a b c. (a %1 -> b %1 -> c) %1 -> f a %1 -> f b %1 -> f c
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 = (a %1 -> f b) -> (a, a) %1 -> f (a, b)
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 = (a %1 -> f b) -> (a, b, a) %1 -> f (a, b, b)
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 = (a %1 -> f b) -> (a, b, c, a) %1 -> f (a, b, c, b)
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 = (a %1 -> f b) -> (a, b, c, d, a) %1 -> f (a, b, c, d, b)
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 = (a %1 -> f b) -> Maybe a %1 -> f (Maybe b)
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 = (a %1 -> f b) -> Const a a %1 -> f (Const a b)
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 = (a %1 -> f b) -> Either a a %1 -> f (Either a b)
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 = (a %1 -> f b) -> U1 a %1 -> f (U1 b)
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 = (a %1 -> f b) -> V1 a %1 -> f (V1 b)
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 = (a %1 -> f b) -> (:*:) f g a %1 -> f ((:*:) f g b)
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 = (a %1 -> f b) -> (:+:) f g a %1 -> f ((:+:) f g b)
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 = (a %1 -> f b) -> M1 i c f a %1 -> f (M1 i c f b)
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 = (a %1 -> f b) -> Par1 a %1 -> f (Par1 b)
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 = (a %1 -> f b) -> (:.:) f g a %1 -> f ((:.:) f g b)
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 = (a %1 -> f b) -> K1 i v a %1 -> f (K1 i v b)
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 = (a %1 -> f b) -> URec (Ptr ()) a %1 -> f (URec (Ptr ()) b)
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 = (a %1 -> f b) -> URec Char a %1 -> f (URec Char b)
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 = (a %1 -> f b) -> URec Double a %1 -> f (URec Double b)
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 = (a %1 -> f b) -> URec Float a %1 -> f (URec Float b)
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 = (a %1 -> f b) -> URec Int a %1 -> f (URec Int b)
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 = (a %1 -> f b) -> URec Word a %1 -> f (URec Word b)
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) = Curried (Yoneda f) (Yoneda f) (t b)
%1 -> Curried (Yoneda f) (Yoneda f) (M1 i c t b)
forall a b. Coercible a b => a %1 -> b
lcoerce ((a %1 -> f b) -> t a %1 -> Curried (Yoneda f) (Yoneda f) (t b)
forall (t :: * -> *) (f :: * -> *) a b.
(GTraversable t, Applicative f) =>
(a %1 -> f b) -> t a %1 -> Curried (Yoneda f) (Yoneda f) (t b)
forall (f :: * -> *) a b.
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) = (t b %1 -> MP1 m t b)
%1 -> Curried (Yoneda f) (Yoneda f) (t b)
%1 -> Curried (Yoneda f) (Yoneda f) (MP1 m t b)
forall a b.
(a %1 -> b)
%1 -> Curried (Yoneda f) (Yoneda f) a
%1 -> Curried (Yoneda f) (Yoneda f) b
forall (f :: * -> *) a b.
Functor f =>
(a %1 -> b) %1 -> f a %1 -> f b
Control.fmap t b %m -> MP1 m t b
t b %1 -> MP1 m t b
forall {k} (b :: k -> *) (c :: k) (a :: Multiplicity).
b c %a -> MP1 a b c
MP1 ((a %1 -> f b) -> t a %1 -> Curried (Yoneda f) (Yoneda f) (t b)
forall (t :: * -> *) (f :: * -> *) a b.
(GTraversable t, Applicative f) =>
(a %1 -> f b) -> t a %1 -> Curried (Yoneda f) (Yoneda f) (t b)
forall (f :: * -> *) a b.
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) = Curried (Yoneda f) (Yoneda f) b
%1 -> Curried (Yoneda f) (Yoneda f) (Par1 b)
forall a b. Coercible a b => a %1 -> b
lcoerce (f b %1 -> Curried (Yoneda f) (Yoneda f) b
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) = Curried (Yoneda f) (Yoneda f) (f (g b))
%1 -> Curried (Yoneda f) (Yoneda f) ((:.:) f g b)
forall a b. Coercible a b => a %1 -> b
lcoerce ((g a %1 -> f (g b))
-> f (g a) %1 -> Curried (Yoneda f) (Yoneda f) (f (g b))
forall (t :: * -> *) (f :: * -> *) a b.
(GTraversable t, Applicative f) =>
(a %1 -> f b) -> t a %1 -> Curried (Yoneda f) (Yoneda f) (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a %1 -> f b) -> f a %1 -> Curried (Yoneda f) (Yoneda f) (f b)
gtraverse ((a %1 -> f b) -> g a %1 -> f (g b)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a %1 -> f b) -> t a %1 -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a %1 -> f b) -> g a %1 -> f (g 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) = f b -> (:+:) f g b
forall k (f :: k -> *) (g :: k -> *) (p :: k). f p -> (:+:) f g p
L1 (f b %1 -> (:+:) f g b)
%1 -> Curried (Yoneda f) (Yoneda f) (f b)
%1 -> Curried (Yoneda f) (Yoneda f) ((:+:) f g b)
forall (f :: * -> *) a b.
Functor f =>
(a %1 -> b) %1 -> f a %1 -> f b
Control.<$> (a %1 -> f b) -> f a %1 -> Curried (Yoneda f) (Yoneda f) (f b)
forall (t :: * -> *) (f :: * -> *) a b.
(GTraversable t, Applicative f) =>
(a %1 -> f b) -> t a %1 -> Curried (Yoneda f) (Yoneda f) (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a %1 -> f b) -> f a %1 -> Curried (Yoneda f) (Yoneda f) (f b)
gtraverse a %1 -> f b
f f a
x
gtraverse a %1 -> f b
f (R1 g a
x) = g b -> (:+:) f g b
forall k (f :: k -> *) (g :: k -> *) (p :: k). g p -> (:+:) f g p
R1 (g b %1 -> (:+:) f g b)
%1 -> Curried (Yoneda f) (Yoneda f) (g b)
%1 -> Curried (Yoneda f) (Yoneda f) ((:+:) f g b)
forall (f :: * -> *) a b.
Functor f =>
(a %1 -> b) %1 -> f a %1 -> f b
Control.<$> (a %1 -> f b) -> g a %1 -> Curried (Yoneda f) (Yoneda f) (g b)
forall (t :: * -> *) (f :: * -> *) a b.
(GTraversable t, Applicative f) =>
(a %1 -> f b) -> t a %1 -> Curried (Yoneda f) (Yoneda f) (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a %1 -> f b) -> g a %1 -> Curried (Yoneda f) (Yoneda f) (g 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) = (f b %1 -> g b %1 -> (:*:) f g b)
%1 -> Curried (Yoneda f) (Yoneda f) (f b)
%1 -> Curried (Yoneda f) (Yoneda f) (g b)
%1 -> Curried (Yoneda f) (Yoneda f) ((:*:) f g b)
forall a b c.
(a %1 -> b %1 -> c)
%1 -> Curried (Yoneda f) (Yoneda f) a
%1 -> Curried (Yoneda f) (Yoneda f) b
%1 -> Curried (Yoneda f) (Yoneda f) c
forall (f :: * -> *) a b c.
Applicative f =>
(a %1 -> b %1 -> c) %1 -> f a %1 -> f b %1 -> f c
Control.liftA2 f b -> g b -> (:*:) f g b
forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
(:*:) ((a %1 -> f b) -> f a %1 -> Curried (Yoneda f) (Yoneda f) (f b)
forall (t :: * -> *) (f :: * -> *) a b.
(GTraversable t, Applicative f) =>
(a %1 -> f b) -> t a %1 -> Curried (Yoneda f) (Yoneda f) (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a %1 -> f b) -> f a %1 -> Curried (Yoneda f) (Yoneda f) (f b)
gtraverse a %1 -> f b
f f a
x) ((a %1 -> f b) -> g a %1 -> Curried (Yoneda f) (Yoneda f) (g b)
forall (t :: * -> *) (f :: * -> *) a b.
(GTraversable t, Applicative f) =>
(a %1 -> f b) -> t a %1 -> Curried (Yoneda f) (Yoneda f) (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a %1 -> f b) -> g a %1 -> Curried (Yoneda f) (Yoneda f) (g 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) = K1 i c b %1 -> Curried (Yoneda f) (Yoneda f) (K1 i c b)
forall a. a %1 -> Curried (Yoneda f) (Yoneda f) a
forall (f :: * -> *) a. Applicative f => a %1 -> f a
Control.pure (c -> K1 i c b
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 = U1 b %1 -> Curried (Yoneda f) (Yoneda f) (U1 b)
forall a. a %1 -> Curried (Yoneda f) (Yoneda f) a
forall (f :: * -> *) a. Applicative f => a %1 -> f a
Control.pure U1 b
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 = V1 b %1 -> Curried (Yoneda f) (Yoneda f) (V1 b)
forall a. a %1 -> Curried (Yoneda f) (Yoneda f) a
forall (f :: * -> *) a. Applicative f => a %1 -> f a
Control.pure (case V1 a
v of {})
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) = UAddr b %1 -> Curried (Yoneda f) (Yoneda f) (UAddr b)
forall a. a %1 -> Curried (Yoneda f) (Yoneda f) a
forall (f :: * -> *) a. Applicative f => a %1 -> f a
Control.pure (Addr# -> UAddr b
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) = UChar b %1 -> Curried (Yoneda f) (Yoneda f) (UChar b)
forall a. a %1 -> Curried (Yoneda f) (Yoneda f) a
forall (f :: * -> *) a. Applicative f => a %1 -> f a
Control.pure (Char# -> UChar b
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) = UDouble b %1 -> Curried (Yoneda f) (Yoneda f) (UDouble b)
forall a. a %1 -> Curried (Yoneda f) (Yoneda f) a
forall (f :: * -> *) a. Applicative f => a %1 -> f a
Control.pure (Double# -> UDouble b
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) = UFloat b %1 -> Curried (Yoneda f) (Yoneda f) (UFloat b)
forall a. a %1 -> Curried (Yoneda f) (Yoneda f) a
forall (f :: * -> *) a. Applicative f => a %1 -> f a
Control.pure (Float# -> UFloat b
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) = UInt b %1 -> Curried (Yoneda f) (Yoneda f) (UInt b)
forall a. a %1 -> Curried (Yoneda f) (Yoneda f) a
forall (f :: * -> *) a. Applicative f => a %1 -> f a
Control.pure (Int# -> UInt b
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) = UWord b %1 -> Curried (Yoneda f) (Yoneda f) (UWord b)
forall a. a %1 -> Curried (Yoneda f) (Yoneda f) a
forall (f :: * -> *) a. Applicative f => a %1 -> f a
Control.pure (Word# -> UWord b
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 = Yoneda f (t b) %1 -> f (t b)
forall (f :: * -> *) a. Yoneda f a %1 -> f a
lowerYoneda (Yoneda f (t b) %1 -> f (t b))
-> (t a %1 -> Yoneda f (t b)) -> t a %1 -> f (t b)
forall b c a (q :: Multiplicity) (m :: Multiplicity)
(n :: Multiplicity).
(b %1 -> c) %q -> (a %1 -> b) %m -> a %n -> c
. Curried (Yoneda f) (Yoneda f) (t b) %1 -> Yoneda f (t b)
forall (f :: * -> *) (g :: * -> *) a.
Applicative f =>
Curried f g a %1 -> g a
lowerCurriedC (Curried (Yoneda f) (Yoneda f) (t b) %1 -> Yoneda f (t b))
-> (t a %1 -> Curried (Yoneda f) (Yoneda f) (t b))
-> t a
%1 -> Yoneda f (t b)
forall b c a (q :: Multiplicity) (m :: Multiplicity)
(n :: Multiplicity).
(b %1 -> c) %q -> (a %1 -> b) %m -> a %n -> c
. (Rep1 t b %1 -> t b)
%1 -> Curried (Yoneda f) (Yoneda f) (Rep1 t b)
%1 -> Curried (Yoneda f) (Yoneda f) (t b)
forall a b.
(a %1 -> b)
%1 -> Curried (Yoneda f) (Yoneda f) a
%1 -> Curried (Yoneda f) (Yoneda f) b
forall (f :: * -> *) a b.
Functor f =>
(a %1 -> b) %1 -> f a %1 -> f b
Control.fmap Rep1 t b %1 -> t b
forall p (m :: Multiplicity). Rep1 t p %m -> t p
forall {k} (f :: k -> *) (p :: k) (m :: Multiplicity).
Generic1 f =>
Rep1 f p %m -> f p
to1 (Curried (Yoneda f) (Yoneda f) (Rep1 t b)
%1 -> Curried (Yoneda f) (Yoneda f) (t b))
-> (t a %1 -> Curried (Yoneda f) (Yoneda f) (Rep1 t b))
-> t a
%1 -> Curried (Yoneda f) (Yoneda f) (t b)
forall b c a (q :: Multiplicity) (m :: Multiplicity)
(n :: Multiplicity).
(b %1 -> c) %q -> (a %1 -> b) %m -> a %n -> c
. (a %1 -> f b)
-> Rep1 t a %1 -> Curried (Yoneda f) (Yoneda f) (Rep1 t b)
forall (t :: * -> *) (f :: * -> *) a b.
(GTraversable t, Applicative f) =>
(a %1 -> f b) -> t a %1 -> Curried (Yoneda f) (Yoneda f) (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a %1 -> f b)
-> Rep1 t a %1 -> Curried (Yoneda f) (Yoneda f) (Rep1 t b)
gtraverse a %1 -> f b
f (Rep1 t a %1 -> Curried (Yoneda f) (Yoneda f) (Rep1 t b))
-> (t a %1 -> Rep1 t a)
-> t a
%1 -> Curried (Yoneda f) (Yoneda f) (Rep1 t b)
forall b c a (q :: Multiplicity) (m :: Multiplicity)
(n :: Multiplicity).
(b %1 -> c) %q -> (a %1 -> b) %m -> a %n -> c
. t a %1 -> Rep1 t a
forall p (m :: Multiplicity). t p %m -> Rep1 t p
forall {k} (f :: k -> *) (p :: k) (m :: Multiplicity).
Generic1 f =>
f p %m -> Rep1 f p
from1
{-# INLINE genericTraverse #-}