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

Brandon Moore brandonm at yahoo-inc.com
Wed Apr 5 16:17:09 EDT 2006


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 at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe




More information about the Haskell-Cafe mailing list