
I have been working on a little Java project lately at work, by way of an introduction to the language, and naturally I often have cause to regret that it isn't Haskell instead. But in the specific matter I'm wrestling with, the Java library's OOP model is, to its credit, allowing me to do some things. I'm using their standard LDAP client library, but swapping in my own function to read X509 certificates for the SSL. Actually, swapping in my own SSL socket "implementation", which in my case just calls the standard library SSL socket implementation to do most of the work. Now it's not like I can't imagine it working better - it may be a little fragile, for one thing - but I have wondered what facilities a Haskell design could have drawn on to de-couple implementation components like that. Let's say you download an IMAP mail client library, and look to see if it can operate on a UNIX pipe; on an SSL socket; authenticate with GSSAPI Kerberos 5 -- when none of those things are supported out of the box. (As I have needed, and done, all three of those with the standard Python IMAP library module.) You may also want its I/O operations to integrate with some dispatching core, for a GUI. But of course you also want the basic interface to be simple in this area - the IMAP protocol itself is complicated enough! So I'm the one user in a thousand that will want to provide my own I/O functions, for example. In the old world, I guess I would be looking for some extended API where my I/O functions are parameters to the "open" or "init" function, and the IMAP functions take over from there. In a more pure functional oriented model, could it be an extended API that exposes the IMAP functionality as operations on data, and leaves it to me to deal with the I/O? Donn Cave, donn@drizzle.com

On 7 Nov 2007, at 11:26 AM, Donn Cave wrote:
I have been working on a little Java project lately at work, by way of an introduction to the language, and naturally I often have cause to regret that it isn't Haskell instead.
But in the specific matter I'm wrestling with, the Java library's OOP model is, to its credit, allowing me to do some things. I'm using their standard LDAP client library, but swapping in my own function to read X509 certificates for the SSL. Actually, swapping in my own SSL socket "implementation", which in my case just calls the standard library SSL socket implementation to do most of the work.
Now it's not like I can't imagine it working better - it may be a little fragile, for one thing - but I have wondered what facilities a Haskell design could have drawn on to de-couple implementation components like that. Let's say you download an IMAP mail client library, and look to see if it can operate on a UNIX pipe; on an SSL socket; authenticate with GSSAPI Kerberos 5 -- when none of those things are supported out of the box. (As I have needed, and done, all three of those with the standard Python IMAP library module.) You may also want its I/O operations to integrate with some dispatching core, for a GUI. But of course you also want the basic interface to be simple in this area - the IMAP protocol itself is complicated enough!
So I'm the one user in a thousand that will want to provide my own I/O functions, for example. In the old world, I guess I would be looking for some extended API where my I/O functions are parameters to the "open" or "init" function, and the IMAP functions take over from there. In a more pure functional oriented model, could it be an extended API that exposes the IMAP functionality as operations on data, and leaves it to me to deal with the I/O?
That would be my ideal: protocol layers implemented as functions over lazy lists. Naturally, those compose very cleanly (at least in a pipeline-like fashion. Combining that with running protocol modules in serial (e.g., using some standard initial authentication protocol, then switching to something else) is a bit more complicated (but certainly very doable)). jcc

So I'm the one user in a thousand that will want to provide my own I/O functions, for example. In the old world, I guess I would be looking for some extended API where my I/O functions are parameters to the "open" or "init" function, and the IMAP functions take over from there. In a more pure functional oriented model, could it be an extended API that exposes the IMAP functionality as operations on data, and leaves it to me to deal with the I/O?
I believe a typeclass could solve this for you. The typeclass member functions serve as your interface definition. For example, say "auth" was a member function. Then you could implement instances which authorized using NTLM, HTTP Basic, etc. It's similar to how you'd do the same thing in java with interfaces, in fact. Justin

