Hi Phil,
On 22/01/11 14:07, gutti wrote:
Dear Haskellers,
I'm looking for Vector and especially Matric interpolation ala:
z = interp2 (xMatrix, yMatrix, zMatrix, x, y)
- x and y can be single values or also vectors or matrices
- indeally with the options nearest, linear, quadratic, qubic..
Any hope that there is something similar especially using the HMatrix
matrices (Matrix Double). - If I have to code it any suggestions ?
Cheers Phil
I'm not sure if this is what you mean, as I'm not familiar with matlab,
so apologies if this is totally a waste of time.. But I had a simple
cubic interpolation implemented already, it wasn't too hard to lift it
into matrices (there are many elevation permutations, I imagine), I used
(fromLists ...stuff... toLists), but maybe there's a better way:
{-# LANGUAGE NoMonomorphismRestriction #-}
module Interpolate where
import Numeric.LinearAlgebra
import Data.List (zipWith5)
-- cubic interpolation
cubic t a b c d =
let a1 = 0.5 * (c - a)
a2 = a - 2.5 * b + 2.0 * c - 0.5 * d
a3 = 0.5 * (d - a) + 1.5 * (b - c)
in ((a3 * t + a2) * t + a1) * t + b
-- boring manual lifting
liftMatrix5 f a b c d e =
let la = toLists a
lb = toLists b
lc = toLists c
ld = toLists d
le = toLists e
in fromLists (zipWith5 (zipWith5 f) la lb lc ld le)
-- test
mt = (3><3) [0, 0.1 ..]
ma = (3><3) [0, 1 ..]
mb = (3><3) [0, 2 ..]
mc = (3><3) [0, 3 ..]
md = (3><3) [0, 4 ..]
test = liftMatrix5 cubic mt ma mb mc md
{- test output
(3><3)
[ 0.0, 2.1, 4.4
, 6.9, 9.6, 12.5
, 15.600000000000001, 18.9, 22.4 ]
-}
--
http://claudiusmaximus.goto10.org
_______________________________________________
Haskell-Cafe mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/haskell-cafe