Confused about Cyclic struture

Hi, Im a newbie to Haskell and the concept of "cyclic strutures" has confused me a lot For example (taken from Richard Bird's book): ones = 1:ones Its clear that it involves a cyclic structure But: ones = repeat 1 repeat x = x:repeat x I dont really understand what the differences between these two and why the latter does not have a cyclic structure ? Why does changing : repeat x = xs where xs = x:xs create a cyclic stucture ? Thank you Anh _________________________________________________________________ Winks & nudges are here - download MSN Messenger 7.0 today! http://messenger.msn.co.uk

well, it is a little bit tricky. you know, imps do not always make what you want. imp_creates x = x `knot` imp x where knot = (:) imagine the following: you pull a foulard out of your sleeve, foulard : sleeve where sleeve = imp_creates foulard and pull foulard : foulard : sleeve where sleeve = imp_creates foulard and pull. foulard : foulard : foulard : sleeve where sleeve = imp_creates foulard you will waste more and more space, maybe your storage will swell to discworld. this is recursion, but not a cyclic structure. on the other hand: serviette_ring where serviette_ring = foulard `knot` serviette_ring you will pull one single foulard through that thing. x@( foulard `knot` serviette_ring ) where knot = (:) serviette_ring = x and then there is a knot with the beginnig of the same thing you pulled out before. beginning@( foulard `knot` beginning ) where knot = (:) if you pull more and more, you will get the same foulard again and again. you do not need an imp to produce more and more foulards, because this knot closes the ring. so, you will never fill the room just by pulling, because this is a nice little "cyclic structure". - marc

On Thu, 2005-07-07 at 18:43 +0000, Dinh Tien Tuan Anh wrote:
Hi, Im a newbie to Haskell and the concept of "cyclic strutures" has confused me a lot
I think it can be confusing for most people, so I wouldn't be too concerned. I may not answer your question completely, but I hope to give you an idea of where to start. To understand cyclic structures it is useful to think of "graph reduction", because these graphs allow us to conveniently represent sharing between objects. Cycles are simply "self-sharing".
For example (taken from Richard Bird's book):
ones = 1:ones Its clear that it involves a cyclic structure
Here's a graph representation of that list (needs a fixed width font to view correctly): @<--- / \ | / \_| @ / \ / \ (:) 1 The @ sign represents function application. Note that the top application has a cyclic right argument. A good question is how did this cycle come about? One way of answering this question is to consider how recursion can be implemented in graph reduction. The textbook approach is to say: okay let's introduce a dedicated recursion operator, we'll call it fix (for fixpoint or maybe fixed point). The idea is that all recursive equations in the program can be re-written into non-recursive equations by way of the new fix operator. The intuition is that we want to get rid of the recursive call inside ones. Here's a first step: ones' = \z -> 1 : z I've called it ones' to avoid confusion with the original ones. Now the parameter z takes the place of ones in the right-hand-side. We can try to get back to the original version by applying ones' to itself: ones' ones' Of course this doesn't work because ones is now a function, and the rightmost ones' must also be applied to itself: ones' (ones' ones') Still it doesn't work for the same reason. What we want is a way to apply ones' to itself "forever". That's where fix comes in. It should satisfy this equation: fix f = f (fix f) Thus: fix ones' = ones' (ones' (ones' (ones' ... ) ) ) = 1 : (ones' (ones' (ones' ... ) ) ) = 1 : 1 : (ones' (ones' ...) ) ... So we can tidy things up a bit: ones = fix (\z -> 1 : z) This is the infinite list of ones, but not recursive (though fix is recursive!). So how is fix represented as a graph? Here's one option: fix----> \f | | @ / \ / \ f @ / \ / \ fix f No cycles! Here's another "clever" option: fix---->\f | | @<---- / \ | / \__| f Now a cycle. Note how the cycle captures the notion of a function applied to itself forever. Consider the difference between the two graph implementations of fix in the definition of ones, such that we have: ones---->@ / \ / \ fix \z (looks a bit funny because of the lambda) | | @ / \ / \ @ z / \ / \ (:) 1 Hopefully you can see that the first version of fix will not produce a cycle, but the second one will.
But:
ones = repeat 1 repeat x = x:repeat x
repeat x = xs where xs = x:xs create a cyclic stucture ?
Consider the difference between: repeat = fix (\z x -> x : z x) and: repeat x = fix (\z -> x : z) Draw both graphs that result from using the cyclic version of fix. You should note that only the second graph ends up with a cycle in the tail of the list. I've intentionally skipped over some details, like how to handle where clauses. Grab a textbook to fill in the details. Note that Haskell does not make any requirements as to how recursion should be implemented. Therefore there is no guarantee how much sharing you will get - it depends on the details of the compiler. However, all the popular compilers seem to implement something akin to the cyclic version of fix. Cheers, Bernie.

So is sharing already implemented in Haskell ? Do i have to use "where" clause to implement the sharing ? Thanks a lot for your help Cheers
To understand cyclic structures it is useful to think of "graph reduction", because these graphs allow us to conveniently represent sharing between objects. Cycles are simply "self-sharing".
_________________________________________________________________ It's fast, it's easy and it's free. Get MSN Messenger 7.0 today! http://messenger.msn.co.uk

Another question, it's said in the book that using cyclic structure (like ones = 1:ones) , the list would be represented by a fixed amount of memory. Does it mean [1,1,1......] only occupy one cell of memory ? How about in " take 100 [1,1,...] " ?
From: "Dinh Tien Tuan Anh"
To: haskell-cafe@haskell.org Subject: Re: [Haskell-cafe] Confused about Cyclic struture Date: Fri, 08 Jul 2005 11:41:02 +0000 So is sharing already implemented in Haskell ?
Do i have to use "where" clause to implement the sharing ?
Thanks a lot for your help Cheers
To understand cyclic structures it is useful to think of "graph reduction", because these graphs allow us to conveniently represent sharing between objects. Cycles are simply "self-sharing".
_________________________________________________________________ It's fast, it's easy and it's free. Get MSN Messenger 7.0 today! http://messenger.msn.co.uk
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_________________________________________________________________ Be the first to hear what's new at MSN - sign up to our free newsletters! http://www.msn.co.uk/newsletters

On Fri, 8 Jul 2005, Dinh Tien Tuan Anh wrote:
Another question, it's said in the book that using cyclic structure (like ones = 1:ones) , the list would be represented by a fixed amount of memory.
Does it mean [1,1,1......] only occupy one cell of memory ? How about in " take 100 [1,1,...] " ?
'take' will certainly ignore the cyclic structure. Even if it could detect the cycle in its argument there is no way to represent the list of 100 elements more efficiently.

Hello Dinh, Friday, July 08, 2005, 9:12:22 PM, you wrote: DTTA> Another question, it's said in the book that using cyclic structure (like DTTA> ones = 1:ones) , the list would be represented by a fixed amount of memory. DTTA> Does it mean [1,1,1......] only occupy one cell of memory ? DTTA> How about in " take 100 [1,1,...] " ? in order to understand how Haskell datastructures uses memory, you must remember that Haskell does LAZY evaluation. it means that any data represented as CLOSURE - pointer to function which upon call will compute this data, or VALUE - computed data itself. LAZY avaluation means that all data computed only when needed - in the time of USING them instead of time of ASSIGNMENT as in all other STRICT languages (Pascal, C++, ML and so on). when the data used FIRST TIME, function stored in its closure is evaluated and computed result replaces pointer to function if computed result is not a plain value (Int/Double/Char), but a complex structure (list, tree and so on) it will be not computed entirely, but only the highest level of this structure. all the references to substructures will be represented by the closures - again. so one function call (CLOSURE) representing all the datastructure after evaluation will be replaced by cell which represents highest level of structure and contains references to closures representing next level and these closures will remain unevaluated until the time they are actually used when you use (consume) data in list, you can do it only sequentially. each evaluated list cell contains two links - to value in this list element and to tail of list (it is the list again). when you consume next list element, closure that represents it is evaluated and replaced by cell containing two abovementioned links. when you define "ones=1:ones" this variable will contain unevaluated closure, which would call function "(:)" with two arguments - "1" and "ones". when you start consuming "ones", this closure will be evaluated and replaced by its result - cell containing links to "1" and to closure representing "ones", i.e. this cell itself! so, subsequent consuming of next list elements will goes thorough this cyclic structure without any additional evaluations "take 100 ones" itself will occupy just one memory cell (of 3 elementary values - link to function and to its 2 arguments) - because it, like anything else, represented as CLOSURE. when you goes to consume this value, you will do it sequentially. let's see at take definition: take 0 xs = [] take n (x:xs) = x : take (n-1) xs when you consume first element of "take 100 ones", this function call will be replaced by "1:take 99 ones", i.e. cell which contain reference to "1" and to closure "take 99 ones". as you see, we can't create cycle here just because "take 99 ones" is not the same as "take 100 ones" :-) more thorough, when we compute "take 100 somelist", matching "somelist" to "x:xs" will DECOMPOSE first element of list. evaluating "x : take (n-1) xs" will COMPOSE new cell which contains links to "x" and unevaluated closure "take (n-1) xs". so, recursive evaluation of "take" will build new list - element-by-element, but this list will contain links to the same elements (represented as closures) as original list. even if you define take 0 xs = xs take n (x:xs) = x : take (n-1) xs so that "take 100 xs" will return just the same list, Haskell on evaluation of "take" will rebuild first 100 elements of list and only after this will share the list remainder (of couse, i don't count for possible smart compiler's optimization) give attention to that while "take" will rebuild structure of list, it will use links to list elements as is. this list can contain complex elements - for example, another lists, but links to this sublists (again represented with evaluated values or unevaluated closures) will be just copied to new list. for example, "take 3 [ones, [1..1000000], map (2*) ones, ones]" will only create 3 new cells which will share pointers to sublists with original list. it is possible because in Haskell data value never changed - it can be only represented as unevaluated or evaluted, so we can share subelements of datastructure without any risk to encounter a side behaviour next, "take 100 ones" will require memory for all 100 elements only when it is fully evaluated. but not all data necessarily goes to this state. for example, this data may be completely ignored in computation, or just a few elements will be evaluated as in "take 3 [1..100]". moreover, evaluated elements of this list may be immediately consumed without creating actual cells, as in "sum [1..100]". on the other side, Haskell compilers try to not re-evaluate datastructures and when your usage of variable don't goes into a "producer-consumer" pattern, evaluated closures are replaced with their values, so on the next use of same variable it will be already evaluated (to degree that was needed for previous usage). run the following program and see at delays between numbers printed: main = do let n = 12345678 let xs = [1, sum [1..n], 1, sum [1..n-1]] print$ sum (take 1 xs) print$ sum (take 2 xs) print$ sum (take 3 xs) print$ sum (take 4 xs) you can also see how many memmory this program require to run - under "GHC -O2" it allocated 2.7 gb in heap but all this memory was immediately reused so maximum memory usage will be only 5 kb so i can say that possibility to create cyclic datastructures in Haskell is basically the same as in C, Pascal or any other language having poiners/references/whatever. the real difference is what you do this not by ASSIGNMENTS but by declaration of structure itself without any problems with referring to structures that will be declared later: let a = 1:b b = 2:c c = 3:a powers_of_2 = 1 : map (2*) powers_of_2 fibonachi = 1 : 1 : zipWith (+) fibonachi (tail fibonachi) sharing of parts of datastructures are also possible (and easy) in imperative languages. but SAFE sharing is possible only in Haskell just because datastructures never change their values, so we never need to copy datastructure just to give the same value to another variable. as a result, it is widely used in function definitions and even in compiler optimisations hope this will help :) -- Best regards, Bulat mailto:bulatz@HotPOP.com

