{- | BishopData is a module in the HasGP Gaussian Process library. 
     It contains functions to generate toy data as used in "Neural 
     Networks for Pattern Recognition," by Chris Bishop.

     There is one difference between this data and that in the book. 
     Namely: this data is adjusted to have zero mean, making it easier 
     to use in the demonstrations.

     Copyright (C) 2011 Sean Holden. sbh11\@cl.cam.ac.uk.
-}
{- This file is part of HasGP.

   HasGP is free software: you can redistribute it and/or modify
   it under the terms of the GNU General Public License as published by
   the Free Software Foundation, either version 3 of the License, or
   (at your option) any later version.

   HasGP is distributed in the hope that it will be useful,
   but WITHOUT ANY WARRANTY; without even the implied warranty of
   MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
   GNU General Public License for more details.

   You should have received a copy of the GNU General Public License
   along with HasGP.  If not, see <http://www.gnu.org/licenses/>.
-}
module HasGP.Data.BishopData where

import Numeric.LinearAlgebra

import HasGP.Types.MainTypes
import HasGP.Support.Random

h :: Double -> Double
h x = (0.4 * (sin (2 * pi * x))) -- to get the original data add 0.5 to this

bishopData :: (Inputs, Targets)
bishopData = (asColumn inputs, (mapVector h inputs) + n)
    where
      xVar = 0.05
      random = normalVectorSimple 1 1 60
      n = scale (0.05) $ subVector 0 30 random
      i1 = (constant 0.25 15) + (scale (xVar) $ subVector 30 15 random)
      i2 = (constant 0.75 15) + (scale (xVar) $ subVector 45 15 random)
      inputs = join [i1, i2]