On Wed, 7 Nov 2007, Justin Bailey wrote:
So I'm the one user in a thousand that will want to provide my own I/O functions, for example. In the old world, I guess I would be looking for some extended API where my I/O functions are parameters to the "open" or "init" function, and the IMAP functions take over from there. In a more pure functional oriented model, could it be an extended API that exposes the IMAP functionality as operations on data, and leaves it to me to deal with the I/O?
I believe a typeclass could solve this for you. The typeclass member functions serve as your interface definition. For example, say "auth" was a member function. Then you could implement instances which authorized using NTLM, HTTP Basic, etc.
It's similar to how you'd do the same thing in java with interfaces, in fact.
That auth function is not a bad example, because there are a number of cross dependencies along the way to authentication. When you try to design a generic API that will supports all kinds of authentication, you end up with some abominable tangle like SASL, and even then you end up punting on some of them (where does your SSL certificate go?) Some of the underlying protocols involve more than one round trip (Kerberos), others need access to the SSL state, etc. What I'm running up the flagpole here, so to speak, is the notion that if at a larger scale you write your application protocol engine so that it just operates on data and doesn't need to take control over "the wire", that might give you a thinner API, and fewer problems to solve via typeclass. Donn Cave, donn@drizzle.com

Donn Cave wrote:
But in the specific matter I'm wrestling with, the Java library's OOP model is, to its credit, allowing me to do some things. I'm using their standard LDAP client library, but swapping in my own function to read X509 certificates for the SSL. Actually, swapping in my own SSL socket "implementation", which in my case just calls the standard library SSL socket implementation to do most of the work.
Now it's not like I can't imagine it working better - it may be a little fragile, for one thing - but I have wondered what facilities a Haskell design could have drawn on to de-couple implementation components like that. Let's say you download an IMAP mail client library, and look to see if it can operate on a UNIX pipe; on an SSL socket; authenticate with GSSAPI Kerberos 5 -- when none of those things are supported out of the box. (As I have needed, and done, all three of those with the standard Python IMAP library module.) You may also want its I/O operations to integrate with some dispatching core, for a GUI. But of course you also want the basic interface to be simple in this area - the IMAP protocol itself is complicated enough!
I have similar questions about Haskell abstracting away implementations behind interfaces as well. I have become used to an approach where I will not worry about databases/persistence when beginning. I will create an interface to a database layer (e.g., save(object), retrieve(id), findByName(name)) etc., and an implementation that uses in memory collections to begin with. Later I will replace this with database calls. This also helps in my current project as we support multiple databases. If findByName requires different SQL on different databases it's easy to have a different implementation used at run time. How does this type of approach work in Haskell? or what is the Haskell way to achieve this? Levi

levi.stephen wrote:
I have similar questions about Haskell abstracting away implementations behind interfaces as well. I have become used to an approach where I will not worry about databases/persistence when beginning. I will create an interface to a database layer (e.g., save(object), retrieve(id), findByName(name)) etc., and an implementation that uses in memory collections to begin with. Later I will replace this with database calls.
How does this type of approach work in Haskell? or what is the Haskell way to achieve this?
If OO is a good approach for a problem, it's straightforward to model it in haskell. If you plan to access an external DB in any case, then the interface will involve the IO Monad. Something along the lines of: data Object data ID data ObjectStore = ObjectStore { save :: Object -> IO ID, retrieve :: IO -> IO (Maybe Object), retrieveByName :: String -> IO (Maybe Object) } createMemoryStore :: IO ObjectStore connnectExternalStore :: ConnectionParams -> IO ObjectStore Tim

Tim Docker wrote:
levi.stephen wrote:
I have similar questions about Haskell abstracting away implementations behind interfaces as well. I have become used to an approach where I will not worry about databases/persistence when beginning. I will create an interface to a database layer (e.g., save(object), retrieve(id), findByName(name)) etc., and an implementation that uses in memory collections to begin with. Later I will replace this with database calls.
How does this type of approach work in Haskell? or what is the Haskell way to achieve this?
If OO is a good approach for a problem, it's straightforward to model it in haskell. If you plan to access an external DB in any case, then the interface will involve the IO Monad. Something along the lines of:
data Object data ID
data ObjectStore = ObjectStore { save :: Object -> IO ID, retrieve :: IO -> IO (Maybe Object), retrieveByName :: String -> IO (Maybe Object) }
createMemoryStore :: IO ObjectStore connnectExternalStore :: ConnectionParams -> IO ObjectStore
Tim
Thanks for the example. I keep forgetting that I can have use functions like this. I keep having data types made up of just values and/or type classes. I should probably use types like the above more often. My concern (which may be inexperience ;) ) is with the monads here though. What if I hadn't seen that the IO monad (or any other Monad) was going to be necessary in the type signatures? Levi

