[Haskell-cafe] Re: [Haskell] What's up with this Haskell runtime error message:

Michael Goodrich michael.goodrich at gmail.com
Wed Apr 5 16:21:32 EDT 2006


On 4/5/06, ihope <ihope127 at gmail.com> wrote:
>
> On 4/5/06, Michael Goodrich <michael.goodrich at gmail.com> wrote:
> > Looks like my calulation involves a self referential set of definitions.
> >
> >  Is Haskell not able to deal with a self referential set of definitions?
>
> Yes, it is, but not if that definition doesn't evaluate to a "proper"
> value. For example:
>
> main = do
>   print x
>   where x = 3 * x^2
>
> What do you expect this to do?
>
> It may help if you toss us the offending code.




I will be glad to.  But just to make it more simple,  it is a recursive
function with a self referential set of definitions that builds a list like
this :
------------------------------------------------------------------------------------------------------------

 foo  (step,r0,mu0) = bar (step,r1,r0,mu1,mu0)
    where
    r1 = r0-step*rd
    mu1 = mu0-step*mud
    rd = c*c*mu0
    mud = c*c/r0 - (foobar_r z)/c
    c = baz(z)
    z = 6.378388e6-r0

baz z | z<125 = -0.25*z+1537.5
        | otherwise = 0.0169*z+1504.1

foobar_r z | z<125 = 0.25
    | otherwise = -0.0169

bar (step,r2,r1,mu2,mu1) = (r,z0) : bar (step,r1,r,mu1,m)
    where
    r = r2+2*step*rdc
    m = mu2+2*step*mudc
    rdc = (rd2+rd1+rd0)/6
    mudc = (mud2+mud1+mud0)/6

    rd2 = c2*c2*mu2
    mud2 = c2*c2/r2 - (foobar_r z2)/c2

    rd1 = c1*c1*mu1
    mud1 = c1*c1/r1 - (foobar_r z1)/c1

    rd0 = c0*c0*m
    mud0 = c0*c0/r - (foobar_r z0)/c0

    c2 = baz(z2)
    c1 = baz(z1)
    c0 = baz(z0)

    z2 = 6.378388e6-r2
    z1 = 6.378388e6-r1
    z0 = 6.378388e6-r

main :: IO ()
main = do
    print $ take 100 (foo (0.1, 6.378388e6,0))
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org//pipermail/haskell-cafe/attachments/20060405/315bba97/attachment.htm


More information about the Haskell-Cafe mailing list