module RC.Helpers
( addBiases
, randList
, randMatrix
, randSparse
, hsigmoid
) where
import System.Random
import Data.List ( unfoldr )
import qualified Numeric.LinearAlgebra as LA
hsigmoid :: (Fractional a, Ord a)
=> (a, a, a)
-> a
-> a
hsigmoid (β, width, offset) x = f
where
f | x < offset = 0.0
| x < width = β * (x offset)
| otherwise = β * (width offset)
addBiases :: LA.Matrix Double -> LA.Matrix Double
addBiases m = let no = LA.cols m
m' = LA.konst 1.0 (1, no)
in m' LA.=== m
randMatrix
:: StdGen
-> (Int, Int)
-> (Double, Double)
-> LA.Matrix Double
randMatrix seed (rows', cols') (minVal, maxVal) = (LA.reshape cols'. LA.vector) xs
where
xs = f <$> randList (rows' * cols') seed
f x = (maxVal minVal) * x + minVal
randSparse g (rows', cols') (minVal, maxVal) connectivity =
LA.reshape cols' $ LA.vector xs
where
(g1, g2) = split g
rlist = randList (rows' * cols')
xs = zipWith f (rlist g1) (rlist g2)
f lv rv | lv < connectivity = (maxVal minVal) * rv + minVal
| otherwise = 0.0
randList :: (Random a, Floating a) => Int -> StdGen -> [a]
randList n = take n. unfoldr (Just. random)