Hi, im using Hugs 98 and learing how to use interactive Haskell. As read in the book: capitalise :: [Char] -> [Char] capitalise = takeWhile(/='.') . map toUpper interact capitalise its said the program is FULLY INTERACTIVE, i.e: as soon as 'h' typed on the keyboard, an 'H' appears on the screen. But the program above always waits untill ENTER was hit to display the result Is this normal ? Is the book right ? I thought if the list was evaluated lazily, then it should be fully interactive. Cheers. _________________________________________________________________ Be the first to hear what's new at MSN - sign up to our free newsletters! http://www.msn.co.uk/newsletters

On Mon, 11 Jul 2005, Dinh Tien Tuan Anh wrote:
Hi, im using Hugs 98 and learing how to use interactive Haskell. As read in the book:
capitalise :: [Char] -> [Char] capitalise = takeWhile(/='.') . map toUpper
interact capitalise
its said the program is FULLY INTERACTIVE, i.e: as soon as 'h' typed on the keyboard, an 'H' appears on the screen. But the program above always waits untill ENTER was hit to display the result
Is this normal ? Is the book right ?
Yes, it is certainly not Hugs which prevents from realtime interaction but it is the terminal you are using. If the terminal lets you delete the characters on the current line it has to keep them until you complete it with ENTER. Piping from and to other programs or files may not have this problem.