levi.stephen wrote:
My concern (which may be inexperience ;) ) is with the monads here though. What if I hadn't seen that the IO monad (or any other Monad) was going to be necessary in the type signatures?
You'd have some refactoring to do :-) But actually, it's not possible to create an interface that works this way without using some monad, as the interface relies on side-effects. A pure interface would have to look something like: data ObjectStore = ObjectStore { save :: Object -> (ID,ObjectStore), retrieve :: ID -> Maybe Object, retrieveByName :: Maybe Object } (ie the save method would have to return a new object store). Instead of using IO, you could have parameterised the store over the monad: data ObjectStore m = ObjectStore { save :: Object -> m ID, retrieve :: ID -> m (Maybe Object), retrieveByName :: String -> m (Maybe Object) } but given your planned use, this may well be over-abstraction. Tim

On Thu, 2007-11-08 at 13:21 +1100, Tim Docker wrote:
levi.stephen wrote:
My concern (which may be inexperience ;) ) is with the monads here though. What if I hadn't seen that the IO monad (or any other Monad) was going to be necessary in the type signatures?
You'd have some refactoring to do :-)
http://www.cs.kent.ac.uk/projects/refactor-fp/catalogue/Monadification1.html

Tim Docker wrote:
levi.stephen wrote:
My concern (which may be inexperience ;) ) is with the monads here though. What if I hadn't seen that the IO monad (or any other Monad) was going to be necessary in the type signatures?
You'd have some refactoring to do :-) But actually, it's not possible to create an interface that works this way without using some monad, as the interface relies on side-effects. A pure interface would have to look something like:
I agree in this case the monad use is clear. Practically it might a case of if a monad is needed, it's either obvious, or its introduction indicates a refactor being a good thing and will lead to a better design. Levi

Don't shoot me... The last exchange with Andrew Bromage made me recall a homework which was given to some students by a particularly nasty teacher I happen to know. The question is to generate the whole infinite Rabbit Sequence in one shot (co-recursive, selbstverständlich). The Rabbit Sequence: 1,0,1,1,0,1,0,1,1,0,1,1,0,1,0,1,1,0,1,0,1,1,0,1,1,0,1,0,1,1,0,1,1,0,... may be obtained in two ways. A. 1. Begin with one *young* rabbit: 0. 2. In one unit of time a young rabbit grows, becomes *old*: 1. 3. In one unit of time an old rabbit has an offspring, transmutes into [1,0] (Yes, the rewriting order is meaningful). The evelution continues... So, after three units we have: 1 0 1. After four: 10110. Then 10110101. Etc. B. The n-th instance fulfils the recurrence rs 0 = [0] rs 1 = [1] rs n = rs (n-1) ++ rs (n-2) === That's it, you see now what is the relation between the Rabbit Sequence and Fibonacci. This nasty acquaintance of mine asked the students to write down a simple procedure which generates the sequence after the infinite number of units of time. Of course, any finite prefix of it. The pedagogical result was a disaster. Some students began to work, but then the teacher went crazy and demanded the solution (in Haskell) as a one-liner. Just one line, and standard Prelude functions, nothing more. So, the students thought that if it is a one liner, it must be stupid, and abandoned this exercise. Would somebody try to solve it, before I unveil the solution? It isn't difficult. Jerzy Karczmarczuk

How about this, infiniteRS :: [Int] infiniteRS = let acum a1 a2 = a2 ++ acum (a1++a2) a1 in 1 : acum [1] [0] it certainly fits in one line but it's not really elegant

