-- While working on this module you are encouraged to remove it and fix
-- any warnings in the module. See
--     http://hackage.haskell.org/trac/ghc/wiki/WorkingConventions#Warnings
-- for details  

-----------------------------------------------------------------------------
-- |
-- Module      :  Vector Utils
-- Copyright   :  (c) Philipp Pribbernow
-- License     :  BSD-style (see the file libraries/base/LICENSE)
-- 
-- Maintainer  :  libraries@haskell.org
-- Stability   :  experimental
-- Portability :  portable
--
-- A library providing basic vector operations for the clustering module
-----------------------------------------------------------------------------

module Numeric.Statistics.Clustering.VectorUtils (
                      -- * Datatypes
                      Vector(..),
                      
                      -- * Vector Creation
                      singleton,
                      emptyVector,
                      fromList,
                      
                      -- * Vector Operations
                      addV,
                      subV,
                      mulV,
                      divV,
                      sumV,
                      
                      -- * Vector Metrics
                      euklideanDistance,
                      qeuklideanDistance,
                      norm,
                      meanSquareV,
                      
                      -- * Mathematical Helper Functions
                      average,
                      devsq
                   ) where

   
{----------------------------------------------------------------------------
  Datatypes
-----------------------------------------------------------------------------}  

-- | a vector is represented as an ordinary list    
type Vector a = [a]


{----------------------------------------------------------------------------
  Vector Creation
-----------------------------------------------------------------------------}  

-- | maps an element into a one element vector
singleton :: a -> Vector a
singleton = \x -> [x]

-- | creates an empty vector
emptyVector :: [a]
emptyVector = []

-- | converts every element of a given list into a one element vector
fromList :: [a] -> [Vector a]
fromList = map singleton

{----------------------------------------------------------------------------
  Basic vector operations
-----------------------------------------------------------------------------}

-- | subtracts two given vectors
subV :: Num a => [a] -> [a] -> [a]
subV a b = zipWith (-) a b

-- | adds two given vectors
addV :: Num a => [a] -> [a] -> [a]
addV a b = zipWith (+) a b

-- | calculates the vector product of two given vectors
mulV :: Num a => [a] -> [a] -> [a]
mulV a b = zipWith (*) a b

-- | divides two given vectors
divV :: Fractional a => [a] -> [a] -> [a]
divV a b = zipWith (/) a b

-- | calculates the sum of a given list of vectors
sumV :: Num a => [[a]] -> [a]
sumV = foldl addV emptyVector 

{----------------------------------------------------------------------------
  Vector metrics
-----------------------------------------------------------------------------}
		
-- calculates the distance between two vectors in euklidean space
euklideanDistance :: Floating a => Vector a -> Vector a -> a
euklideanDistance a b = norm $ a `subV` b

-- calculates the quadratic euklidean distance
qeuklideanDistance :: Floating a => [a] -> [a] -> a
qeuklideanDistance a b = sum $ map (flip(^)2) $ a `subV` b

-- calculates the norm of a vector
norm :: Floating a => Vector a -> a
norm v = sqrt $ sum (v `mulV` v)

-- computes mean square for a given set of for vectors
meanSquareV :: Floating a => [Vector a] -> a
meanSquareV vs = meanSquareV' 0 vs 
  where 
    meanSquareV' res [] = res
    meanSquareV' res vs' = meanSquareV' (res + (devsq $ map head vs')) (filter (/= []) (map tail vs'))

    
{----------------------------------------------------------------------------
  Mathematical Helper Functions 
-----------------------------------------------------------------------------}
    
-- calculates the average
average :: Floating a => [a] -> a
average xs = let l = length xs
             in (sum xs) / (fromIntegral l)
             
devsq :: Floating a => [a] -> a
devsq xs = let m = average xs
           in sum $ map ((^2).(flip (-))m) xs