{- | Demonstration of Gaussian process regression using the simple data from "Neural Networks for Pattern Recognition," by Chris Bishop. This version estimates the hyperparameters using the optimization algorithm from HMatrix. For details of the algorithms involved see www.gaussianprocesses.org. 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 . -} module HasGP.Demos.RegressionDemo1 where import Numeric.LinearAlgebra import Numeric.GSL.Minimization import HasGP.Data.BishopData import HasGP.Types.MainTypes import HasGP.Support.Linear import HasGP.Support.Random import HasGP.Regression.Regression import HasGP.Covariance.SquaredExp demo = do putStrLn "Generating the training data..." let (inputs, targets) = bishopData saveMatrix "inputs.txt" "%g" inputs fprintfVector "targets.txt" "%g" targets putStrLn "Searching for best hyperparameters..." let f = gpRLogHyperToEvidence (SquaredExponential 0 0) inputs targets let ev = fst . f let gev = snd . f let (solution, path) = minimizeVD ConjugatePR 0.0001 50 0.01 0.1 ev gev (constant (log 0.1) 3) putStrLn $ "Found: " ++ (show solution) putStrLn $ "Path: " putStrLn $ show path putStrLn "Learning and predicting..." let newPoints = fromColumns $ [linspace 100 (0.0,1.0)] let (newOuts, var) = gpRPredict' (SquaredExponential (solution @> 1) (solution @> 2)) (solution @> 0) inputs targets newPoints fprintfVector "outputs.txt" "%g" newOuts fprintfVector "variances.txt" "%g" var putStrLn "Done" return ()