Skip to content

Commit 25dd2f1

Browse files
committed
hlint and format
1 parent 77fb89f commit 25dd2f1

File tree

8 files changed

+22
-30
lines changed

8 files changed

+22
-30
lines changed

backprop.cabal

Lines changed: 3 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -62,20 +62,17 @@ library
6262
Prelude.Backprop.Explicit
6363
Prelude.Backprop.Num
6464

65-
other-modules:
66-
Data.Type.Util
67-
Numeric.Backprop.Internal
68-
65+
other-modules: Data.Type.Util
6966
hs-source-dirs: src
7067
ghc-options:
7168
-Wall -Wcompat -Wincomplete-record-updates -Wredundant-constraints
69+
-Wunused-packages
7270

7371
build-depends:
7472
base >=4.7 && <5
7573
, containers
7674
, deepseq
7775
, microlens
78-
, primitive
7976
, reflection
8077
, transformers
8178
, vector
@@ -96,7 +93,7 @@ benchmark backprop-mnist-bench
9693
hs-source-dirs: bench
9794
ghc-options:
9895
-Wall -Wcompat -Wincomplete-record-updates -Wredundant-constraints
99-
-threaded -rtsopts -with-rtsopts=-N -O2
96+
-threaded -rtsopts -with-rtsopts=-N -O2 -Wunused-packages
10097

10198
build-depends:
10299
backprop

