hnn-0.2.0.0: A reasonably fast and simple neural network library

Copyright(c) 2012 Gatlin Johnson
LicenseLGPL
Maintainerrokenrol@gmail.com
Stabilityexperimental
PortabilityGHC
Safe HaskellNone
LanguageHaskell98

AI.HNN.Recurrent.Network

Contents

Description

An implementation of recurrent neural networks in pure Haskell.

A network is an adjacency matrix of connection weights, the number of neurons, the number of inputs, and the threshold values for each neuron.

E.g.,

module Main where

import AI.HNN.Recurrent.Network

main = do
    let numNeurons = 3
        numInputs  = 1
        thresholds = replicate numNeurons 0.5
        inputs     = [[0.38], [0.75]]
        adj        = [ 0.0, 0.0, 0.0,
                       0.9, 0.8, 0.0,
                       0.0, 0.1, 0.0 ]
    n <- createNetwork numNeurons numInputs adj thresholds :: IO (Network Double)
    output <- evalNet n inputs sigmoid
    putStrLn $ "Output: " ++ (show output)

This creates a network with three neurons (one of which is an input), an arbitrary connection / weight matrix, and arbitrary thresholds for each neuron. Then, we evaluate the network with an arbitrary input.

For the purposes of this library, the outputs returned are the values of all the neurons except the inputs. Conceptually, in a recurrent net *any* non-input neuron can be treated as an output, so we let you decide which ones matter.

Synopsis

Network type

data Network a Source

Our recurrent neural network

Instances

(Show a, Element a) => Show (Network a) 

createNetwork Source

Arguments

:: (Variate a, Fractional a, Storable a) 
=> Int

number of total neurons neurons (input and otherwise)

-> Int

number of inputs

-> [a]

flat weight matrix

-> [a]

threshold (bias) values for each neuron

-> IO (Network a)

a new network

Creates a network with an adjacency matrix of your choosing, specified as an unboxed vector. You also must supply a vector of threshold values.

Evaluation functions

computeStep Source

Arguments

:: (Variate a, Num a, Storable a, Product a) 
=> Network a

Network to evaluate input

-> Vector a

vector of pre-existing state

-> (a -> a)

activation function

-> Vector a

list of inputs

-> Vector a

new state vector

Evaluates a network with the specified function and list of inputs precisely one time step. This is used by evalNet which is probably a more convenient interface for client applications.

evalNet Source

Arguments

:: (Num a, Variate a, Fractional a, Product a) 
=> Network a

Network to evaluate inputs

-> [[a]]

list of input lists

-> (a -> a)

activation function

-> IO (Vector a)

output state vector

Iterates over a list of input vectors in sequence and computes one time step for each.

Misc

sigmoid :: Floating a => a -> a Source

It's a simple, differentiable sigmoid function.