You can make it pretty short too, if you allow yourself fix: rs=1:fix(\f p n->n++f(p++n)p)[1][0] I came up with this on the train home, but then I realised it was the same as your solution :) On 08/11/2007, at 12:57 PM, Alfonso Acosta wrote:
How about this,
infiniteRS :: [Int] infiniteRS = let acum a1 a2 = a2 ++ acum (a1++a2) a1 in 1 : acum [1] [0]
it certainly fits in one line but it's not really elegant _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Report from the Rabbit Warren. Thank you, everybody, for your contribution. The problem was, how to construct a one-liner which generates the infinite Rabbit Sequence: 10110101101101011010110110101101101011010110110101101011011010110... This is the result of an *infinite time* evolution of a system which iteratively rewrites one young rabbit: 0 -> 1, an old one, and one old: 1 -> 10: itself and a young offspring. The finite sequence after n units of time fulfils: rs n = rs (n-1) ++ rs (n-2). For people beginning to learn Haskell, and having *some* acquaintance with infinite streams and co-recursive algorithms, this may be a bit frustrating, because of the "left recursivity", which makes it difficult to "anchor" the recurrence. But here we have seen plenty of specialists. The solution which used the evolution/rewriting operator, needed \x->if x==0 then [1] else [1,0]) simplified by Andrew Bromage to: \x->1:[0|x==1] . Very cute! I will substitute it from now on. There were two solutions based on it. Ross Paterson: rs_rp = let rs = 0 : [x|r<-rs, x <- 1:[0|r==1]] in 1:rs Andrew Bromage: rs_ab = zipWith(!!)(fix(([1]:).map(>>= \x->1:[0|x==1])))[0..] This one cheats a bit, fix doesn't belong to the standard, but, well writing fix f = f (fix f) won't kill anybody. But the complexity of this algorithm is bad, it seems the slowest one among contributed. Seems, making an infinite list of infinite lists, and then selecting the members makes the algorithm quadratic. Still, both seem to notice one nice property of the Rabbit Sequence. If you take any such system: a sequence of symbols, which evolves through some rewriting, where one symbol may be mapped to many (so the sequence grows), in general there is no limiting form, you get chaos. Not here! Rabbits are decent fellows (some Australians may disagree) and the infinite, ultimate sequence *is a fixed point* of its evolution operator. This was my solution: rs_jk = 1:rq where _:rq = concat (map (\x->1:[0|x==1]) rs_jk) This is a bit similar to RP. Those who know the List Monad may try to squeeze the concat . map into something using >>=, if they wish. Mirko Rahn exploited concatMap (I didn't, since when the exercise was proposed, students didn't know it existed): rs_mr = limit [[1],[1,0]] [1] where limit h w = l where l = f w ++ f (tail l) f = concatMap ((!!) h) The nice point here is that the same limit function can be used to generate the sequence of Thue-Morse, which as every patriotic French child knows, has been invented by P. Prouhet, in 1859...; also some other sequences may come out of it. But it is not a one-liner, what an unforgivable shame! (BTW, Thue wrote his papers in Norwegian only, so patriots from Norway might disagree with French historians.) We see here another cute way of representing the basic rewriting function! Notice that ((!!) [[1],[1,0]]) is a function which converts 0->1, 1->10. A bit exotic, though... So, we can easily squeeze the M.R. solution into a specific form rs_m1 = f [1] ++ f (tail rs_m1) where f = concatMap (\x->1:[0|x==1]) or simply: rs_m1 = [1,0] ++ concatMap (\x->1:[0|x==1]) (tail rs_m1) This is *almost* identical to my solution. I have a vague impression that the solution of Alfonso Acosta: rs_aa = let acum a1 a2 = a2 ++ acum (a1++a2) a1 in 1 : acum [1] [0] is also somehow related to this limit stuff, although it is simpler, and formulated differently. A few minutes ago I read Bernie Pope, who used fix in a similar context, and concluded that he got the solution of Alfonso Acosta. Finally, Bernie Pope original: mrs = [0] : [1] : zipWith (++) (tail mrs) mrs rs_bp = [(mrs !! n) !! (n-1) | n <- [1..]] produced something which also begins with a list of lists. It seems that it is faster than the solution of A.B., but I have also the impression that it generates a lot of temporary rubbish: the printing of a long sequence periodically stops as if GC sneaked in. Finally, Stuart Cook: fibs' = 1 : 2 : zipWith (+) fibs' (tail fibs') rs_sc = 1 : 0 : (fibs' >>= flip take rs_sc) is a nice way (but in TWO lines, scandalous...) of co-recurring through this fixed-point, not element by element, but with chunks whose size increase as the Fibonacci numbers do. Thank you once more! Jerzy Karczmarczuk

On Thu, 8 Nov 2007 jerzy.karczmarczuk@info.unicaen.fr wrote:
Report from the Rabbit Warren.
Thank you, everybody, for your contribution. The problem was, how to construct a one-liner which generates the infinite Rabbit Sequence: 10110101101101011010110110101101101011010110110101101011011010110... This is the result of an *infinite time* evolution of a system which iteratively rewrites one young rabbit: 0 -> 1, an old one, and one old: 1 -> 10: itself and a young offspring. The finite sequence after n units of time fulfils: rs n = rs (n-1) ++ rs (n-2).
And now we have much Haskell code for one sequence to be submitted to the Online Encyclopedia of Integer Sequences!

Henning Thielemann writes:
And now we have much Haskell code for one sequence to be submitted to the Online Encyclopedia of Integer Sequences!
Is there anything really there in Haskell?... Well, if you are interested in something more "venerable" than rabbits, why not try the sequence which gives the number of rooted trees: T_n = 0,1,1,2,4,9,20,48,115,286,719,1842,4766,12486,32973,87811,... Such combinatorial coefficients are sometimes useful in practice. (Even in theoretical physics...) Their generating function T(x) = Sum_{n >= 1} T_n*x^n fulfils the Polya relation: T(x) = x*exp(T(x) + T(x^2)/2 + T(x^3)/3 + T(x^4)/4+...+ T(x^m)/m + ...) from which you see clearly that you don't see anything clearly. For T_n there is a recurrence: T_(n+1) = (1/n) * sum_{k=1..n} ( sum_{d|k} d*T_(d) ) * T_(n-k+1). (where d|k means the sum over the divisors of k) whose advantage is that is really so awfully ugly, that it looks professional... And it seems that the formulae in Maple, etc., on the page of Sloane, are based essentially on that. == I tried to code the stuff *directly* from the Polya identity. I'll give the solution below, but, perhaps, try yourself? It is not a one-liner, though, and uses a small package for formal series manipulation. Recall that if a series u_0 + u_1*x + u_2*x^2 + ... is represented by a list [u_0, u_1,...], then the sum and the difference are just zipWith (+/-). The multiplication is: (u0:uq)*v@(v0:vq) = u0*v0 : u0*>vq + v*uq and the division: (u0:uq) / v@(v0:vq) = let w0 = u0/v0 in w0:(uq - w0*>vq)/v where (*>) = map . (*), multiplies a series by a scalar. Now, we have here an exponential, so it seems that a Floating instance of the series is necessary. However, in order to prevent some people from pointing out that this would break down, let's define a *restricted* exponential, exp0(s) for s such that s_0=0. Then, if s is rational, the exponential will also be rational. We shall use the ideology described well in Knuth. If w=exp(s), then w' = w*s', and w = (exp s_0) + INTEG w*s' which is a co-recursive relation for w. In Haskell: intgs = nt 1 where nt n = n : nt (n+1) sDif (_:sq) = zipWith (*) sq intgs -- differentiation of a series sInt c s = c : zipWith (/) s intgs -- integration, with the int. constant Don't ask me why not [1 ..]. This forces an instance of Enum, I don't want to hear about. Now, the series exponential: exp0 u@(0:_) = w where w = sInt 1 (sDif u * w) -- otherwise it fails. and finally, the Polya formula. Notice the following: a. The T(x) starts with x*..., so the zeroth coeff is zero. The restricted exponential should work. b. T(x^k) puts some zeros between the elements of T(x), that's all. This is done by the function (\x->x : replicate...) below. c. The infinite sum of T(x^m)/m is *co-recursively doable!!* So, finally, tau = 0 : psi where psi = exp0(foldr1 (\x s->0:x+s) -- this (+) is for series. (map (\m->(1/fromInteger m)*> concatMap (\x->x : replicate (fromInteger(m-1)) 0) psi) intgs)) So, after all, if the auxiliary series functions are considered to be a part of our "standard" environment, we got a one-liner, although the length of this line is substantial. Anybody tries to shorten this? If you don't, I'll put it on my grave stone, but hopefully not yet tomorrow. Jerzy Karczmarczuk

On 11/8/07, jerzy.karczmarczuk@info.unicaen.fr
I have a vague impression that the solution of Alfonso Acosta:
rs_aa = let acum a1 a2 = a2 ++ acum (a1++a2) a1 in 1 : acum [1] [0]
is also somehow related to this limit stuff, although it is simpler, and formulated differently.
I particularly like its similarity to this definition: fibs = let fibs' a1 a2 = a2 : fibs' (a1 + a2) a1 in fibs' 1 0 Stuart

On Thu, Nov 08, 2007 at 12:09:27PM +0100, jerzy.karczmarczuk@info.unicaen.fr wrote:
This was my solution: rs_jk = 1:rq where _:rq = concat (map (\x->1:[0|x==1]) rs_jk) This is a bit similar to RP.
I started with that, but eliminated the tail by substituting and unrolling: _:rq = concat (map (\x->1:[0|x==1]) rs_jk) = concat (map (\x->1:[0|x==1]) (1:rq)) = 1:0:concat (map (\x->1:[0|x==1]) rq)

It's not over yet, the rabbits are still going strong on the fibonacci-side. Jerzy Karczmarczuk wrote:
the solution of Alfonso Acosta:
rs_aa = let acum a1 a2 = a2 ++ acum (a1++a2) a1 in 1 : acum [1] [0]
We can apply the difference list trick to obtain f 0 = (0:) f 1 = (1:) f n = f (n-1) . f (n-2) i.e. rs_aa' = let accum r1 r2 = r2 . accum (r1 . r2) r1 in 1: accum (1:) (0:) undefined
Finally, Bernie Pope original:
mrs = [0] : [1] : zipWith (++) (tail mrs) mrs rs_bp = [(mrs !! n) !! (n-1) | n <- [1..]]
produced something which also begins with a list of lists. It seems that it is faster than the solution of A.B., but I have also the impression that it generates a lot of temporary rubbish: the printing of a long sequence periodically stops as if GC sneaked in.
and mrs' = (0:) : (1:) : zipWith (.) (tail mrs') mrs' To speed up Bernie's infinite list flattening, we note that for every "generalized" fibonacci sequence f n = f (n-1) <+> f (n-2) we have the following telescope "sum" f (n+2) = f 1 <+> f 0 <+> f 1 <+> f 2 <+> ... <+> f n = f 2 <+> f 1 <+> f 2 <+> ... <+> f n = f 3 <+> f 2 <+> ... <+> f n i.e. f (n+2) = f 1 <+> foldr1 (<+>) [f k | k <- [0..n]] This identity allows us to write f ∞ = f 1 <+> foldr1 (<+>) [f k | k <- [0..]] and hence rs_bp' = 1: foldr1 (.) mrs' undefined To close the circle, Alfonso's solution is in fact the deforestation of this one. Regards, apfelmus

