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

Looks like my calulation involves a self referential set of definitions. Is Haskell not able to deal with a self referential set of definitions? I was frankly hoing it would since otherwise there is then the specter of sequence, i.e. that I have to finesse the order in which things are calculated so as to avoid it. Thoughts? cheers, -Mike

On 4/5/06, Michael Goodrich
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.

On 4/5/06, ihope
On 4/5/06, Michael Goodrich
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))

Michael Goodrich wrote: [snip]
r = r2+2*step*rdc rdc = (rd2+rd1+rd0)/6 rd0 = c0*c0*m c0 = baz(z0) z0 = 6.378388e6-r
The equations above form a loop: each one requires the one below it, and the last one requires the first one. (And yes, baz is strict) Regards, Roberto Zunino.

On 4/5/06, Roberto Zunino
Michael Goodrich wrote: [snip]
r = r2+2*step*rdc rdc = (rd2+rd1+rd0)/6 rd0 = c0*c0*m c0 = baz(z0) z0 = 6.378388e6-r
The equations above form a loop: each one requires the one below it, and the last one requires the first one.
(And yes, baz is strict)
Regards, Roberto Zunino.
Interesting, I was told that it is ok to have a mutually dependent set of definitions - are you saying that Haskell cannot handle this? Also I know what strict means, but why are you saying that baz is strict?

Michael Goodrich wrote:
Also I know what strict means, but why are you saying that baz is strict?
Because otherwise the loop would be OK. For instance if baz were baz x = 100 -- lazy then the equations could be evaluated starting from c0 = baz z0 = 100 rd0 = c0*c0*m = 100*100*m -- etc. and eventually all the variables could be defined. Another example: the pair constructor (,) is lazy so c = (3, fst c) -- "loop" on c is OK, and defines c=(3,3). Regards, Roberto Zunino.

