using error x as a placeholder

Hal Daume III hdaume@ISI.EDU
Tue, 14 May 2002 11:39:57 -0700 (PDT)


I've seen 'error "foo"' or simply 'undefined' used as a placeholder for
elements in a structure which we, as programmers, know will be filled in
soon.  Often this makes the code clearer because the creation of the data
structure and filling in its values is separated (you could argue with
this, but that's not the point).

This troubles me, though, because even though *we* know the elements will
be filled in, maybe the strictness analyser doesn't.  So, to test this, I
wrote the following program:

module Main where

import Array

sumArray :: Array Int Integer -> Integer
sumArray arr = sumArray' 0 low
    where (low,high) = bounds arr
	  sumArray' acc pos | pos > high = acc
			    | otherwise  = sumArray' (acc + (arr!pos)) (pos+1)


mkArray1 :: Array Int Integer
mkArray1 = fillInArr 1 (listArray (1,9999) (repeat undefined))
    where fillInArr 5000 arr = arr // [(5000,arr!4999 + arr!5001)]
	  fillInArr 1    arr = fillInArr 2 (arr // [(1,1),(9999,2)])
	  fillInArr n    arr = fillInArr (n+1)
			        (arr // [(n,(arr!(n-1))+(arr!(10001-n))),(10000-n,(arr!(n-1))+(arr!(10001-n))+1)])

mkArray2 :: Array Int Integer
mkArray2 = fillInArr 1 (listArray (1,9999) (repeat 0))
    where fillInArr 5000 arr = arr // [(5000,arr!4999 + arr!5001)]
	  fillInArr 1    arr = fillInArr 2 (arr // [(1,1),(9999,2)])
	  fillInArr n    arr = fillInArr (n+1)
			        (arr // [(n,(arr!(n-1))+(arr!(10001-n))),(10000-n,(arr!(n-1))+(arr!(10001-n))+1)])

main = print $ (sumArray mkArray1) `mod` 1024

And compiled it using both mkArray1 (which has undefined elements,
supposedly) and mkArray2, which doesn't.  (I tried to come up with a
function with which to fill in the array that was nontrivial, in the sence
that it would be difficult to code using accumulators without the explicit
recursive 'fillInArr' function.)

The timing results were:

mkArray1: 11.42u 0.79s 0:13.47 90.6%
mkArray2: 24.55u 2.31s 0:30.12 89.1%

Which is actually *slower*.  Any ideas why?  (These were compiled with ghc
5.02.3 -O2 -fvia-c -fall-strict)

 - Hal

--
Hal Daume III

 "Computer science is no more about computers    | hdaume@isi.edu
  than astronomy is about telescopes." -Dijkstra | www.isi.edu/~hdaume