
When experimenting with list index sets (i.e. lists more general than provided by Haskell), I arrived at the problem that in the example code below for example h(list 6) does not (in Hugs) write out the beginning of the list lazily. It does work for list 6 first (list 6) rest (list 6) 10 -+ (list 3) and so on. So it seems to be a problem with h, also suggested by heap profiling, perhaps similar to that of "foldl". So is it possible to fix it? The function h x is derived by unwinding the monadic construct corresponding to (for lists) do {i <- [x..]; return i} So there are not many possibilities of change. Below, (-+) corresponds, for lists, to ":", "first" to "head", and "rest" to "tail". Hans Aberg -------- data List a = List(Integer->a) instance Show a => Show (List a) where show (List f) = "[" ++ show (f(0)) ++ concat ["," ++ show (f(toInteger i))| i<-[1..]] ++ "]" list :: Integer -> List Integer list x = List(\z -> x+z) (-+) :: a -> List a -> List a x -+ (List y) = List(f) where f 0 = x f k = y(k-1) first :: List a -> a first (List f) = f 0 rest :: List a -> List a rest (List y) = List(f) where f k = y(k+1) h :: List a -> List a h x = (-+) (first x) (h (rest x)) --------

Hans Aberg wrote:
When experimenting with list index sets (i.e. lists more general than provided by Haskell), I arrived at the problem that in the example code below for example h(list 6) does not (in Hugs) write out the beginning of the list lazily. It does work for list 6 first (list 6) rest (list 6) 10 -+ (list 3) and so on. So it seems to be a problem with h, also suggested by heap profiling, perhaps similar to that of "foldl".
So is it possible to fix it? The function h x is derived by unwinding the monadic construct corresponding to (for lists) do {i <- [x..]; return i} So there are not many possibilities of change.
Below, (-+) corresponds, for lists, to ":", "first" to "head", and "rest" to "tail".
Hans Aberg
-------- data List a = List(Integer->a)
instance Show a => Show (List a) where show (List f) = "[" ++ show (f(0)) ++ concat ["," ++ show (f(toInteger i))| i<-[1..]] ++ "]"
list :: Integer -> List Integer list x = List(\z -> x+z)
(-+) :: a -> List a -> List a x -+ (List y) = List(f) where f 0 = x f k = y(k-1)
first :: List a -> a first (List f) = f 0
rest :: List a -> List a rest (List y) = List(f) where f k = y(k+1)
h :: List a -> List a h x = (-+) (first x) (h (rest x))
The combination of (-+) and h is too strict, this modification works: (-+) :: a -> List a -> List a x -+ ~(List y) = List(f) where -- lazy pattern match f 0 = x f k = y(k-1) Claude -- http://claudiusmaximus.goto10.org

On Thu, Mar 27, 2008 at 2:18 PM, Claude Heiland-Allen
The combination of (-+) and h is too strict, this modification works:
(-+) :: a -> List a -> List a x -+ ~(List y) = List(f) where -- lazy pattern match
f 0 = x f k = y(k-1)
More to the point, if List is declared as: newtype List a = List (Integer -> a) Instead of with "data", it also works. The problem, as was stated, was that -+ is too strict. That is, without the ~ there, -+ evaluates its right argument to make sure it's not _|_ (that is the only other possibility in this case), and then proceeds with the rest of the function. So in: h x = first x -+ h (rest X) This first evaluates the recursive call, which will evaluate the recursive call, which ... Luke

On 27 Mar 2008, at 15:32, Luke Palmer wrote:
More to the point, if List is declared as:
newtype List a = List (Integer -> a)
Instead of with "data", it also works.
The problem, as was stated, was that -+ is too strict. That is, without the ~ there, -+ evaluates its right argument to make sure it's not _|_ (that is the only other possibility in this case), and then proceeds with the rest of the function. So in:
h x = first x -+ h (rest X)
This first evaluates the recursive call, which will evaluate the recursive call, which ...
Thank for the suggestion, and explanation. The reason I used a "data" construct was that I include the size of the list, excluded in order to keep the example as simple as possible: data List a = List(Ordinal -> a, Ordinal) In addition, there seems to be no way to choose default value for a given (non-empty) type in Haskell, so I wrote it data List a = Empty | List(Ordinal -> a, Ordinal) Here, if a type T has a default element t, I can represent the empty list by List(\_ -> t, 0) making the constructor "Empty" redundant. Hans Aberg