Michael Goodrich 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?
I was frankly hoing it would since otherwise there is then the specter of sequence, i.e. that I have to finesse the order in which things are calculated so as to avoid it.
Thoughts?
Lazy evaluation is great with self-referential definitions, but id doesn't do so well with ill-founded definitions. It also won't find fixpoints of numeric equations. Here are some examples, and then some explanation. Things that work: {- for interactive use in ghci -} let ones = 1:ones --infinite list of ones let counting = 1:map (+1) counting -- infinite list counting up from one let fibs = 1:1:zipWith (+) fibs (tail fibs) --fibbonacci numbers {- A larger program. turns references by name into direct references Try on a cyclic graph, like buildGraph [("a",["b"]),("b",["a"])] -} import Data.List import Data.Map as Map data Node = Node String [Node] type NodeDesc = (String, [String]) buildNode :: Map String Node -> NodeDesc -> Node buildNode env (name,outlinks) = Node name (concat [Map.lookup other finalBinds | other <- outlinks]) buildGraph :: [(String,[String])] -> [Node] buildGraph descs = nodes where (finalBinds, nodes) = mapAccumR buildExtend Map.empty descs buildExtend binds desc@(name,_) = let node = buildNode finalBinds desc in (Map.insert name node binds, node) Things that will not work: let x = x -- no information on how to define x let x = 2*x + 1 -- this is not treated algebraically let broke = 1:zipWith (+) broke (tail broke) -- the second element depends on itself Recursive definitions in Haskell can be explained by saying that they find the least-defined fixedpoint of the equations. Every type in Haskell has all the usual values you would have in a strict language, plus an undefined value which corresponds to a nonterminating computation. Also, there are values where subterms of different types are undefined values of that type rather. For example, with pairs of numbers there are these posibilites (x,y) / \ (_|_,x) (x,|_|) \ / (_|_,_|_) | _|_ where x and y represent any defined number, and _|_ is "undefined", or a non-terminating computation. A value on any line is considered more defined than values on lower lines. Any value which can be obtained from another by replacing subterms with _|_ is less defined, if neither can be made from the other that way than neither is more defined that the other. Think of a definition like x = f x. That will make x the least-defined value which is a fixedpoint of f. For example, numeric operations are (generally) strict, so _|_ * x = _|_, _|_ + x = _|_, and _|_ is a fixedpoint of \x -> 2*x + 1. for broke, consider the function f = \l -> 1:(zipWith (+) l (tail l)) f (x:_|_) = 1:zipWith (+) (1:_|_) (tail (1:_|_)) = 1:zipWith (+) (1:_|_) _|_ = 1:_|_ so 1:_|_ is a fixedpoint. It's also the least fixedpoint, because _|_:_|_ is not a fixedpoint, and f _|_ = 1:<something>, so _|_ is not a fixedpoint either. If I try that definition of broke, ghci prints "[1" and hangs, indicating that the rest of the list is undefined. If multiple definitions are involved, think of a function on a tuple of all the definitions: x = y y = 1:x corresponds to the least fixedpoint of (\(x,y) -> (y,1:x)) The recursiveness in the graph example is more tedious to analyze like this, but it works out the same way - whatever value of "finalBinds" is fed into the recursive equation, you get out a map built by taking the empty map and adding a binding for each node name. Chase it around a few more times, and you'll get some detail about the nodes. Also, posting code really helps if you want specific advice. Thanks to the hard work of compiler writers, the error message are usually precise enough for a message like this to describe the possibilites. If you enjoy my rambling I suppose you should keep posting error messages :) Brandon
cheers,
-Mike
------------------------------------------------------------------------
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Oops, I just realized that you gave me the answer, namely that it won't find
fixed points of numeric sets of equations.
Pity, that would really have made Haskell useful for this kind of scientific
computing.
On 4/5/06, Brandon Moore
Michael Goodrich 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?
I was frankly hoing it would since otherwise there is then the specter of sequence, i.e. that I have to finesse the order in which things are calculated so as to avoid it.
Thoughts?
Lazy evaluation is great with self-referential definitions, but id doesn't do so well with ill-founded definitions. It also won't find fixpoints of numeric equations. Here are some examples, and then some explanation.
Things that work:
{- for interactive use in ghci -} let ones = 1:ones --infinite list of ones let counting = 1:map (+1) counting -- infinite list counting up from one let fibs = 1:1:zipWith (+) fibs (tail fibs) --fibbonacci numbers
{- A larger program. turns references by name into direct references Try on a cyclic graph, like buildGraph [("a",["b"]),("b",["a"])] -} import Data.List import Data.Map as Map
data Node = Node String [Node] type NodeDesc = (String, [String])
buildNode :: Map String Node -> NodeDesc -> Node buildNode env (name,outlinks) = Node name (concat [Map.lookup other finalBinds | other <- outlinks])
buildGraph :: [(String,[String])] -> [Node] buildGraph descs = nodes where (finalBinds, nodes) = mapAccumR buildExtend Map.empty descs buildExtend binds desc@(name,_) = let node = buildNode finalBinds desc in (Map.insert name node binds, node)
Things that will not work:
let x = x -- no information on how to define x
let x = 2*x + 1 -- this is not treated algebraically
let broke = 1:zipWith (+) broke (tail broke) -- the second element depends on itself
Recursive definitions in Haskell can be explained by saying that they find the least-defined fixedpoint of the equations. Every type in Haskell has all the usual values you would have in a strict language, plus an undefined value which corresponds to a nonterminating computation. Also, there are values where subterms of different types are undefined values of that type rather.
For example, with pairs of numbers there are these posibilites (x,y) / \ (_|_,x) (x,|_|) \ / (_|_,_|_) | _|_ where x and y represent any defined number, and _|_ is "undefined", or a non-terminating computation. A value on any line is considered more defined than values on lower lines. Any value which can be obtained from another by replacing subterms with _|_ is less defined, if neither can be made from the other that way than neither is more defined that the other.
Think of a definition like x = f x. That will make x the least-defined value which is a fixedpoint of f. For example, numeric operations are (generally) strict, so _|_ * x = _|_, _|_ + x = _|_, and _|_ is a fixedpoint of \x -> 2*x + 1.
for broke, consider the function f = \l -> 1:(zipWith (+) l (tail l)) f (x:_|_) = 1:zipWith (+) (1:_|_) (tail (1:_|_)) = 1:zipWith (+) (1:_|_) _|_ = 1:_|_ so 1:_|_ is a fixedpoint. It's also the least fixedpoint, because _|_:_|_ is not a fixedpoint, and f _|_ = 1:<something>, so _|_ is not a fixedpoint either. If I try that definition of broke, ghci prints "[1" and hangs, indicating that the rest of the list is undefined.
If multiple definitions are involved, think of a function on a tuple of all the definitions:
x = y y = 1:x
corresponds to the least fixedpoint of (\(x,y) -> (y,1:x))
The recursiveness in the graph example is more tedious to analyze like this, but it works out the same way - whatever value of "finalBinds" is fed into the recursive equation, you get out a map built by taking the empty map and adding a binding for each node name. Chase it around a few more times, and you'll get some detail about the nodes.
Also, posting code really helps if you want specific advice. Thanks to the hard work of compiler writers, the error message are usually precise enough for a message like this to describe the possibilites. If you enjoy my rambling I suppose you should keep posting error messages :)
Brandon
cheers,
-Mike
------------------------------------------------------------------------
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Wednesday 05 April 2006 04:51 pm, Michael Goodrich wrote:
Oops, I just realized that you gave me the answer, namely that it won't find fixed points of numeric sets of equations.
Pity, that would really have made Haskell useful for this kind of scientific computing.
See section 4 of: http://www.cs.chalmers.se/~rjmh/Papers/whyfp.html See also: http://www.haskell.org/haskellwiki/Libraries_and_tools/Mathematics http://users.info.unicaen.fr/~karczma/arpap/
On 4/5/06, Brandon Moore
wrote: Michael Goodrich 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?
I was frankly hoing it would since otherwise there is then the specter of sequence, i.e. that I have to finesse the order in which things are calculated so as to avoid it.
Thoughts?
Lazy evaluation is great with self-referential definitions, but id doesn't do so well with ill-founded definitions. It also won't find fixpoints of numeric equations. Here are some examples, and then some explanation.
Things that work:
{- for interactive use in ghci -} let ones = 1:ones --infinite list of ones let counting = 1:map (+1) counting -- infinite list counting up from one let fibs = 1:1:zipWith (+) fibs (tail fibs) --fibbonacci numbers
{- A larger program. turns references by name into direct references Try on a cyclic graph, like buildGraph [("a",["b"]),("b",["a"])] -} import Data.List import Data.Map as Map
data Node = Node String [Node] type NodeDesc = (String, [String])
buildNode :: Map String Node -> NodeDesc -> Node buildNode env (name,outlinks) = Node name (concat [Map.lookup other finalBinds | other <- outlinks])
buildGraph :: [(String,[String])] -> [Node] buildGraph descs = nodes where (finalBinds, nodes) = mapAccumR buildExtend Map.empty descs buildExtend binds desc@(name,_) = let node = buildNode finalBinds desc in (Map.insert name node binds, node)
Things that will not work:
let x = x -- no information on how to define x
let x = 2*x + 1 -- this is not treated algebraically
let broke = 1:zipWith (+) broke (tail broke) -- the second element depends on itself
Recursive definitions in Haskell can be explained by saying that they find the least-defined fixedpoint of the equations. Every type in Haskell has all the usual values you would have in a strict language, plus an undefined value which corresponds to a nonterminating computation. Also, there are values where subterms of different types are undefined values of that type rather.
For example, with pairs of numbers there are these posibilites (x,y) / \ (_|_,x) (x,|_|) \ / (_|_,_|_)
_|_ where x and y represent any defined number, and _|_ is "undefined", or a non-terminating computation. A value on any line is considered more defined than values on lower lines. Any value which can be obtained from another by replacing subterms with _|_ is less defined, if neither can be made from the other that way than neither is more defined that the other.
Think of a definition like x = f x. That will make x the least-defined value which is a fixedpoint of f. For example, numeric operations are (generally) strict, so _|_ * x = _|_, _|_ + x = _|_, and _|_ is a fixedpoint of \x -> 2*x + 1.
for broke, consider the function f = \l -> 1:(zipWith (+) l (tail l)) f (x:_|_) = 1:zipWith (+) (1:_|_) (tail (1:_|_)) = 1:zipWith (+) (1:_|_) _|_ = 1:_|_ so 1:_|_ is a fixedpoint. It's also the least fixedpoint, because _|_:_|_ is not a fixedpoint, and f _|_ = 1:<something>, so _|_ is not a fixedpoint either. If I try that definition of broke, ghci prints "[1" and hangs, indicating that the rest of the list is undefined.
If multiple definitions are involved, think of a function on a tuple of all the definitions:
x = y y = 1:x
corresponds to the least fixedpoint of (\(x,y) -> (y,1:x))
The recursiveness in the graph example is more tedious to analyze like this, but it works out the same way - whatever value of "finalBinds" is fed into the recursive equation, you get out a map built by taking the empty map and adding a binding for each node name. Chase it around a few more times, and you'll get some detail about the nodes.
Also, posting code really helps if you want specific advice. Thanks to the hard work of compiler writers, the error message are usually precise enough for a message like this to describe the possibilites. If you enjoy my rambling I suppose you should keep posting error messages :)
Brandon
cheers,
-Mike
----------------------------------------------------------------------- -
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (5)
-
Brandon Moore
-
ihope
-
Michael Goodrich
-
Robert Dockins
-
Roberto Zunino