Skip to content

Commit

Permalink
version bump and changelong
Browse files Browse the repository at this point in the history
  • Loading branch information
mstksg committed Feb 13, 2018
1 parent c3a710f commit 9ac99dd
Show file tree
Hide file tree
Showing 2 changed files with 37 additions and 18 deletions.
8 changes: 7 additions & 1 deletion CHANGELOG.md
Original file line number Diff line number Diff line change
@@ -1,9 +1,15 @@
Changelog
=========

Pending Changes
Version 0.1.3.0
---------------

*Feb 12, 2018*

<https://github.com/mstksg/backprop/releases/tag/v0.1.3.0>

* *Preulude.Backprop* module added with lifted versions of several *Prelude*
and base functions.
* `liftOpX` family of operators now have a more logical ordering for type
variables. This change breaks backwards-compatibility.
* `opIsoN` added to export list of *Numeric.Backprop*
Expand Down
47 changes: 30 additions & 17 deletions src/Prelude/Backprop.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE ScopedTypeVariables #-}

-- |
-- Module : Prelude.Backprop
Expand Down Expand Up @@ -49,72 +50,76 @@ import qualified Data.Coerce as C
import qualified Prelude as P

-- | Lifted 'P.sum'
sum :: (Foldable t, Applicative t, Num (t a), Num a, Reifies s W)
sum :: forall t a s. (Foldable t, Functor t, Num (t a), Num a, Reifies s W)
=> BVar s (t a)
-> BVar s a
sum = liftOp1 . op1 $ \xs ->
( P.sum xs
, \d -> P.const d P.<$> xs
, (P.<$ xs)
)
{-# INLINE sum #-}

-- | Lifted 'P.pure'. Really intended only for 'Applicative' instances
-- with fixed number of items; untintended consequences might arise when
-- using it with containers with variable number of items.
pure
:: (Foldable t, Applicative t, Num (t a), Num a, Reifies s W)
:: forall t a s. (Foldable t, Applicative t, Num (t a), Num a, Reifies s W)
=> BVar s a
-> BVar s (t a)
pure = liftOp1 . op1 $ \x ->
( P.pure x
, P.sum
)
{-# INLINE pure #-}

-- | Lifted 'P.product'
product
:: (Foldable t, Applicative t, Num (t a), Fractional a, Reifies s W)
:: forall t a s. (Foldable t, Functor t, Num (t a), Fractional a, Reifies s W)
=> BVar s (t a)
-> BVar s a
product = liftOp1 . op1 $ \xs ->
let p = P.product xs
in ( p
, \d -> (\x -> p * d / x) P.<$> xs
)
{-# INLINE product #-}

-- | Lifted 'P.length'. Really intended only for 'Foldable' instances
-- with fixed number of items; untintended consequences might arise when
-- using it with containers with variable number of items.
-- | Lifted 'P.length'.
length
:: (Foldable t, Num (t a), Num b, Reifies s W)
:: forall t a b s. (Foldable t, Num (t a), Num b, Reifies s W)
=> BVar s (t a)
-> BVar s b
length = liftOp1 . op1 $ \xs ->
( P.fromIntegral (P.length xs)
, P.const 0
)
{-# INLINE length #-}

-- | Lifted 'P.minimum'. Undefined for situations where 'P.minimum' would
-- be undefined.
minimum
:: (Foldable t, Functor t, Num a, Ord a, Num (t a), Reifies s W)
:: forall t a s. (Foldable t, Functor t, Num a, Ord a, Num (t a), Reifies s W)
=> BVar s (t a)
-> BVar s a
minimum = liftOp1 . op1 $ \xs ->
let m = P.minimum xs
in ( m
, \d -> (\x -> if x == m then d else 0) P.<$> xs
)
{-# INLINE minimum #-}

-- | Lifted 'P.maximum'. Undefined for situations where 'P.maximum' would
-- be undefined.
maximum
:: (Foldable t, Functor t, Num a, Ord a, Num (t a), Reifies s W)
:: forall t a s. (Foldable t, Functor t, Num a, Ord a, Num (t a), Reifies s W)
=> BVar s (t a)
-> BVar s a
maximum = liftOp1 . op1 $ \xs ->
let m = P.maximum xs
in ( m
, \d -> (\x -> if x == m then d else 0) P.<$> xs
)
{-# INLINE maximum #-}

-- | Lifted 'P.fmap'. Lifts backpropagatable functions to be
-- backpropagatable functions on 'Traversable' 'Functor's.
Expand All @@ -123,19 +128,21 @@ maximum = liftOp1 . op1 $ \xs ->
-- untintended consequences might arise when using it with containers with
-- variable number of items.
fmap
:: (Traversable f, Num a, Num b, Num (f b), Reifies s W)
:: forall f a b s. (Traversable f, Num a, Num b, Num (f b), Reifies s W)
=> (BVar s a -> BVar s b)
-> BVar s (f a)
-> BVar s (f b)
fmap f = collectVar . P.fmap f . sequenceVar
{-# INLINE fmap #-}

-- | Alias for 'fmap'.
(<$>)
:: (Traversable f, Num a, Num b, Num (f b), Reifies s W)
:: forall f a b s. (Traversable f, Num a, Num b, Num (f b), Reifies s W)
=> (BVar s a -> BVar s b)
-> BVar s (f a)
-> BVar s (f b)
(<$>) = fmap
{-# INLINE (<$>) #-}

-- | Lifted 'P.traverse'. Lifts backpropagatable functions to be
-- backpropagatable functions on 'Traversable' 'Functor's.
Expand All @@ -144,14 +151,15 @@ fmap f = collectVar . P.fmap f . sequenceVar
-- fixed number of items; untintended consequences might arise when using
-- it with containers with variable number of items.
traverse
:: (Traversable t, Applicative f, Foldable f, Num a, Num b, Num (f (t b)), Num (t b), Reifies s W)
:: forall t f a b s. (Traversable t, Applicative f, Foldable f, Num a, Num b, Num (f (t b)), Num (t b), Reifies s W)
=> (BVar s a -> f (BVar s b))
-> BVar s (t a)
-> BVar s (f (t b))
traverse f = collectVar
. P.fmap collectVar
. P.traverse f
. sequenceVar
{-# INLINE traverse #-}

-- | Lifted 'P.liftA2'. Lifts backpropagatable functions to be
-- backpropagatable functions on 'Traversable' 'Applicative's.
Expand All @@ -160,7 +168,8 @@ traverse f = collectVar
-- fixed number of items; untintended consequences might arise when using
-- it with containers with variable number of items.
liftA2
:: ( Traversable f
:: forall f a b c s.
( Traversable f
, Applicative f
, Num a, Num b, Num c, Num (f c)
, Reifies s W
Expand All @@ -171,6 +180,7 @@ liftA2
-> BVar s (f c)
liftA2 f x y = collectVar $ f P.<$> sequenceVar x
P.<*> sequenceVar y
{-# INLINE liftA2 #-}

-- | Lifted 'P.liftA3'. Lifts backpropagatable functions to be
-- backpropagatable functions on 'Traversable' 'Applicative's.
Expand All @@ -179,7 +189,8 @@ liftA2 f x y = collectVar $ f P.<$> sequenceVar x
-- fixed number of items; untintended consequences might arise when using
-- it with containers with variable number of items.
liftA3
:: ( Traversable f
:: forall f a b c d s.
( Traversable f
, Applicative f
, Num a, Num b, Num c, Num d, Num (f d)
, Reifies s W
Expand All @@ -192,10 +203,12 @@ liftA3
liftA3 f x y z = collectVar $ f P.<$> sequenceVar x
P.<*> sequenceVar y
P.<*> sequenceVar z
{-# INLINE liftA3 #-}

-- | Coerce items inside a 'BVar'.
coerce
:: (C.Coercible a b, Num a, Num b, Reifies s W)
:: forall a b s. (C.Coercible a b, Num a, Num b, Reifies s W)
=> BVar s a
-> BVar s b
coerce = liftOp1 $ opIso C.coerce C.coerce
{-# INLINE coerce #-}

0 comments on commit 9ac99dd

Please sign in to comment.