You're right, i've been using shell in Emacs to run Hugs, but when back to normal terminal, it works. Just for curiousity, why does it happen ? Thank you very much Cheers
Yes, it is certainly not Hugs which prevents from realtime interaction but it is the terminal you are using. If the terminal lets you delete the characters on the current line it has to keep them until you complete it with ENTER. Piping from and to other programs or files may not have this problem.
_________________________________________________________________ Use MSN Messenger to send music and pics to your friends http://messenger.msn.co.uk

could anyone tell me what i did wrong with this please sumHam :: Integer -> Float sumHam n = sum [1/x | x<-[1..n]] Error: type error in explicitly typed binding **** Term: sumHam **** Type: Integer -> Integer **** Does not match : Integer -> Float it only works if i remove the first line. Tried changing Float by Double and still not working Pls help Cheers _________________________________________________________________ Be the first to hear what's new at MSN - sign up to our free newsletters! http://www.msn.co.uk/newsletters

Thanks for your reply, i just simply removed the first line and it works, but i dont understand why 1/x is not Float.
Try this:
sumHam :: Integer -> Float sumHam n = sum [1.0/(fromIntegral x) | x<-[-1..n]]
-- Andy
_________________________________________________________________ Use MSN Messenger to send music and pics to your friends http://messenger.msn.co.uk

