module Lagrange where
nombre_points :: Integer
nombre_points = 7
-- creation d'une liste exluant i
list :: Integer -> [Integer]
list i = filter (/=i) [0..nombre_points-1]
-- un terme du polynôme de Lagrange
--un_terme :: Float -> Integer -> Integer -> Float
un_terme t j i = (t - i_f)/(j_f - i_f)
where i_f = fromInteger i
j_f = fromInteger j
--produit des termes pour obtenir le polynôme d'un point
les_termes t j = map (un_terme t j) (list j)
poly t j = product (les_termes t j)
--blend (a,t) = a(0) * (poly t 0) + a(1) * (poly t 1) + a(2) * (poly t 2) + a(3) * (poly t 3) +
-- a(4) * (poly t 4) + a(5) * (poly t 5) + a(6) * (poly t 6)
--t est le paramètre du polynôme, a sera la coordonnée (x ou y).
blend_un_point :: Float -> (Integer -> Float) -> Integer -> Float
blend_un_point t a numero_point = a(numero_point) * (poly t numero_point)
blend_les_points t a = map (blend_un_point t a) [0..6]
blend :: (Integer -> Float, Float) -> Float
blend (a,t) = sum (blend_les_points t a)
-- Sample points
xy = [(-4.0,0.0), (-1.0,1.0), (-3.0,3.0), (0.0,4.0), (3.0,3.0),(1.0,1.0),(4.0,0.0)]
--creation des fonctions x et y
x :: Integer -> Float
x pos = fst (xy !! pos_Integer)
where pos_Integer = fromInteger(pos)
y :: Integer -> Float
y pos = snd (xy !! pos_Integer)
where pos_Integer = fromInteger(pos)
-- Blend the sample points for some given u:
bx :: Float -> Float
bx(u) = blend(x,u)
by :: Float -> Float
by(u) = blend(y,u)
-- Take m+1 values for u, from 0 to nombre_points, equally spaced:
us :: Integer -> [Float]
us m = map (/mf) [0..6*mf]
where mf = fromInteger m
-- For
m = 50
-- we get us(m)=[0.0, 0.125, 0.25, 0.375, 0.5, 0.625, 0.75, 0.875, 1.0].
-- Now get a list of points for the above values of the parameter:
xs = map bx (us(m))
ys = map by (us(m))
-- Running this, we get, where I've rounded the results to 2 digits:
--
-- xs = [0.00, 0.38, 0.75, 1.1, 1.5, 1.9, 2.3, 2.6, 3.0]
-- ys = [0.00, 0.46, 1.00, 1.7, 2.3, 2.8, 3.1, 3.2, 3.0]
-- Finally, get a list of pairs (x,y), i.e. a list of points:
ps = zip xs ys
-- In this example, running "ps" we get, after rounding, the points:
--
-- [(0, 0), (0.38, 0.46), (0.75, 1), (1.1, 1.7),
-- (1.5, 2.3), (1.9, 2.8), (2.3, 3.1), (2.6, 3.2), (3, 3)]
--
-- Now plot lines joining these points to get an approximation of the curve