A few comments:
On Thu, Mar 27, 2008 at 2:55 PM, Hans Aberg
The reason I used a "data" construct was that I include the size of the list, excluded in order to keep the example as simple as possible: data List a = List(Ordinal -> a, Ordinal)
This could still be a newtype, because of the tuple you used here. A more standard way to do this would be: data List a = List (Ordinal -> a) Ordinal Or a record so you could name them. By your naming, am I correct in assuming that you're implementing transfinite lists? If so, cool!
In addition, there seems to be no way to choose default value for a given (non-empty) type in Haskell, so I wrote it data List a = Empty | List(Ordinal -> a, Ordinal) Here, if a type T has a default element t, I can represent the empty list by List(\_ -> t, 0) making the constructor "Empty" redundant.
You could use 'undefined', which has value _|_ (if you're sure that it will never be used). List (const undefined) 0 Or even: List undefined 0 Which are almost, but not quite, identical. (Many argue they should be) Luke

On 27 Mar 2008, at 17:51, Luke Palmer wrote:
By your naming, am I correct in assuming that you're implementing transfinite lists? If so, cool!
Yes, it is an old idea I brought up now. If list length is written also for infinite lists, then concatenated lists get indexed by the sum of their ordinals (and length too). So length x does not cause non-termination if x is an infinite list, but a value. In addition, one needs to restrict to singly linked lists; a list is essentially a cashed lazy function. I wrote a class Ordinal for ordinals below epsilon_0, which are the ones generated by the first uncountable ordinal (the set of natural numbers), and ordinal sum, product and exponentiation, which can be represented explicitly using CNF (Cantor's normal form). These are not large in mathematical terms, but in computers, I think they will suffice a long go. I haven't debugged it yet. But if somebody is interested, just let me know. I think Haskell should have such a module, worked up by computer programmers, who surely can do a better job than me :-). Small ordinal infinities arise naturally when one has say orders f floating windows, or and TeX has (I think) orders of stretchability.
The reason I used a "data" construct was that I include the size of the list, excluded in order to keep the example as simple as possible: data List a = List(Ordinal -> a, Ordinal)
This could still be a newtype, because of the tuple you used here. A more standard way to do this would be:
data List a = List (Ordinal -> a) Ordinal
Or a record so you could name them.
Thank you. I tend to favor tuplet notation because the are more methematical-like, though I have noticed, it is somewhat cumbersome in Haskell pattern matching.
In addition, there seems to be no way to choose default value for a given (non-empty) type in Haskell, so I wrote it data List a = Empty | List(Ordinal -> a, Ordinal) Here, if a type T has a default element t, I can represent the empty list by List(\_ -> t, 0) making the constructor "Empty" redundant.
You could use 'undefined', which has value _|_ (if you're sure that it will never be used).
List (const undefined) 0
Or even:
List undefined 0
Which are almost, but not quite, identical. (Many argue they should be)
I think I need just something that can be plugged into the function spot when length is 0. Hans Aberg

Another way to defer the evaluation of the second argument of (-+) is like this:
(-+) :: a -> List a -> List a
x -+ y = List(f) where
f 0 = x
f k = case y of List g -> g (k-1)
This is exactly what the lazy pattern will do at compile-time. Does
this give you a better understanding of how lazy patterns work and why
they fix the problem?
-- ryan
On 3/27/08, Hans Aberg
On 27 Mar 2008, at 17:51, Luke Palmer wrote:
A more standard way to do this would be:
data List a = List (Ordinal -> a) Ordinal
I used data List a = Empty | (Ordinal->a) :+ Ordinal which might then be simplified by dropping "Empty".
Hans Aberg
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On 28 Mar 2008, at 03:03, Ryan Ingram wrote:
Another way to defer the evaluation of the second argument of (-+) is like this:
(-+) :: a -> List a -> List a x -+ y = List(f) where f 0 = x f k = case y of List g -> g (k-1)
This is exactly what the lazy pattern will do at compile-time.
Thank you for inputs - I discovered adding ordinal length made it tricky to get the lazy evaluation I called for. The problem is that I use data List a = (Ordinal->a) :+ Ordinal and then in (-++) :: a -> List a -> List a x -++ (b:+ q) = f:+(1+q) where f 0 = x f k = b(k-1) possibly I need to get both b and q to be lazy. I tried experimenting with putting i ~also on them, but it did not seem to work. So I may have to experiment a bit more, and perhaps return with a more completet example later. But inputs are welcome.
Does this give you a better understanding of how lazy patterns work and why they fix the problem?
I had such rewriting in mind as well, but could not figure out the right blend. The manual call the lazy pattern "irrefutable". The terminology you use here is more intuitive. It show a problem in language design: Haskell has mad a choice of strict and lazy evaluation in different context, but it has the disadvantage of hiding away the semantics. Something to think about when designing the next lazy computer language. :-) Hans Aberg

On 28 Mar 2008, at 03:03, Ryan Ingram wrote:
Another way to defer the evaluation of the second argument of (-+) is like this:
(-+) :: a -> List a -> List a x -+ y = List(f) where f 0 = x f k = case y of List g -> g (k-1)
This is exactly what the lazy pattern will do at compile-time. Does this give you a better understanding of how lazy patterns work and why they fix the problem?
I have various other patterns that need to be forced lazy - inputs welcome. In the code below, where I have put in a "0" instead of the first uncountable ordinal w, if I include in "show" the case a == 0, then h (list 6) won't print, as then the value of "a" is computed. And in the ordinal version data List a = (Ordinal->a) :+ Ordinal then the function (-+) :: a -> List a -> List a x -+ ~(y :+ q) = f:+(1+q) where f 0 = x f k = y(k-1) does not compute, because there is a similar problem with the 1+q evaluation, I think this is because the class Ordinal + uses case: instance Num Ordinal where x + y | finite x && finite y = toOrdinal(tcoef x + tcoef y) x + y | lexp x < lexp y = y x + y | lexp x == lexp y = prepend (lexp x, lcoef x + lcoef y) (trail y) x + y = prepend (lexp x, lcoef x) ((trail x) + y) So these patterns perhaps should be made lazy. though I do not know exactly how. Hans -------- infixr 5 :+ data List a = (Integer->a) :+ Integer instance Show a => Show (List a) where -- show (f:+a) | a == 0 = "[]" show (f :+ a) = "[" ++ show (f(0)) ++ concat ["," ++ show (f(toInteger i))| i<-[1..]] ++ "]" list :: Integer -> List Integer list x = (\z -> x+z) :+ 0 (-+) :: a -> List a -> List a x -+ ~(y :+ q) = f:+(1+q) where f 0 = x f k = y(k-1) first :: List a -> a first (f :+ _) = f 0 rest :: List a -> List a rest (y :+ _) = f :+ 0 where f k = y(k+1) h :: List a -> List a h x = (-+) (first x) (h (rest x)) --------

On 28 Mar 2008, at 03:03, Ryan Ingram wrote:
Another way to defer the evaluation of the second argument of (-+) is like this:
(-+) :: a -> List a -> List a x -+ y = List(f) where f 0 = x f k = case y of List g -> g (k-1)
This is exactly what the lazy pattern will do at compile-time. Does this give you a better understanding of how lazy patterns work and why they fix the problem?
I can isolate the problem with the addition in the code below, where I have defined a type Natural just in order to introduce a user defined operator. - For ordinals, it is more complicated. Then h (list 6) only printouts "[N 6,", after which it gets stuck in the Natural.+. Adding ~ to (N x) + (N y) does not help, nor other variations. But replacing Natural with integer, produces the normal infinite list printout. So it must be here it is stuck. Hans -------- infix 5 :+ data Natural = N Integer deriving (Eq, Show) instance Num Natural where fromInteger x = N x abs x = x signum 0 = 0 signum _ = 1 (N x) + (N y) = N(x + y) data List a = (Natural->a) :+ Natural instance Show a => Show (List a) where show (f :+ _) = "[" ++ show (f(0)) ++ concat ["," ++ show (f(N (toInteger i)))| i<-[1..]] ++ "]" list :: Natural -> List Natural list x = (\z -> x+z) :+ 0 (-+) :: a -> List a -> List a x -+ ~(y :+ q) = f:+(1+q) where f 0 = x f k = y(k-1) first :: List a -> a first (f :+ _) = f 0 rest :: List a -> List a rest (y :+ _) = f :+ 0 where f k = y(k+1) h :: List a -> List a h x = (-+) (first x) (h (rest x)) --------

I have fixed the problem now. In the last letter, with the Natural class, I had not added instance Num Natural where (N x) - (N y) = N(x - y) which the Ordinal class then in fact has one. Then it turns out that it is merely the fact that "show" had some cases looking at the list length that blocked its output. So there, one should probably have some recursion that extracts elements one by one, without computing list length, and adds a termination 2]" if the remaining list is empty. So it seems possible to emulate Haskell list behavior with this model, which is one thing I wanted to know. Hans