Thanks for your reply, i just simply removed the first line and it works, but i dont understand why 1/x is not Float.
It depends on the type of 'x'. If 'x' is a Float, (1/x) will be a Float. If 'x' is a Double, (1/x) will be a Double. If 'x' is an Integer (1/x) will not typecheck because (/) is only defined for Fractional arguments, and Integer is not an element of Fractional. In your case, you had constrained 'x' to be an Integer, so it requires a cast to perform the division and get a Float. Removing the type signature allows the compiler to assign a more general type to 'x', and so it typechecks.

You are trying to divide by an Integer and get a Float. Haskell doesn't do automatic numeric conversion, so you have to do the casts manually. Prelude> let sumHam n = sum [ 1 / (fromIntegral x) | x <- [1..n] ] Prelude> sumHam 5 2.283333333333333 Dinh Tien Tuan Anh wrote:
could anyone tell me what i did wrong with this please
sumHam :: Integer -> Float sumHam n = sum [1/x | x<-[1..n]]
Error: type error in explicitly typed binding **** Term: sumHam **** Type: Integer -> Integer **** Does not match : Integer -> Float
it only works if i remove the first line. Tried changing Float by Double and still not working
Pls help Cheers
_________________________________________________________________ Be the first to hear what's new at MSN - sign up to our free newsletters! http://www.msn.co.uk/newsletters
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

