[Haskell-fr] inférence

Dupont Corentin cdupont at sii.fr
Mon Sep 10 06:23:07 EDT 2007


Salut!
J'ai besoin d'un peu d'aide...
Je débute en haskell. J'essai d'écrire un petit programme qui implémente les
"polynômes interpolateurs de Lagrange".

Mais ma question est plus générale, c'est que j'ai souvent du mal avec le
moteur d'inférence de Haskell.
En effet, un coup mon code compile. Ensuite je fait une petite modif sur une
ligne et ça ne compile plus en me levant une erreur sur une partie
(apparemment) complètement différente du code!!

Dans mon exemple j'ai une variable *nombre_points*. C'est clairement un
entier. Comment le préciser?
Je voudrais aussi l'utiliser dans des divisions. Comment faire?
Je pense que c'est le problème dans mon exemple ci-dessous.

 Merci pour votre aide!
Corentin

PS: Y as t-il un forum en Français d'entraide?


Il me sort une erreur du style:

*Lagrange.hs:60:13:
    No instance for (Fractional Int)
      arising from use of `us' at Lagrange.hs:60:13-17
    Possible fix: add an instance declaration for (Fractional Int)
    In the second argument of `map', namely `(us (m))'
    In the expression: map by (us (m))
    In the definition of `ys': ys = map by (us (m))*

Voici l'exemple:

*module Lagrange where


nombre_points = 7

-- creation d'une liste exluant i
list i = [x | x <- [0..nombre_points-1], x /= i]

-- un terme du polynôme de Lagrange
un_terme t j i = (t - i)/(j - i)

--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)


--Si je décommente les 2 lignes suivantes et que je commente l'autre
définition de blend ci-dessous, ça marche:
--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 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 (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 a = fst (xy !! a)
y a = snd (xy !! a)


-- Blend the sample points for some given u:
bx(u) = blend(x,u)
by(u) = blend(y,u)

-- Take m+1 values for u, from 0 to nombre_points, equally spaced:
us(m) = map (/m) [0.0..(7-1)*m]

-- For

m = 50.0

-- 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
*
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-fr/attachments/20070910/330ac8e8/attachment.htm


More information about the Haskell-fr mailing list