{- | Gaussian Process Library. This module contains assorted functions that 
   support the computation of covariance, constructing covariance matrices 
   etc.

   Covariance functions store log parameters. Functions are needed to return 
   the covariance and its derivative. Derivatives are with respect to the 
   actual parameters, NOT their logs.

   Copyright (C) 2011 Sean Holden. sbh11\@cl.cam.ac.uk.
-}
{- 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.Covariance.Basic 
   (
     CovarianceFunction,
     trueHyper,
     covariance,
     dCovarianceDParameters,
     makeCovarianceFromList,
     makeListFromCovariance,
     covarianceMatrix,
     covarianceWithPoint,
     covarianceWithPoints
   ) where

import Numeric.LinearAlgebra

import HasGP.Types.MainTypes

class CovarianceFunction a where
    -- ^ The actual hyperparameter values.
    trueHyper :: a -> DVector           
    -- ^ The covariance
    covariance :: a -> DVector -> DVector -> Double 
    -- ^ Derivative of covariance with respect to parameters 
    dCovarianceDParameters :: a -> DVector -> DVector -> DVector 
    -- ^ Construct using log parameters.
    makeCovarianceFromList :: a -> [Double] -> a 
    -- ^ Get log parameters.
    makeListFromCovariance :: a -> [Double]  

-- | Construct a matrix of covariances from a covariance and a design matrix. 
covarianceMatrix :: (CovarianceFunction c) => c -> Inputs 
              -> CovarianceMatrix
covarianceMatrix c d = (r><r) [(covariance c x y) | x <- dList, y <- dList]
    where
      r = rows d
      dList = toRows d

-- | Constructs the column vector required when a new input is included. 
--   Constructed as a matrix to avoid further work elsewhere. 
covarianceWithPoint :: (CovarianceFunction c) => c 
                    -> Inputs
                    -> Input
                    -> DVector
covarianceWithPoint c d xStar = fromList [((covariance c) x xStar) | x <- dList]
    where
      r = rows d
      dList = toRows d

-- | covarianceWithPoint applied to a list of points to produce 
--   a list of vectors.
covarianceWithPoints :: (CovarianceFunction c) => c 
                    -> Inputs 
                    -> [Input]
                    -> [DVector]
covarianceWithPoints c d xStars = map (covarianceWithPoint c d) xStars