On 27 Mar 2008, at 15:18, Claude Heiland-Allen wrote:
The combination of (-+) and h is too strict, this modification works:
(-+) :: a -> List a -> List a x -+ ~(List y) = List(f) where -- lazy pattern match f 0 = x f k = y(k-1)
Thank you for the fast response. Yes, that might be what I want. I had a look at lazy patterns, but could not figure out how to put them in. So thanks again. Hans Aberg

Hmmm, seems like your (-+) is not lazy enough. Since pattern matching is strict by default, you have anything -+ (_|_) = (_|_) Therefore, the function, which is constantly (_|_), is a fixed point for the equation defining h. In other words, if you define h' x = undefined then you have h' x = (-+) anything (h anything) in particular, h' x = (-+) (first x) (h (rest x)) You can fix it by defining (-+) as x -+ ~(List y) = ...
data List a = List(Integer->a)
instance Show a => Show (List a) where show (List f) = "[" ++ show (f(0)) ++ concat ["," ++ show (f(toInteger i))| i<-[1..]] ++ "]"
list :: Integer -> List Integer list x = List(\z -> x+z)
(-+) :: a -> List a -> List a x -+ (List y) = List(f) where f 0 = x f k = y(k-1)
first :: List a -> a first (List f) = f 0
rest :: List a -> List a rest (List y) = List(f) where f k = y(k+1)
h :: List a -> List a h x = (-+) (first x) (h (rest x)) -------- _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On 27 Mar 2008, at 15:58, Miguel Mitrofanov wrote:
Hmmm, seems like your (-+) is not lazy enough. ... You can fix it by defining (-+) as
x -+ ~(List y) = ...
Yes, this has been pointed out...
Since pattern matching is strict by default, you have
anything -+ (_|_) = (_|_)
Therefore, the function, which is constantly (_|_), is a fixed point for the equation defining h. In other words, if you define
h' x = undefined
then you have
h' x = (-+) anything (h anything)
in particular,
h' x = (-+) (first x) (h (rest x))
But additional explanation is helpful. Thank you. Hans Aberg
participants (5)
-
Claude Heiland-Allen
-
Hans Aberg
-
Luke Palmer
-
Miguel Mitrofanov
-
Ryan Ingram