Perhaps I am really asking it to do too much.
This I thought might be reasonable since one is supposed to be achieving a sequence-less style of programming. But this would seem to be a counter example where I will be essentially forced to implement a sequential processing semantic in a language environment which ostensibly would deny me such (for my own good I understand).
Thoughts?
On 4/6/06, Garrett Mitchener <[EMAIL PROTECTED]> wrote:
I came up with a system of coloring -- you'll have to view this message as html to see it. You start with the input parameters -- those are green. Anything defined in terms of green is blue. Anything defined in terms of green & blue is purple. Anything defined in terms of green, blue, and purple is orange, etc. Then you can see the problem. So in foo, everything checks out, you get to orange and there's just a couple of expressions left and you can see that there's no loop.-----------------------------------------------------------------------------------------------------------
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
But when you try coloring bar, you get this far and then we're stuck. The problem is clear: r depends on rdc, which depends on rd0, which depends on c0, which depends on z0, which depends on r. So your definition for r includes a loop.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))
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe