{-# LANGUAGE FlexibleContexts #-}
{-# OPTIONS_HADDOCK not-home #-}
module Prelude.Backprop.Explicit (
sum
, product
, length
, minimum
, maximum
, traverse
, toList
, mapAccumL
, mapAccumR
, foldr, foldl'
, fmap, fmapConst
, pure
, liftA2
, liftA3
, fromIntegral
, realToFrac
, round
, fromIntegral'
, coerce
) where
import Data.Bifunctor
import Numeric.Backprop.Explicit
import Prelude (Num(..), Fractional(..), Eq(..), Ord(..), Functor, Foldable, Traversable, Applicative, (.), ($))
import qualified Control.Applicative as P
import qualified Data.Coerce as C
import qualified Data.Foldable as P
import qualified Data.Traversable as P
import qualified Prelude as P
sum :: (Foldable t, Functor t, Num a, Reifies s W)
=> AddFunc (t a)
-> BVar s (t a)
-> BVar s a
sum :: forall (t :: * -> *) a s.
(Foldable t, Functor t, Num a, Reifies s W) =>
AddFunc (t a) -> BVar s (t a) -> BVar s a
sum AddFunc (t a)
af = forall a b s.
Reifies s W =>
AddFunc a -> Op '[a] b -> BVar s a -> BVar s b
liftOp1 AddFunc (t a)
af forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> (b, b -> a)) -> Op '[a] b
op1 forall a b. (a -> b) -> a -> b
$ \t a
xs ->
( forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
P.sum t a
xs
, (forall (f :: * -> *) a b. Functor f => a -> f b -> f a
P.<$ t a
xs)
)
{-# INLINE sum #-}
pure
:: (Foldable t, Applicative t, Reifies s W)
=> AddFunc a
-> ZeroFunc a
-> BVar s a
-> BVar s (t a)
pure :: forall (t :: * -> *) s a.
(Foldable t, Applicative t, Reifies s W) =>
AddFunc a -> ZeroFunc a -> BVar s a -> BVar s (t a)
pure AddFunc a
af ZeroFunc a
zfa = forall a b s.
Reifies s W =>
AddFunc a -> Op '[a] b -> BVar s a -> BVar s b
liftOp1 AddFunc a
af forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> (b, b -> a)) -> Op '[a] b
op1 forall a b. (a -> b) -> a -> b
$ \a
x ->
( forall (f :: * -> *) a. Applicative f => a -> f a
P.pure a
x
, \t a
d -> case forall (t :: * -> *) a. Foldable t => t a -> [a]
P.toList t a
d of
[] -> forall a. ZeroFunc a -> a -> a
runZF ZeroFunc a
zfa a
x
a
e:[a]
es -> forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
P.foldl' (forall a. AddFunc a -> a -> a -> a
runAF AddFunc a
af) a
e [a]
es
)
{-# INLINE pure #-}
product
:: (Foldable t, Functor t, Fractional a, Reifies s W)
=> AddFunc (t a)
-> BVar s (t a)
-> BVar s a
product :: forall (t :: * -> *) a s.
(Foldable t, Functor t, Fractional a, Reifies s W) =>
AddFunc (t a) -> BVar s (t a) -> BVar s a
product AddFunc (t a)
af = forall a b s.
Reifies s W =>
AddFunc a -> Op '[a] b -> BVar s a -> BVar s b
liftOp1 AddFunc (t a)
af forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> (b, b -> a)) -> Op '[a] b
op1 forall a b. (a -> b) -> a -> b
$ \t a
xs ->
let p :: a
p = forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
P.product t a
xs
in ( a
p
, \a
d -> (\a
x -> a
p forall a. Num a => a -> a -> a
* a
d forall a. Fractional a => a -> a -> a
/ a
x) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
P.<$> t a
xs
)
{-# INLINE product #-}
length
:: (Foldable t, Num b, Reifies s W)
=> AddFunc (t a)
-> ZeroFunc (t a)
-> BVar s (t a)
-> BVar s b
length :: forall (t :: * -> *) b s a.
(Foldable t, Num b, Reifies s W) =>
AddFunc (t a) -> ZeroFunc (t a) -> BVar s (t a) -> BVar s b
length AddFunc (t a)
af ZeroFunc (t a)
zfa = forall a b s.
Reifies s W =>
AddFunc a -> Op '[a] b -> BVar s a -> BVar s b
liftOp1 AddFunc (t a)
af forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> (b, b -> a)) -> Op '[a] b
op1 forall a b. (a -> b) -> a -> b
$ \t a
xs ->
( forall a b. (Integral a, Num b) => a -> b
P.fromIntegral (forall (t :: * -> *) a. Foldable t => t a -> Int
P.length t a
xs)
, forall a b. a -> b -> a
P.const (forall a. ZeroFunc a -> a -> a
runZF ZeroFunc (t a)
zfa t a
xs)
)
{-# INLINE length #-}
minimum
:: (Foldable t, Functor t, Ord a, Reifies s W)
=> AddFunc (t a)
-> ZeroFunc a
-> BVar s (t a)
-> BVar s a
minimum :: forall (t :: * -> *) a s.
(Foldable t, Functor t, Ord a, Reifies s W) =>
AddFunc (t a) -> ZeroFunc a -> BVar s (t a) -> BVar s a
minimum AddFunc (t a)
af ZeroFunc a
zf = forall a b s.
Reifies s W =>
AddFunc a -> Op '[a] b -> BVar s a -> BVar s b
liftOp1 AddFunc (t a)
af forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> (b, b -> a)) -> Op '[a] b
op1 forall a b. (a -> b) -> a -> b
$ \t a
xs ->
let m :: a
m = forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
P.minimum t a
xs
in ( a
m
, \a
d -> (\a
x -> if a
x forall a. Eq a => a -> a -> Bool
== a
m then a
d else forall a. ZeroFunc a -> a -> a
runZF ZeroFunc a
zf a
x) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
P.<$> t a
xs
)
{-# INLINE minimum #-}
maximum
:: (Foldable t, Functor t, Ord a, Reifies s W)
=> AddFunc (t a)
-> ZeroFunc a
-> BVar s (t a)
-> BVar s a
maximum :: forall (t :: * -> *) a s.
(Foldable t, Functor t, Ord a, Reifies s W) =>
AddFunc (t a) -> ZeroFunc a -> BVar s (t a) -> BVar s a
maximum AddFunc (t a)
af ZeroFunc a
zf = forall a b s.
Reifies s W =>
AddFunc a -> Op '[a] b -> BVar s a -> BVar s b
liftOp1 AddFunc (t a)
af forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> (b, b -> a)) -> Op '[a] b
op1 forall a b. (a -> b) -> a -> b
$ \t a
xs ->
let m :: a
m = forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
P.maximum t a
xs
in ( a
m
, \a
d -> (\a
x -> if a
x forall a. Eq a => a -> a -> Bool
== a
m then a
d else forall a. ZeroFunc a -> a -> a
runZF ZeroFunc a
zf a
x) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
P.<$> t a
xs
)
{-# INLINE maximum #-}
foldr
:: (Traversable t, Reifies s W)
=> AddFunc a
-> ZeroFunc a
-> (BVar s a -> BVar s b -> BVar s b)
-> BVar s b
-> BVar s (t a)
-> BVar s b
foldr :: forall (t :: * -> *) s a b.
(Traversable t, Reifies s W) =>
AddFunc a
-> ZeroFunc a
-> (BVar s a -> BVar s b -> BVar s b)
-> BVar s b
-> BVar s (t a)
-> BVar s b
foldr AddFunc a
af ZeroFunc a
z BVar s a -> BVar s b -> BVar s b
f BVar s b
x = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
P.foldr BVar s a -> BVar s b -> BVar s b
f BVar s b
x forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) s a.
(Traversable t, Reifies s W) =>
AddFunc a -> ZeroFunc a -> BVar s (t a) -> [BVar s a]
toList AddFunc a
af ZeroFunc a
z
{-# INLINE foldr #-}
foldl'
:: (Traversable t, Reifies s W)
=> AddFunc a
-> ZeroFunc a
-> (BVar s b -> BVar s a -> BVar s b)
-> BVar s b
-> BVar s (t a)
-> BVar s b
foldl' :: forall (t :: * -> *) s a b.
(Traversable t, Reifies s W) =>
AddFunc a
-> ZeroFunc a
-> (BVar s b -> BVar s a -> BVar s b)
-> BVar s b
-> BVar s (t a)
-> BVar s b
foldl' AddFunc a
af ZeroFunc a
z BVar s b -> BVar s a -> BVar s b
f BVar s b
x = forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
P.foldl' BVar s b -> BVar s a -> BVar s b
f BVar s b
x forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) s a.
(Traversable t, Reifies s W) =>
AddFunc a -> ZeroFunc a -> BVar s (t a) -> [BVar s a]
toList AddFunc a
af ZeroFunc a
z
{-# INLINE foldl' #-}
fmap
:: (Traversable f, Reifies s W)
=> AddFunc a
-> AddFunc b
-> ZeroFunc a
-> ZeroFunc b
-> (BVar s a -> BVar s b)
-> BVar s (f a)
-> BVar s (f b)
fmap :: forall (f :: * -> *) s a b.
(Traversable f, Reifies s W) =>
AddFunc a
-> AddFunc b
-> ZeroFunc a
-> ZeroFunc b
-> (BVar s a -> BVar s b)
-> BVar s (f a)
-> BVar s (f b)
fmap AddFunc a
afa AddFunc b
afb ZeroFunc a
zfa ZeroFunc b
zfb BVar s a -> BVar s b
f = forall (t :: * -> *) a s.
(Reifies s W, Foldable t, Functor t) =>
AddFunc a -> ZeroFunc a -> t (BVar s a) -> BVar s (t a)
collectVar AddFunc b
afb ZeroFunc b
zfb forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
P.fmap BVar s a -> BVar s b
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a s.
(Reifies s W, Traversable t) =>
AddFunc a -> ZeroFunc a -> BVar s (t a) -> t (BVar s a)
sequenceVar AddFunc a
afa ZeroFunc a
zfa
{-# INLINE fmap #-}
fmapConst
:: (Functor f, Foldable f, Reifies s W)
=> AddFunc (f a)
-> AddFunc b
-> ZeroFunc (f a)
-> ZeroFunc b
-> BVar s b
-> BVar s (f a)
-> BVar s (f b)
fmapConst :: forall (f :: * -> *) s a b.
(Functor f, Foldable f, Reifies s W) =>
AddFunc (f a)
-> AddFunc b
-> ZeroFunc (f a)
-> ZeroFunc b
-> BVar s b
-> BVar s (f a)
-> BVar s (f b)
fmapConst AddFunc (f a)
afa AddFunc b
afb ZeroFunc (f a)
zfa ZeroFunc b
zfb = forall a b c s.
Reifies s W =>
AddFunc a
-> AddFunc b -> Op '[a, b] c -> BVar s a -> BVar s b -> BVar s c
liftOp2 AddFunc b
afb AddFunc (f a)
afa forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b c. (a -> b -> (c, c -> (a, b))) -> Op '[a, b] c
op2 forall a b. (a -> b) -> a -> b
$ \b
x f a
xs ->
( b
x forall (f :: * -> *) a b. Functor f => a -> f b -> f a
P.<$ f a
xs
, \f b
d -> ( case forall (t :: * -> *) a. Foldable t => t a -> [a]
P.toList f b
d of
[] -> forall a. ZeroFunc a -> a -> a
runZF ZeroFunc b
zfb b
x
b
e:[b]
es -> forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
P.foldl' (forall a. AddFunc a -> a -> a -> a
runAF AddFunc b
afb) b
e [b]
es
, forall a. ZeroFunc a -> a -> a
runZF ZeroFunc (f a)
zfa f a
xs
)
)
{-# INLINE fmapConst #-}
traverse
:: (Traversable t, Applicative f, Foldable f, Reifies s W)
=> AddFunc a
-> AddFunc b
-> AddFunc (t b)
-> ZeroFunc a
-> ZeroFunc b
-> (BVar s a -> f (BVar s b))
-> BVar s (t a)
-> BVar s (f (t b))
traverse :: forall (t :: * -> *) (f :: * -> *) s a b.
(Traversable t, Applicative f, Foldable f, Reifies s W) =>
AddFunc a
-> AddFunc b
-> AddFunc (t b)
-> ZeroFunc a
-> ZeroFunc b
-> (BVar s a -> f (BVar s b))
-> BVar s (t a)
-> BVar s (f (t b))
traverse AddFunc a
afa AddFunc b
afb AddFunc (t b)
aftb ZeroFunc a
zfa ZeroFunc b
zfb BVar s a -> f (BVar s b)
f
= forall (t :: * -> *) a s.
(Reifies s W, Foldable t, Functor t) =>
AddFunc a -> ZeroFunc a -> t (BVar s a) -> BVar s (t a)
collectVar AddFunc (t b)
aftb ZeroFunc (t b)
zftb
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
P.fmap (forall (t :: * -> *) a s.
(Reifies s W, Foldable t, Functor t) =>
AddFunc a -> ZeroFunc a -> t (BVar s a) -> BVar s (t a)
collectVar AddFunc b
afb ZeroFunc b
zfb)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
P.traverse BVar s a -> f (BVar s b)
f
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a s.
(Reifies s W, Traversable t) =>
AddFunc a -> ZeroFunc a -> BVar s (t a) -> t (BVar s a)
sequenceVar AddFunc a
afa ZeroFunc a
zfa
where
zftb :: ZeroFunc (t b)
zftb = forall a. (a -> a) -> ZeroFunc a
ZF forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
P.fmap (forall a. ZeroFunc a -> a -> a
runZF ZeroFunc b
zfb)
{-# INLINE zftb #-}
{-# INLINE traverse #-}
liftA2
:: ( Traversable f
, Applicative f
, Reifies s W
)
=> AddFunc a
-> AddFunc b
-> AddFunc c
-> ZeroFunc a
-> ZeroFunc b
-> ZeroFunc c
-> (BVar s a -> BVar s b -> BVar s c)
-> BVar s (f a)
-> BVar s (f b)
-> BVar s (f c)
liftA2 :: forall (f :: * -> *) s a b c.
(Traversable f, Applicative f, Reifies s W) =>
AddFunc a
-> AddFunc b
-> AddFunc c
-> ZeroFunc a
-> ZeroFunc b
-> ZeroFunc c
-> (BVar s a -> BVar s b -> BVar s c)
-> BVar s (f a)
-> BVar s (f b)
-> BVar s (f c)
liftA2 AddFunc a
afa AddFunc b
afb AddFunc c
afc ZeroFunc a
zfa ZeroFunc b
zfb ZeroFunc c
zfc BVar s a -> BVar s b -> BVar s c
f BVar s (f a)
x BVar s (f b)
y
= forall (t :: * -> *) a s.
(Reifies s W, Foldable t, Functor t) =>
AddFunc a -> ZeroFunc a -> t (BVar s a) -> BVar s (t a)
collectVar AddFunc c
afc ZeroFunc c
zfc
forall a b. (a -> b) -> a -> b
$ BVar s a -> BVar s b -> BVar s c
f forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
P.<$> forall (t :: * -> *) a s.
(Reifies s W, Traversable t) =>
AddFunc a -> ZeroFunc a -> BVar s (t a) -> t (BVar s a)
sequenceVar AddFunc a
afa ZeroFunc a
zfa BVar s (f a)
x
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
P.<*> forall (t :: * -> *) a s.
(Reifies s W, Traversable t) =>
AddFunc a -> ZeroFunc a -> BVar s (t a) -> t (BVar s a)
sequenceVar AddFunc b
afb ZeroFunc b
zfb BVar s (f b)
y
{-# INLINE liftA2 #-}
liftA3
:: ( Traversable f
, Applicative f
, Reifies s W
)
=> AddFunc a
-> AddFunc b
-> AddFunc c
-> AddFunc d
-> ZeroFunc a
-> ZeroFunc b
-> ZeroFunc c
-> ZeroFunc d
-> (BVar s a -> BVar s b -> BVar s c -> BVar s d)
-> BVar s (f a)
-> BVar s (f b)
-> BVar s (f c)
-> BVar s (f d)
liftA3 :: forall (f :: * -> *) s a b c d.
(Traversable f, Applicative f, Reifies s W) =>
AddFunc a
-> AddFunc b
-> AddFunc c
-> AddFunc d
-> ZeroFunc a
-> ZeroFunc b
-> ZeroFunc c
-> ZeroFunc d
-> (BVar s a -> BVar s b -> BVar s c -> BVar s d)
-> BVar s (f a)
-> BVar s (f b)
-> BVar s (f c)
-> BVar s (f d)
liftA3 AddFunc a
afa AddFunc b
afb AddFunc c
afc AddFunc d
afd ZeroFunc a
zfa ZeroFunc b
zfb ZeroFunc c
zfc ZeroFunc d
zfd BVar s a -> BVar s b -> BVar s c -> BVar s d
f BVar s (f a)
x BVar s (f b)
y BVar s (f c)
z
= forall (t :: * -> *) a s.
(Reifies s W, Foldable t, Functor t) =>
AddFunc a -> ZeroFunc a -> t (BVar s a) -> BVar s (t a)
collectVar AddFunc d
afd ZeroFunc d
zfd
forall a b. (a -> b) -> a -> b
$ BVar s a -> BVar s b -> BVar s c -> BVar s d
f forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
P.<$> forall (t :: * -> *) a s.
(Reifies s W, Traversable t) =>
AddFunc a -> ZeroFunc a -> BVar s (t a) -> t (BVar s a)
sequenceVar AddFunc a
afa ZeroFunc a
zfa BVar s (f a)
x
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
P.<*> forall (t :: * -> *) a s.
(Reifies s W, Traversable t) =>
AddFunc a -> ZeroFunc a -> BVar s (t a) -> t (BVar s a)
sequenceVar AddFunc b
afb ZeroFunc b
zfb BVar s (f b)
y
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
P.<*> forall (t :: * -> *) a s.
(Reifies s W, Traversable t) =>
AddFunc a -> ZeroFunc a -> BVar s (t a) -> t (BVar s a)
sequenceVar AddFunc c
afc ZeroFunc c
zfc BVar s (f c)
z
{-# INLINE liftA3 #-}
coerce :: C.Coercible a b => BVar s a -> BVar s b
coerce :: forall a b s. Coercible a b => BVar s a -> BVar s b
coerce = forall a b s. Coercible a b => BVar s a -> BVar s b
coerceVar
{-# INLINE coerce #-}
fromIntegral
:: (P.Integral a, P.Integral b, Reifies s W)
=> AddFunc a
-> BVar s a
-> BVar s b
fromIntegral :: forall a b s.
(Integral a, Integral b, Reifies s W) =>
AddFunc a -> BVar s a -> BVar s b
fromIntegral AddFunc a
af = forall s a b.
Reifies s W =>
AddFunc a -> (a -> b) -> (b -> a) -> BVar s a -> BVar s b
isoVar AddFunc a
af forall a b. (Integral a, Num b) => a -> b
P.fromIntegral forall a b. (Integral a, Num b) => a -> b
P.fromIntegral
{-# INLINE fromIntegral #-}
realToFrac
:: (Fractional a, P.Real a, Fractional b, P.Real b, Reifies s W)
=> AddFunc a
-> BVar s a
-> BVar s b
realToFrac :: forall a b s.
(Fractional a, Real a, Fractional b, Real b, Reifies s W) =>
AddFunc a -> BVar s a -> BVar s b
realToFrac AddFunc a
af = forall s a b.
Reifies s W =>
AddFunc a -> (a -> b) -> (b -> a) -> BVar s a -> BVar s b
isoVar AddFunc a
af forall a b. (Real a, Fractional b) => a -> b
P.realToFrac forall a b. (Real a, Fractional b) => a -> b
P.realToFrac
{-# INLINE realToFrac #-}
round
:: (P.RealFrac a, P.Integral b, Reifies s W)
=> AddFunc a
-> BVar s a
-> BVar s b
round :: forall a b s.
(RealFrac a, Integral b, Reifies s W) =>
AddFunc a -> BVar s a -> BVar s b
round AddFunc a
af = forall s a b.
Reifies s W =>
AddFunc a -> (a -> b) -> (b -> a) -> BVar s a -> BVar s b
isoVar AddFunc a
af forall a b. (RealFrac a, Integral b) => a -> b
P.round forall a b. (Integral a, Num b) => a -> b
P.fromIntegral
{-# INLINE round #-}
fromIntegral'
:: (P.Integral a, P.RealFrac b, Reifies s W)
=> AddFunc a
-> BVar s a
-> BVar s b
fromIntegral' :: forall a b s.
(Integral a, RealFrac b, Reifies s W) =>
AddFunc a -> BVar s a -> BVar s b
fromIntegral' AddFunc a
af = forall s a b.
Reifies s W =>
AddFunc a -> (a -> b) -> (b -> a) -> BVar s a -> BVar s b
isoVar AddFunc a
af forall a b. (Integral a, Num b) => a -> b
P.fromIntegral forall a b. (RealFrac a, Integral b) => a -> b
P.round
{-# INLINE fromIntegral' #-}
toList
:: (Traversable t, Reifies s W)
=> AddFunc a
-> ZeroFunc a
-> BVar s (t a)
-> [BVar s a]
toList :: forall (t :: * -> *) s a.
(Traversable t, Reifies s W) =>
AddFunc a -> ZeroFunc a -> BVar s (t a) -> [BVar s a]
toList AddFunc a
af ZeroFunc a
z = forall b a s.
Reifies s W =>
AddFunc a -> ZeroFunc b -> Traversal' b a -> BVar s b -> [BVar s a]
toListOfVar AddFunc a
af (forall a. (a -> a) -> ZeroFunc a
ZF (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
P.fmap (forall a. ZeroFunc a -> a -> a
runZF ZeroFunc a
z))) forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
P.traverse
{-# INLINE toList #-}
mapAccumL
:: (Traversable t, Reifies s W)
=> AddFunc b
-> AddFunc c
-> ZeroFunc b
-> ZeroFunc c
-> (BVar s a -> BVar s b -> (BVar s a, BVar s c))
-> BVar s a
-> BVar s (t b)
-> (BVar s a, BVar s (t c))
mapAccumL :: forall (t :: * -> *) s b c a.
(Traversable t, Reifies s W) =>
AddFunc b
-> AddFunc c
-> ZeroFunc b
-> ZeroFunc c
-> (BVar s a -> BVar s b -> (BVar s a, BVar s c))
-> BVar s a
-> BVar s (t b)
-> (BVar s a, BVar s (t c))
mapAccumL AddFunc b
afb AddFunc c
afc ZeroFunc b
zfb ZeroFunc c
zfc BVar s a -> BVar s b -> (BVar s a, BVar s c)
f BVar s a
s =
forall (p :: * -> * -> *) b c a.
Bifunctor p =>
(b -> c) -> p a b -> p a c
second (forall (t :: * -> *) a s.
(Reifies s W, Foldable t, Functor t) =>
AddFunc a -> ZeroFunc a -> t (BVar s a) -> BVar s (t a)
collectVar AddFunc c
afc ZeroFunc c
zfc)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) s a b.
Traversable t =>
(s -> a -> (s, b)) -> s -> t a -> (s, t b)
P.mapAccumL BVar s a -> BVar s b -> (BVar s a, BVar s c)
f BVar s a
s
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a s.
(Reifies s W, Traversable t) =>
AddFunc a -> ZeroFunc a -> BVar s (t a) -> t (BVar s a)
sequenceVar AddFunc b
afb ZeroFunc b
zfb
{-# INLINE mapAccumL #-}
mapAccumR
:: (Traversable t, Reifies s W)
=> AddFunc b
-> AddFunc c
-> ZeroFunc b
-> ZeroFunc c
-> (BVar s a -> BVar s b -> (BVar s a, BVar s c))
-> BVar s a
-> BVar s (t b)
-> (BVar s a, BVar s (t c))
mapAccumR :: forall (t :: * -> *) s b c a.
(Traversable t, Reifies s W) =>
AddFunc b
-> AddFunc c
-> ZeroFunc b
-> ZeroFunc c
-> (BVar s a -> BVar s b -> (BVar s a, BVar s c))
-> BVar s a
-> BVar s (t b)
-> (BVar s a, BVar s (t c))
mapAccumR AddFunc b
afb AddFunc c
afc ZeroFunc b
zfb ZeroFunc c
zfc BVar s a -> BVar s b -> (BVar s a, BVar s c)
f BVar s a
s =
forall (p :: * -> * -> *) b c a.
Bifunctor p =>
(b -> c) -> p a b -> p a c
second (forall (t :: * -> *) a s.
(Reifies s W, Foldable t, Functor t) =>
AddFunc a -> ZeroFunc a -> t (BVar s a) -> BVar s (t a)
collectVar AddFunc c
afc ZeroFunc c
zfc)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) s a b.
Traversable t =>
(s -> a -> (s, b)) -> s -> t a -> (s, t b)
P.mapAccumR BVar s a -> BVar s b -> (BVar s a, BVar s c)
f BVar s a
s
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a s.
(Reifies s W, Traversable t) =>
AddFunc a -> ZeroFunc a -> BVar s (t a) -> t (BVar s a)
sequenceVar AddFunc b
afb ZeroFunc b
zfb
{-# INLINE mapAccumR #-}