{-# LANGUAGE FlexibleContexts #-}
{-# OPTIONS_HADDOCK not-home #-}
module Prelude.Backprop.Num (
sum
, product
, length
, minimum
, maximum
, traverse
, toList
, mapAccumL
, mapAccumR
, foldr, foldl'
, fmap, fmapConst
, (<$>), (<$), ($>)
, pure
, liftA2
, liftA3
, fromIntegral
, realToFrac
, round
, fromIntegral'
, E.coerce
) where
import Numeric.Backprop.Num
import Prelude (Num(..), Fractional(..), Ord(..), Functor, Foldable, Traversable, Applicative)
import qualified Numeric.Backprop.Explicit as E
import qualified Prelude as P
import qualified Prelude.Backprop.Explicit as E
sum :: (Foldable t, Functor t, Num (t a), Num a, Reifies s W)
=> BVar s (t a)
-> BVar s a
sum = E.sum E.afNum
{-# INLINE sum #-}
pure
:: (Foldable t, Applicative t, Num a, Reifies s W)
=> BVar s a
-> BVar s (t a)
pure = E.pure E.afNum E.zfNum
{-# INLINE pure #-}
product
:: (Foldable t, Functor t, Num (t a), Fractional a, Reifies s W)
=> BVar s (t a)
-> BVar s a
product = E.product E.afNum
{-# INLINE product #-}
length
:: (Foldable t, Num (t a), Num b, Reifies s W)
=> BVar s (t a)
-> BVar s b
length = E.length E.afNum E.zfNum
{-# INLINE length #-}
minimum
:: (Foldable t, Functor t, Num a, Ord a, Num (t a), Reifies s W)
=> BVar s (t a)
-> BVar s a
minimum = E.minimum E.afNum E.zfNum
{-# INLINE minimum #-}
maximum
:: (Foldable t, Functor t, Num a, Ord a, Num (t a), Reifies s W)
=> BVar s (t a)
-> BVar s a
maximum = E.maximum E.afNum E.zfNum
{-# INLINE maximum #-}
foldr
:: (Traversable t, Num a, Reifies s W)
=> (BVar s a -> BVar s b -> BVar s b)
-> BVar s b
-> BVar s (t a)
-> BVar s b
foldr = E.foldr E.afNum E.zfNum
{-# INLINE foldr #-}
foldl'
:: (Traversable t, Num a, Reifies s W)
=> (BVar s b -> BVar s a -> BVar s b)
-> BVar s b
-> BVar s (t a)
-> BVar s b
foldl' = E.foldl' E.afNum E.zfNum
{-# INLINE foldl' #-}
fmap
:: (Traversable f, Num a, Num b, Reifies s W)
=> (BVar s a -> BVar s b)
-> BVar s (f a)
-> BVar s (f b)
fmap = E.fmap E.afNum E.afNum E.zfNum E.zfNum
{-# INLINE fmap #-}
fmapConst
:: (Functor f, Foldable f, Num b, Num (f a), Reifies s W)
=> BVar s b
-> BVar s (f a)
-> BVar s (f b)
fmapConst = E.fmapConst E.afNum E.afNum E.zfNum E.zfNum
{-# INLINE fmapConst #-}
(<$>)
:: (Traversable f, Num a, Num b, Reifies s W)
=> (BVar s a -> BVar s b)
-> BVar s (f a)
-> BVar s (f b)
(<$>) = fmap
infixl 4 <$>
{-# INLINE (<$>) #-}
(<$)
:: (Functor f, Foldable f, Num b, Num (f a), Reifies s W)
=> BVar s b
-> BVar s (f a)
-> BVar s (f b)
(<$) = fmapConst
infixl 4 <$
{-# INLINE (<$) #-}
($>)
:: (Functor f, Foldable f, Num b, Num (f a), Reifies s W)
=> BVar s (f a)
-> BVar s b
-> BVar s (f b)
xs $> x = x <$ xs
infixl 4 $>
{-# INLINE ($>) #-}
traverse
:: (Traversable t, Applicative f, Foldable f, Num a, Num b, Num (t b), Reifies s W)
=> (BVar s a -> f (BVar s b))
-> BVar s (t a)
-> BVar s (f (t b))
traverse = E.traverse E.afNum E.afNum E.afNum E.zfNum E.zfNum
{-# INLINE traverse #-}
liftA2
:: ( Traversable f
, Applicative f
, Num a, Num b, Num c
, Reifies s W
)
=> (BVar s a -> BVar s b -> BVar s c)
-> BVar s (f a)
-> BVar s (f b)
-> BVar s (f c)
liftA2 = E.liftA2 E.afNum E.afNum E.afNum E.zfNum E.zfNum E.zfNum
{-# INLINE liftA2 #-}
liftA3
:: ( Traversable f
, Applicative f
, Num a, Num b, Num c, Num d
, Reifies s W
)
=> (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 = E.liftA3 E.afNum E.afNum E.afNum E.afNum
E.zfNum E.zfNum E.zfNum E.zfNum
{-# INLINE liftA3 #-}
fromIntegral
:: (P.Integral a, P.Integral b, Reifies s W)
=> BVar s a
-> BVar s b
fromIntegral = E.fromIntegral E.afNum
{-# INLINE fromIntegral #-}
realToFrac
:: (Fractional a, P.Real a, Fractional b, P.Real b, Reifies s W)
=> BVar s a
-> BVar s b
realToFrac = E.realToFrac E.afNum
{-# INLINE realToFrac #-}
round
:: (P.RealFrac a, P.Integral b, Reifies s W)
=> BVar s a
-> BVar s b
round = E.round E.afNum
{-# INLINE round #-}
fromIntegral'
:: (P.Integral a, P.RealFrac b, Reifies s W)
=> BVar s a
-> BVar s b
fromIntegral' = E.fromIntegral' E.afNum
{-# INLINE fromIntegral' #-}
toList
:: (Traversable t, Num a, Reifies s W)
=> BVar s (t a)
-> [BVar s a]
toList = E.toList E.afNum E.zfNum
{-# INLINE toList #-}
mapAccumL
:: (Traversable t, Num b, Num c, Reifies s W)
=> (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 = E.mapAccumL E.afNum E.afNum E.zfNum E.zfNum
{-# INLINE mapAccumL #-}
mapAccumR
:: (Traversable t, Num b, Num c, Reifies s W)
=> (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 = E.mapAccumR E.afNum E.afNum E.zfNum E.zfNum
{-# INLINE mapAccumR #-}