mirror of
https://github.com/HuwCampbell/grenade.git
synced 2024-11-22 06:55:13 +03:00
Merge pull request #50 from schnecki/master
Added the sinusoid activation function layer
This commit is contained in:
commit
b613502971
@ -81,6 +81,7 @@ library
|
|||||||
Grenade.Layers.Pooling
|
Grenade.Layers.Pooling
|
||||||
Grenade.Layers.Relu
|
Grenade.Layers.Relu
|
||||||
Grenade.Layers.Reshape
|
Grenade.Layers.Reshape
|
||||||
|
Grenade.Layers.Sinusoid
|
||||||
Grenade.Layers.Softmax
|
Grenade.Layers.Softmax
|
||||||
Grenade.Layers.Tanh
|
Grenade.Layers.Tanh
|
||||||
Grenade.Layers.Trivial
|
Grenade.Layers.Trivial
|
||||||
|
39
src/Grenade/Layers/Sinusoid.hs
Normal file
39
src/Grenade/Layers/Sinusoid.hs
Normal file
@ -0,0 +1,39 @@
|
|||||||
|
{-# LANGUAGE DataKinds #-}
|
||||||
|
{-# LANGUAGE FlexibleInstances #-}
|
||||||
|
{-# LANGUAGE MultiParamTypeClasses #-}
|
||||||
|
{-# LANGUAGE TypeFamilies #-}
|
||||||
|
{-# LANGUAGE TypeOperators #-}
|
||||||
|
{-|
|
||||||
|
Module : Grenade.Layers.Sinusoid
|
||||||
|
Description : Sinusoid nonlinear layer
|
||||||
|
Copyright : (c) Manuel Schneckenreither, 2018
|
||||||
|
License : BSD2
|
||||||
|
Stability : experimental
|
||||||
|
-}
|
||||||
|
module Grenade.Layers.Sinusoid (
|
||||||
|
Sinusoid (..)
|
||||||
|
) where
|
||||||
|
|
||||||
|
import Data.Serialize
|
||||||
|
import Data.Singletons
|
||||||
|
|
||||||
|
import Grenade.Core
|
||||||
|
|
||||||
|
-- | A Sinusoid layer.
|
||||||
|
-- A layer which can act between any shape of the same dimension, performing a sin function.
|
||||||
|
data Sinusoid = Sinusoid
|
||||||
|
deriving Show
|
||||||
|
|
||||||
|
instance UpdateLayer Sinusoid where
|
||||||
|
type Gradient Sinusoid = ()
|
||||||
|
runUpdate _ _ _ = Sinusoid
|
||||||
|
createRandom = return Sinusoid
|
||||||
|
|
||||||
|
instance Serialize Sinusoid where
|
||||||
|
put _ = return ()
|
||||||
|
get = return Sinusoid
|
||||||
|
|
||||||
|
instance (a ~ b, SingI a) => Layer Sinusoid a b where
|
||||||
|
type Tape Sinusoid a b = S a
|
||||||
|
runForwards _ a = (a, sin a)
|
||||||
|
runBackwards _ a g = ((), cos a * g)
|
@ -1,8 +1,8 @@
|
|||||||
{-# LANGUAGE DataKinds #-}
|
{-# LANGUAGE DataKinds #-}
|
||||||
{-# LANGUAGE TypeOperators #-}
|
|
||||||
{-# LANGUAGE TypeFamilies #-}
|
|
||||||
{-# LANGUAGE FlexibleInstances #-}
|
{-# LANGUAGE FlexibleInstances #-}
|
||||||
{-# LANGUAGE MultiParamTypeClasses #-}
|
{-# LANGUAGE MultiParamTypeClasses #-}
|
||||||
|
{-# LANGUAGE TypeFamilies #-}
|
||||||
|
{-# LANGUAGE TypeOperators #-}
|
||||||
{-|
|
{-|
|
||||||
Module : Grenade.Layers.Tanh
|
Module : Grenade.Layers.Tanh
|
||||||
Description : Hyperbolic tangent nonlinear layer
|
Description : Hyperbolic tangent nonlinear layer
|
||||||
@ -20,7 +20,7 @@ import Data.Singletons
|
|||||||
import Grenade.Core
|
import Grenade.Core
|
||||||
|
|
||||||
-- | A Tanh layer.
|
-- | A Tanh layer.
|
||||||
-- A layer which can act between any shape of the same dimension, perfoming a tanh function.
|
-- A layer which can act between any shape of the same dimension, performing a tanh function.
|
||||||
data Tanh = Tanh
|
data Tanh = Tanh
|
||||||
deriving Show
|
deriving Show
|
||||||
|
|
||||||
|
Loading…
Reference in New Issue
Block a user