bench/bench.hs

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -11,7 +11,6 @@
1111
{-# LANGUAGE TemplateHaskell #-}
1212
{-# LANGUAGE TypeApplications #-}
1313
{-# LANGUAGE TypeFamilies #-}
14-
{-# LANGUAGE TypeSynonymInstances #-}
1514
{-# LANGUAGE ViewPatterns #-}
1615
{-# OPTIONS_GHC -fno-warn-orphans #-}
1716

@@ -279,8 +278,8 @@ gradNetManual x t (Net (Layer w1 b1) (Layer w2 b2) (Layer w3 b3)) =
279278
o2 = o0 / konst o1
280279
-- o3 = - (log o2 <.> t)
281280
dEdO3 = 1
282-
dEdO2 = dEdO3 * (-t / o2)
283-
dEdO1 = -(dEdO2 <.> o0) / (o1 ** 2)
281+
dEdO2 = - (dEdO3 * t / o2)
282+
dEdO1 = -((dEdO2 <.> o0) / (o1 ** 2))
284283
dEdO0 = konst dEdO1 + dEdO2 / konst o1
285284
dEdZ3 = dEdO0 * o0
286285
dEdY3 = dEdZ3

src/Data/Type/Util.hs

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,9 +1,7 @@
1-
{-# LANGUAGE DataKinds #-}
21
{-# LANGUAGE FlexibleContexts #-}
32
{-# LANGUAGE GADTs #-}
43
{-# LANGUAGE LambdaCase #-}
54
{-# LANGUAGE PatternSynonyms #-}
6-
{-# LANGUAGE PolyKinds #-}
75
{-# LANGUAGE RankNTypes #-}
86
{-# LANGUAGE ScopedTypeVariables #-}
97
{-# LANGUAGE TupleSections #-}

src/Numeric/Backprop/Class.hs

Lines changed: 1 addition & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -3,8 +3,6 @@
33
{-# LANGUAGE DataKinds #-}
44
{-# LANGUAGE DefaultSignatures #-}
55
{-# LANGUAGE DeriveDataTypeable #-}
6-
{-# LANGUAGE DeriveFoldable #-}
7-
{-# LANGUAGE DeriveFunctor #-}
86
{-# LANGUAGE DeriveGeneric #-}
97
{-# LANGUAGE DeriveTraversable #-}
108
{-# LANGUAGE EmptyCase #-}
@@ -72,7 +70,6 @@ import Control.Monad
7270
import Data.Coerce
7371
import Data.Complex
7472
import Data.Data
75-
import Data.Foldable hiding (toList)
7673
import Data.Functor.Compose
7774
import Data.Functor.Identity
7875
import qualified Data.Functor.Product as DFP
@@ -386,12 +383,10 @@ instance NFData a => NFData (NumBP a)
386383
instance Applicative NumBP where
387384
pure = NumBP
388385
{-# INLINE pure #-}
389-
f <*> x = NumBP $ (runNumBP f) (runNumBP x)
386+
f <*> x = NumBP $ runNumBP f (runNumBP x)
390387
{-# INLINE (<*>) #-}
391388

392389
instance Monad NumBP where
393-
return = NumBP
394-
{-# INLINE return #-}
395390
x >>= f = f (runNumBP x)
396391
{-# INLINE (>>=) #-}
397392

src/Numeric/Backprop/Explicit.hs

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -5,8 +5,6 @@
55
{-# LANGUAGE FunctionalDependencies #-}
66
{-# LANGUAGE GADTs #-}
77
{-# LANGUAGE LambdaCase #-}
8-
{-# LANGUAGE MultiParamTypeClasses #-}
9-
{-# LANGUAGE PatternSynonyms #-}
108
{-# LANGUAGE RankNTypes #-}
119
{-# LANGUAGE ScopedTypeVariables #-}
1210
{-# LANGUAGE TypeApplications #-}

src/Numeric/Backprop/Internal.hs

Lines changed: 10 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
11
{-# LANGUAGE BangPatterns #-}
2+
{-# LANGUAGE BlockArguments #-}
23
{-# LANGUAGE DeriveDataTypeable #-}
34
{-# LANGUAGE DeriveGeneric #-}
4-
{-# LANGUAGE EmptyCase #-}
55
{-# LANGUAGE FlexibleContexts #-}
66
{-# LANGUAGE FlexibleInstances #-}
77
{-# LANGUAGE GADTs #-}
@@ -14,7 +14,6 @@
1414
{-# LANGUAGE TupleSections #-}
1515
{-# LANGUAGE TypeApplications #-}
1616
{-# LANGUAGE TypeInType #-}
17-
{-# LANGUAGE TypeOperators #-}
1817
{-# LANGUAGE ViewPatterns #-}
1918
{-# OPTIONS_HADDOCK not-home #-}
2019

@@ -672,8 +671,7 @@ initRunner (n, stns) (nx, xs) = do
672671
for_ (zip [n - 1, n - 2 ..] stns) $ \(i, STN (TN{} :: TapeNode c)) ->
673672
MV.write delts i $ unsafeCoerce (Nothing @c)
674673
inps <- MV.new nx
675-
for_ (zip [0 ..] xs) . uncurry $ \i z ->
676-
MV.write inps i z
674+
itraverse_ (MV.write inps) xs
677675
return $ R delts inps
678676
{-# INLINE initRunner #-}
679677

@@ -910,6 +908,14 @@ itraverse f xs = evalStateT (traverse (StateT . go) xs) 0
910908
go x i = (,i + 1) <$> f i x
911909
{-# INLINE itraverse #-}
912910

911+
-- Some utility functions to get around a lens dependency
912+
itraverse_ ::
913+
forall t a b f.
914+
(Foldable t, Monad f) =>
915+
(Int -> a -> f b) -> t a -> f ()
916+
itraverse_ f xs = traverse_ (uncurry f) (zip [0 ..] (toList xs))
917+
{-# INLINE itraverse_ #-}
918+
913919
ixi :: Int -> Lens' [a] a
914920
ixi _ _ [] = internalError "ixi"
915921
ixi 0 f (x : xs) = (: xs) <$> f x

src/Numeric/Backprop/Num.hs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,6 @@
11
{-# LANGUAGE DataKinds #-}
22
{-# LANGUAGE FlexibleContexts #-}
33
{-# LANGUAGE GADTs #-}
4-
{-# LANGUAGE PatternSynonyms #-}
54
{-# LANGUAGE RankNTypes #-}
65
{-# OPTIONS_HADDOCK not-home #-}
76

src/Numeric/Backprop/Op.hs

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -3,9 +3,9 @@
33
{-# LANGUAGE FlexibleContexts #-}
44
{-# LANGUAGE GADTs #-}
55
{-# LANGUAGE LambdaCase #-}
6-
{-# LANGUAGE PatternSynonyms #-}
76
{-# LANGUAGE RankNTypes #-}
87
{-# LANGUAGE ScopedTypeVariables #-}
8+
{-# LANGUAGE TupleSections #-}
99
{-# LANGUAGE TypeApplications #-}
1010
{-# LANGUAGE UndecidableInstances #-}
1111

@@ -122,7 +122,7 @@ import Control.Applicative
122122
import Data.Bifunctor
123123
import Data.Coerce
124124
import Data.Functor.Identity
125-
import Data.List
125+
import Data.List (foldl')
126126
import Data.Type.Util
127127
import Data.Vinyl.Core
128128
import qualified Data.Vinyl.Recursive as VR
@@ -416,15 +416,15 @@ noGrad f = Op $ \xs ->
416416
-- 'idOp' = 'opIso' 'id' 'id'
417417
-- @
418418
idOp :: Op '[a] a
419-
idOp = op1 $ \x -> (x, id)
419+
idOp = op1 (,id)
420420
{-# INLINE idOp #-}
421421

422422
-- | An 'Op' that takes @as@ and returns exactly the input tuple.
423423
--
424424
-- >>> gradOp' opTup (1 :& 2 :& 3 :& RNil)
425425
-- (1 :& 2 :& 3 :& RNil, 1 :& 1 :& 1 :& RNil)
426426
opTup :: Op as (Rec Identity as)
427-
opTup = Op $ \xs -> (xs, id)
427+
opTup = Op (,id)
428428
{-# INLINE opTup #-}
429429

430430
-- | An 'Op' that runs the input value through an isomorphism.
@@ -694,7 +694,7 @@ instance (RPureConstrained Num as, Floating a) => Floating (Op as a) where
694694

695695
-- | 'Op' for division
696696
(/.) :: Fractional a => Op '[a, a] a
697-
(/.) = op2 $ \x y -> (x / y, \g -> (g / y, -g * x / (y * y)))
697+
(/.) = op2 $ \x y -> (x / y, \g -> (g / y, -(g * x / (y * y))))
698698
{-# INLINE (/.) #-}
699699

700700
-- | 'Op' for exponentiation
@@ -746,7 +746,7 @@ sqrtOp = op1 $ \x -> (sqrt x, (/ (2 * sqrt x)))
746746
logBaseOp :: Floating a => Op '[a, a] a
747747
logBaseOp = op2 $ \x y ->
748748
( logBase x y
749-
, let dx = -logBase x y / (log x * x)
749+
, let dx = -(logBase x y / (log x * x))
750750
in \g -> (g * dx, g / (y * log x))
751751
)
752752
{-# INLINE logBaseOp #-}

0 commit comments

Comments
 (0)