i have just encountered another type error. This program tries to print out partitions of a positive integer (i guess) parts 0 = [[]] parts x = [concat (map (y:) parts(x-y) | y<-[1..(x `div` 2)]] and got this error: **** Expression : map (y:) parts(x-y) **** Term : map **** Type : (e->f) -> [e] -> [f] **** Does not match : a -> b -> c -> d why do i have this error ? How to fix it ? Thanks a lot _________________________________________________________________ It's fast, it's easy and it's free. Get MSN Messenger 7.0 today! http://messenger.msn.co.uk

On 2005-07-12 at 12:39-0000 "Dinh Tien Tuan Anh" wrote:
i have just encountered another type error. This program tries to print out partitions of a positive integer (i guess)
parts 0 = [[]] parts x = [concat (map (y:) parts(x-y) | y<-[1..(x `div` 2)]]
^ suspicious spacing! That's the same as
parts x = [concat (map (y:) parts (x-y) | y<-[1..(x `div` 2)]]
ie you are giving map three arguments when it expects two, which is what the type error says. -- Jón Fairbairn Jon.Fairbairn at cl.cam.ac.uk

oh damn, thank you
From: Jon Fairbairn
To: "Dinh Tien Tuan Anh" CC: robdockins@fastmail.fm, haskell-cafe@haskell.org Subject: Re: [Haskell-cafe] Can't explain this error Date: Tue, 12 Jul 2005 14:08:00 +0100 On 2005-07-12 at 12:39-0000 "Dinh Tien Tuan Anh" wrote:
i have just encountered another type error. This program tries to print out partitions of a positive integer (i
guess)
parts 0 = [[]] parts x = [concat (map (y:) parts(x-y) | y<-[1..(x `div` 2)]]
^
suspicious spacing! That's the same as
parts x = [concat (map (y:) parts (x-y) | y<-[1..(x `div` 2)]]
ie you are giving map three arguments when it expects two, which is what the type error says.
-- Jón Fairbairn Jon.Fairbairn at cl.cam.ac.uk
_________________________________________________________________ Winks & nudges are here - download MSN Messenger 7.0 today! http://messenger.msn.co.uk

On 12 Jul 2005, at 14:39, Dinh Tien Tuan Anh wrote:
parts 0 = [[]] parts x = [concat (map (y:) parts(x-y) | y<-[1..(x `div` 2)]]
First of all ... there is a ) missing ... I guess the line should read parts x = [concat (map (y:) parts(x-y) ) | y<-[1..(x `div` 2)]] ? -- Andy

Dinh Tien Tuan Anh wrote:
Yes, it is certainly not Hugs which prevents from realtime interaction but it is the terminal you are using. If the terminal lets you delete the characters on the current line it has to keep them until you complete it with ENTER. Piping from and to other programs or files may not have this problem.
You're right, i've been using shell in Emacs to run Hugs, but when back to normal terminal, it works.
Just for curiousity, why does it happen ?
Emacs' shell-mode doesn't send anything to the terminal driver until
you hit Return, at which point it sends the whole line.
Note that the terminal driver itself normally does line-buffering,
although this is disabled if you set the buffering for stdin to
NoBuffering.
You can't disable the line-buffering inherent in Emacs' shell-mode;
you would have to use terminal-emulator instead ("M-x term" instead of
"M-x shell").
--
Glynn Clements

On Sat, 2005-07-09 at 13:12 +0400, Bulat Ziganshin wrote:
Hello Dinh,
Friday, July 08, 2005, 9:12:22 PM, you wrote:
DTTA> Another question, it's said in the book that using cyclic structure (like DTTA> ones = 1:ones) , the list would be represented by a fixed amount of memory.
DTTA> Does it mean [1,1,1......] only occupy one cell of memory ? DTTA> How about in " take 100 [1,1,...] " ?
in order to understand how Haskell datastructures uses memory, you must remember that Haskell does LAZY evaluation.
Hi, I'll be a little bit pedantic here. Haskell, the language definition, does not prescribe lazy evaluation. It says that the language is non-strict. Lazy evaluation is an implementation technique which satisfies non-strict semantics, but it is not the only technique which does this. As it happens, GHC, Hugs and nhc98 all employ lazy evaluation. Note that they may still vary in subtle ways as to the precise details of evaluation order, due to program transformations that may be applied to the program during compilation. As I said in my previous mail, the degree of sharing you get within Haskell data structures is not defined in the language, it is defined (perhaps loosely) by the implementation technique. Cheers, Bernie.

Bernard Pope wrote:
I'll be a little bit pedantic here. Haskell, the language definition, does not prescribe lazy evaluation. It says that the language is non-strict. Lazy evaluation is an implementation technique which satisfies non-strict semantics, but it is not the only technique which does this.
This pedantry is renewed periodically. It is a pity that nobody ever writes anything about that other methods of implementation of non-strictness, nor about the languages which use those methods. I believe it might do some good to people who learn functional programming in general, and Haskell in particular. Any takers? Jerzy Karczmarczuk
participants (10)
-
Andy Georges
-
Bernard Pope
-
Bulat Ziganshin
-
Dinh Tien Tuan Anh
-
Glynn Clements
-
Henning Thielemann
-
Jerzy Karczmarczuk
-
Jon Fairbairn
-
Marc A. Ziegert
-
robert dockins