On 11/8/07, jerzy.karczmarczuk@info.unicaen.fr
Would somebody try to solve it, before I unveil the solution? It isn't difficult.
*** SPOILER WARNING *** Here's my attempt, which I wrote without peeking: let fibs' = 1 : 2 : zipWith (+) fibs' (tail fibs') rabbits = 1 : 0 : (fibs' >>= flip take rabbits) It can be golfed down to a single line without difficulty. Is there a nicer solution? Stuart

G'day all. Quoting jerzy.karczmarczuk@info.unicaen.fr:
This nasty acquaintance of mine asked the students to write down a simple procedure which generates the sequence after the infinite number of units of time.
Cool problem! "Simple" is, of course, in the eye of the beholder. zipWith (!!) (fix (([1]:).map(>>= \x->if x==0 then [1] else [1,0]))) [0..] Cheers, Andrew Bromage

G'day all. Quoting ajb@spamcop.net:
zipWith (!!) (fix (([1]:).map(>>= \x->if x==0 then [1] else [1,0]))) [0..]
This was the shortest variant I could manage in the time allotted: zipWith(!!)(fix(([1]:).map(>>= \x->1:[0|x==1])))[0..] Cheers, Andrew Bromage

On 08/11/2007, at 10:56 AM, jerzy.karczmarczuk@info.unicaen.fr wrote:
rs 0 = [0] rs 1 = [1] rs n = rs (n-1) ++ rs (n-2)
Would somebody try to solve it, before I unveil the solution? It isn't difficult.
Jerzy Karczmarczuk
Is this what you are looking for: mrs = [0] : [1] : zipWith (++) (tail mrs) mrs then you can get the one you want with: mrs !! index given a suitable value for index Cheers, Bernie.

Is this what you are looking for:
mrs = [0] : [1] : zipWith (++) (tail mrs) mrs
then you can get the one you want with:
mrs !! index
given a suitable value for index
It seems I didn't read the question carefully - you want the infinite list. You can recover the solution from mrs if you want, but its not very pretty: infrs = [(mrs !! n) !! (n-1) | n <- [1..]]

On Thu, Nov 08, 2007 at 12:56:46AM +0100, jerzy.karczmarczuk@info.unicaen.fr wrote:
This nasty acquaintance of mine asked the students to write down a simple procedure which generates the sequence after the infinite number of units of time. Of course, any finite prefix of it.
rabbit = let rs = 0 : [x | r <- rs, x <- if r==0 then [1] else [1,0]] in 1 : rs

The Rabbit Sequence: 1,0,1,1,0,1,0,1,1,0,1,1,0,1,0,1,1,0,1,0,1,1,0,1,1,0,1,0,1,1,0,1,1,0,...
This nasty acquaintance of mine asked the students to write down a simple procedure which generates the sequence after the infinite number of units of time. Of course, any finite prefix of it.
In terms of limits of morphisms we can simply write limit h w = l where l = f w ++ f (tail l) f = concatMap ((!!) h) rabbit = limit [[1],[1,0]] [1] Some other well known sequences: fibonacci = limit [[0,1],[0]] [0] thue_morse = limit [[0,1],[1,0]] [0] cubic_free = limit [[0,1,2],[0,2],[1]] [0] Of course, we have map (1-) rabbit == fibonacci /BR

On Thu, 2007-11-08 at 00:56 +0100, jerzy.karczmarczuk@info.unicaen.fr wrote:
Don't shoot me...
The last exchange with Andrew Bromage made me recall a homework which was given to some students by a particularly nasty teacher I happen to know.
The question is to generate the whole infinite Rabbit Sequence in one shot (co-recursive, selbstverständlich).
The Rabbit Sequence: 1,0,1,1,0,1,0,1,1,0,1,1,0,1,0,1,1,0,1,0,1,1,0,1,1,0,1,0,1,1,0,1,1,0,... may be obtained in two ways.
A. 1. Begin with one *young* rabbit: 0. 2. In one unit of time a young rabbit grows, becomes *old*: 1. 3. In one unit of time an old rabbit has an offspring, transmutes into [1,0] (Yes, the rewriting order is meaningful).
Don't rabbits ever die? Guess they just become zombie rabbits ... [1] But that still doesn't work, because those would then eat all those other rabbits ... Hm ... [1] .. http://www.ebsqart.com/Artists/cmd_3739_profile_portfolio__3_3_G.htm

Hello Donn, Wednesday, November 7, 2007, 10:26:20 PM, you wrote:
Now it's not like I can't imagine it working better - it may be a little fragile, for one thing - but I have wondered what facilities a Haskell design could have drawn on to de-couple implementation components like that.
:)))) http://haskell.org/haskellwiki/Library/Streams also, in Haskell you don't need to worry about data/functions dilemma. we just give names to some parts of program code - no matter which types they will have -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com
participants (18)
-
ajb@spamcop.net
-
Alfonso Acosta
-
apfelmus
-
Bernie Pope
-
Bulat Ziganshin
-
Derek Elkins
-
Donn Cave
-
Henning Thielemann
-
jerzy.karczmarczuk@info.unicaen.fr
-
Jonathan Cast
-
Justin Bailey
-
Levi Stephen
-
Mirko Rahn
-
Ross Paterson
-
Stuart Cook
-
Thomas Schilling
-
Tim Docker
-
Yitzchak Gale