lapack-0.4.1: Numerical Linear Algebra using LAPACK

Safe HaskellNone
LanguageHaskell98

Numeric.LAPACK.Example.DividedDifference

Description

This module demonstrates triangular matrices.

It verifies that the divided difference scheme nicely fits into a triangular matrix, where function addition is mapped to matrix addition and function multiplication is mapped to matrix multiplication.

http://en.wikipedia.org/wiki/Divided_difference

Synopsis

Documentation

>>> import qualified Test.Utility as Util
>>> import Test.Utility (approxArray)
>>> 
>>> import qualified Numeric.LAPACK.Example.DividedDifference as DD
>>> import qualified Numeric.LAPACK.Vector as Vector
>>> import Numeric.LAPACK.Example.DividedDifference (dividedDifferencesMatrix)
>>> import Numeric.LAPACK.Matrix (ShapeInt, shapeInt, (#+#))
>>> import Numeric.LAPACK.Vector ((|+|))
>>> 
>>> import qualified Data.Array.Comfort.Storable as Array
>>> 
>>> import qualified Test.QuickCheck as QC
>>> 
>>> import Control.Monad (liftM2)
>>> import Data.Tuple.HT (mapPair)
>>> import Data.Semigroup ((<>))
>>> 
>>> type Vector = Vector.Vector ShapeInt Float
>>> 
>>> genDD :: QC.Gen (Vector, (Vector, Vector))
>>> genDD = do
>>> (ys0,ys1) <-
>>> fmap (mapPair (Vector.autoFromList, Vector.autoFromList) .
>>> unzip . take 10) $
>>> QC.listOf $ liftM2 (,) (Util.genElement 10) (Util.genElement 10)
>>> xs <- Util.genDistinct [-10..10] [-10..10] $ Array.shape ys0
>>> return (xs,(ys0,ys1))

upperFromPyramid :: (C sh, Storable a) => sh -> [Vector sh a] -> Upper sh a Source #

dividedDifferencesMatrix :: Vector ShapeInt Float -> Vector ShapeInt Float -> Upper ShapeInt Float Source #

QC.forAll genDD $ \(xs, (ys0,ys1)) -> approxArray (dividedDifferencesMatrix xs (ys0|+|ys1)) (dividedDifferencesMatrix xs ys0 #+# dividedDifferencesMatrix xs ys1)
QC.forAll genDD $ \(xs, (ys0,ys1)) -> approxArray (dividedDifferencesMatrix xs (Vector.mul ys0 ys1)) (dividedDifferencesMatrix xs ys0 <> dividedDifferencesMatrix xs ys1)

parameterDifferencesMatrix :: Vector ShapeInt Float -> Upper ShapeInt Float Source #

QC.forAll (QC.choose (0,10)) $ \n -> let sh = shapeInt n in QC.forAll (Util.genDistinct [-10..10] [-10..10] sh) $ \xs -> approxArray (DD.parameterDifferencesMatrix xs) (DD.upperFromPyramid sh (Vector.zero sh : DD.parameterDifferences xs))

main :: IO () Source #