
Hi Everyone, A few weeks ago, I started learning Haskell (and functional programming) on my own from the wealth if information on the internet. I recently read the paper "Why Functional Programming Matters" [1] and it led me to wonder how to input a lazy list. Suppose I have a function "f" that reads a lazy list, such that "f" only consumes as much of the list as it needs to. Laziness allows me to apply "f" to an infinite list without creating an infinite loop. Now I want to connect the console to "f", such that the list of inputs to "f" comes from the console, one item at a time. To create a specific example, lets suppose I want to read and accumulate the contents of a list, and I want to stop when the sum reaches or exceeds a specified cutoff. I can write this as a function that reads elements from an infinite list:
accumUntilCutoff :: Integer -> [Integer] -> (Integer, [Integer]) accumUntilCutoff cutoff xs = accumHelper cutoff 0 id xs where accumHelper :: {- cutoff -} Integer -> {- sum so far -} Integer -> {- elements so far -} ([Integer] -> [Integer]) -> {- remaining list -} [Integer] -> {- outputs -} (Integer, [Integer]) accumHelper cutoff sum elems [] = (sum, elems []) accumHelper cutoff sum elems (x:xs) = if sum < cutoff then accumHelper cutoff (sum + x) (elems . (x:)) xs else (sum, elems [])
Example: GHCi> accumUntilCutoff 20 [1..] ==> (21,[1,2,3,4,5,6]) GHCi> accumUntilCutoff 20 ([1..6] ++ repeat undefined) ==> (21,[1,2,3,4,5,6]) [This demonstrates that accumUntilCutoff is lazy) Alternatively, I can write a function that (1) prompts the user to enter numbers until the running sum reaches the cutoff, and then (2) returns the results in the IO monad.
readUntilCutoff :: Integer -> IO (Integer, [Integer]) readUntilCutoff cutoff = readHelper cutoff 0 id where readHelper :: {- cutoff -} Integer -> {- sum so far -} Integer -> {- elements so far -} ([Integer] -> [Integer]) -> {- outputs -} IO (Integer, [Integer]) readHelper cutoff sum elems = do if sum < cutoff then do putStr "Enter an integer: " ln <- getLine let x = read ln readHelper cutoff (sum + x) (elems . (x:)) else return $ (sum, elems [])
Example: GHCi> readUntilCutoff 20 Enter an integer: 1 Enter an integer: 2 Enter an integer: 3 Enter an integer: 4 Enter an integer: 5 Enter an integer: 6 ==> (21,[1,2,3,4,5,6]) Here's my puzzle: I am dis-satisfied with the fact that I have to embed IO code in the middle of accumulation code. Is there some way to separate "readUntilCutoff" into two parts (e.g. functions), such that one part would look extremely similar to "accumUntilCutoff", while the other part would handle the user interaction associated with getting the next number? Thank you -- Ron Reference: [1] http://www.cs.chalmers.se/~rjmh/Papers/whyfp.html

On Wed, Jul 11, 2007 at 12:58:34AM -0400, Ronald Guida wrote:
Hi Everyone,
A few weeks ago, I started learning Haskell (and functional programming) on my own from the wealth if information on the internet. I recently read the paper "Why Functional Programming Matters" [1] and it led me to wonder how to input a lazy list.
Suppose I have a function "f" that reads a lazy list, such that "f" only consumes as much of the list as it needs to. Laziness allows me to apply "f" to an infinite list without creating an infinite loop.
Now I want to connect the console to "f", such that the list of inputs to "f" comes from the console, one item at a time.
To create a specific example, lets suppose I want to read and accumulate the contents of a list, and I want to stop when the sum reaches or exceeds a specified cutoff.
I can write this as a function that reads elements from an infinite list:
accumUntilCutoff :: Integer -> [Integer] -> (Integer, [Integer]) accumUntilCutoff cutoff xs = accumHelper cutoff 0 id xs where accumHelper :: {- cutoff -} Integer -> {- sum so far -} Integer -> {- elements so far -} ([Integer] -> [Integer]) -> {- remaining list -} [Integer] -> {- outputs -} (Integer, [Integer]) accumHelper cutoff sum elems [] = (sum, elems []) accumHelper cutoff sum elems (x:xs) = if sum < cutoff then accumHelper cutoff (sum + x) (elems . (x:)) xs else (sum, elems [])
Unrelatedly, a more exerienced Haskeller would probably write this using composition interally: accumUntilCutoff :: (Ord a, Num a) => a -> [a] -> (a, [a]) accumUntilCutoff cutoff xs = findAcceptLast ((>= cutoff) . fst) (zip (scanl (+) 0 xs) (inits xs)) findAcceptLast :: (a -> Bool) -> [a] -> a findAcceptLast pred lst = fromMaybe (last lst) (find pred lst)
Example: GHCi> accumUntilCutoff 20 [1..] ==> (21,[1,2,3,4,5,6]) GHCi> accumUntilCutoff 20 ([1..6] ++ repeat undefined) ==> (21,[1,2,3,4,5,6]) [This demonstrates that accumUntilCutoff is lazy)
Alternatively, I can write a function that (1) prompts the user to enter numbers until the running sum reaches the cutoff, and then (2) returns the results in the IO monad.
readUntilCutoff :: Integer -> IO (Integer, [Integer]) readUntilCutoff cutoff = readHelper cutoff 0 id where readHelper :: {- cutoff -} Integer -> {- sum so far -} Integer -> {- elements so far -} ([Integer] -> [Integer]) -> {- outputs -} IO (Integer, [Integer]) readHelper cutoff sum elems = do if sum < cutoff then do putStr "Enter an integer: " ln <- getLine let x = read ln readHelper cutoff (sum + x) (elems . (x:)) else return $ (sum, elems [])
Example: GHCi> readUntilCutoff 20 Enter an integer: 1 Enter an integer: 2 Enter an integer: 3 Enter an integer: 4 Enter an integer: 5 Enter an integer: 6 ==> (21,[1,2,3,4,5,6])
Here's my puzzle:
I am dis-satisfied with the fact that I have to embed IO code in the middle of accumulation code. Is there some way to separate "readUntilCutoff" into two parts (e.g. functions), such that one part would look extremely similar to "accumUntilCutoff", while the other part would handle the user interaction associated with getting the next number?
Not very nicely. Option 1. Ignore purity This is what Haskell typically does. There is a magic function getContents that returns stdin as a list of characters, lazily, which you can process using ordinary list functions. There is an even more magic function (tecnically not portable, but in the defacto standard libraries) unsafeInterleaveIO, which you can use to make your own magic functions. integersFromStdin :: IO [Integer] integersFromStdin = unsafeInterleaveIO $ do putStr "Enter an integer: " hFlush stdout -- NB: GHCi turns off output buffering in an attempt to be -- friendlier. you need the explicit flush in batch-compiled code. num <- readLn -- handy standard function! rest <- integersFromStdin -- this is magic - unsafeInterleaveIO means that it won't be -- executed until the value is needed return (num : rest) Unfortunately, ignoring purity is fraught with peril. One notable example recently is in HAppS, a Haskell web framework. Alex Jacobson (a haskeller of significant note, not some "clueless newbie") accidentally wrote { length xs > 0 } instead of { not (null xs) } in some parsing code. Which would just be inefficient, normally, but it demanded the whole thing, which as it happened was a lazy stream coming of a socket. Bad data dependencies, bang, deadlock. Option 2. Ignore lists It's possible to describe lists threaded with something else. data ListT m a = m (ListT' m a) data ListT' m a = NilT | ConsT a (ListT m a) You get your safety back ... and lose the standard list functions, list syntax, list comprehensions, list instances, strings-as-lists, et cetera. Stefan

On 7/11/07, Stefan O'Rear
Not very nicely.
Option 1. Ignore purity Option 2. Ignore lists
Option 3. Use continuations You maintein purity while keeping flexibility. One possible implementation:
data Result a = Finished (a, [a]) | NeedInput (a -> Result a)
It's on the NeedInput where we hide the input list. If a for some cutoff and some list there were needed n elements, then there will be (n-1) NeedInput's, one for each except for the first. After the last one, the Result will be Finished.
accumUntilCutoff :: (Ord a, Num a) => a -> a -> Result a accumUntilCutoff = acc (0,[]) where acc (s,p) cutoff x | x >= cutoff = Finished (s+x,reverse $ x:p) | otherwise = NeedInput (acc (s+x,x:p) (cutoff-x))
Note how we explicity "traverse" on the "list".
readUntilCutoff :: (Ord a, Num a, Read a) => a -> IO (a,[a]) readUntilCutoff cutoff = get >>= parse . accumUntilCutoff cutoff where get = putStr "Enter an integer: " >> getLine >>= return . read parse (Finished (s,p)) = return (s,p) parse (NeedInput f) = get >>= parse . f
Probably there's a better way of using continuations, but I think this suffices (and works). Cheers, -- Felipe.

[Ronald Guida, 07/11/07]
Suppose I have a function "f" that reads a lazy list, such that "f" only consumes as much of the list as it needs to. Laziness allows me to apply "f" to an infinite list without creating an infinite loop.
Now I want to connect the console to "f", such that the list of inputs to "f" comes from the console, one item at a time.
How do I do this? [Stefan O'Rear]
Not very nicely.
Apparently, the solution gets ugly. [Stefan O'Rear]
Option 1. Ignore purity [using unsafeInterleaveIO] Option 2. Ignore lists
[Felipe Almeida Lessa]
Option 3. Use continuations
I would like to understand *why* it gets ugly, and I think I figured it out. [Ronald Guida, 07/11/07]
To create a specific example, lets suppose I want to read and accumulate the contents of a list, and I want to stop when the sum reaches or exceeds a specified cutoff.
I can write this as a function that reads elements from an infinite list:
[Snipped: Ronald Guida's newb implementation of accumUntilCutoff]
[Stefan O'Rear, 07/11/07, Improved implementation]
accumUntilCutoff :: (Ord a, Num a) => a -> [a] -> (a, [a]) accumUntilCutoff cutoff xs = findAcceptLast ((>= cutoff) . fst) (zip (scanl (+) 0 xs) (inits xs))
findAcceptLast :: (a -> Bool) -> [a] -> a findAcceptLast pred lst = fromMaybe (last lst) (find pred lst)
First, if I start with an arbitrary pure function, then I can build a dependency graph to determine what to evaluate. Since pure functions are referentially transparent, I am free to evaluate the nodes of my dependency graph in any order, provided that I respect the dependencies. On the one hand, suppose I want to read a list with IO. In order to use IO, or any monad for that matter, I have to pass a "baton"[1] from one operation to the next. If a create a complicated function that involves a monad, then every time I use the "bind" operator, I am adding an edge to my dependency graph. Since I receive a baton from the outside, and I have to return it, I end up threading that baton through my dependency graph. Now when my function is evaluated, the evaluation order, at least for monadic actions, is locked down. On the other hand, I can compare a lazy list function, such as accumUntilCutoff, to a multi-layer perceptron[2]. The input layer of this perceptron receives the contents of a lazy list. List processing functions, such as init, zipWith, and map, construct hidden layers of neurons. For example, "zipWith (+) xs $ tail xs" builds a hidden layer such that each neuron computes the sum of two adjacent inputs. The major contrast between a lazy list function and a multi-layer perceptron is that for some functions, such as filter, takeWhile, dropWhile, and find, I can't build the corresponding neural interconnections until runtime, since these connections depend on the actual *data* that is presented to the inputs. A complicated function, like accumUntilCutoff, is "almost" a multi-layer perceptron, except for the fact that parts of the dependency graph are constructed at runtime based on the input data. This makes it very hard to thread a baton through the dependency graph. So I want to make accumUntilCutoff read its input, lazily, from the console. That means: 1. I need to provide a way to hand the IO baton to accumUntilCutoff and get it back at the end. 2. The baton must be passed, sequentially, to each element of the input list, up to and including the last element that I need. Here is my key observation -- Suppose that: 1. I have two functions f and g that both process a lazy list. 2. I feed the same "lazy list from the console" to both functions. 3. Function f consumes part of the list, and g consumes more than f. 4. I choose to print the result of f, then interact with the user, and later, based on user input, possibly print the result of g. Then: 1. In order to print the result of f, I must pass the baton through f, so the baton will be sequenced through a prefix of my lazy list. 2. In order to determine whether to evaluate g, I must get the baton back from f and use it to interact with the user. 3. If I later need to print the result of g, then I need to pass the baton through g, and the baton must be sequenced *starting in the middle* through my lazy list of user input. As a result, I have to interleave IO operations. Example pseudo-code: 1. main :: IO 2. main = do 3. putStrLn "Hello." 4. xs <- getLazyListOfNumbersFromUser 5. let ys = zipWith (+) xs $ tail xs 6. print (ys !! 0) -- depends on xs !! 0 and 1 7. b <- askUserBool "Would you like to continue? " 8. if b 9. then print (ys !! 1) -- depends on xs !! 1 and 2 10. else return () 11. putStrLn "Goodbye." We *must* ask the user for the first two elements of xs because we have to print the result before asking the user a question. We *can't* ask the user for the third element of xs at this time because the user gets to decide whether we need it. As a result, we must interleave the operation of asking the user for elements of the list "xs" with the operation of asking the user whether to continue.
Now I want to connect the console to "f", such that the list of inputs to "f" comes from the console, one item at a time.
In order to do this, I must either rewrite "f" to pass a baton,
Option 2. Ignore lists Option 3. Use continuations
or else I have to violate purity.
Option 1. Ignore purity [using unsafeInterleaveIO]
In conclusion:
I am dis-satisfied with the fact that I have to embed IO code in the middle of accumulation code.
Then I can either (a) swallow it, (b) use unsafeInterleaveIO, or (c) in the special case that "f" happens to access its input sequentially anyway, rewrite it to pass a baton. ... newb code ...
readUntilCutoff :: Integer -> IO (Integer, [Integer]) readUntilCutoff cutoff = readHelper cutoff 0 id where readHelper :: {- cutoff -} Integer -> {- sum so far -} Integer -> {- elements so far -} ([Integer] -> [Integer]) -> {- outputs -} IO (Integer, [Integer]) readHelper cutoff sum elems = do if sum < cutoff then do putStr "Enter an integer: " ln <- getLine let x = read ln readHelper cutoff (sum + x) (elems . (x:)) else return $ (sum, elems [])
-- Ron References: [1] http://www.haskell.org/haskellwiki/IO_inside#Welcome_to_the_RealWorld.2C_bab... [2] http://en.wikipedia.org/wiki/Artificial_neural_network

On 7/13/07, Ronald Guida
[Ronald Guida, 07/11/07]
Now I want to connect the console to "f", such that the list of inputs to "f" comes from the console, one item at a time. How do I do this?
[Stefan O'Rear]
Not very nicely.
Apparently, the solution gets ugly.
If we have to throw in the towel for a request that is so elementary, surely it means that pure functional programming is broken. Let's not throw in the towel just yet... We just need a bunch of library functions. We hide the ugliness in the library. Rather than post an overlong mail here's some code I threw together last night building on "ListT done right" on the Wiki: http://hpaste.org/1657 The library itself looks ugly but scroll to the end where you see I use 'lifted' versions of foldl, foldlM, filter and takeWhile. It works with ghc, it's easy to use and the input and output are fully interleaved. The IO is almost completely decoupled from the logic. It'd be nice to put together a more complete library that does this kind of stuff. An interesting project might be to try defining a "GeneralisedList" type class of which [] and ListT are both instances so we don't need to distinguish between filter and filterT, say. Then we could make interleaving IO and lists fairly transparent. (And sorry if I'm duplicating what someone else said. The thread is long and I haven't read every word of all of it.) -- Dan

Stefan O'Rear wrote:
Unfortunately, ignoring purity is fraught with peril. One notable example recently is in HAppS, a Haskell web framework. Alex Jacobson (a haskeller of significant note, not some "clueless newbie") accidentally wrote { length xs > 0 } instead of { not (null xs) } in some parsing code. Which would just be inefficient, normally, but it demanded the whole thing, which as it happened was a lazy stream coming of a socket. Bad data dependencies, bang, deadlock.
Ouch! That's gotta sting... I wasn't aware that this function was so leathal. I use it constantly all the time...
Option 2. Ignore lists
It's possible to describe lists threaded with something else.
data ListT m a = m (ListT' m a) data ListT' m a = NilT | ConsT a (ListT m a)
You get your safety back ... and lose the standard list functions, list syntax, list comprehensions, list instances, strings-as-lists, et cetera.
That's... interesting... (I feel yet another "I'm going to have to sit down and think about that one" comming on.)

2007/7/11, Andrew Coppin
Ouch! That's gotta sting...
I wasn't aware that this function was so leathal. I use it constantly all the time...
It isn't that "lethal" usually. It's only because he was using it on an infinite stream that it hurt so much... If you use it on a normal stdin or a hGetContents on a file it will be fine (though you will lose the advantage of its laziness, for example constant memory treatment). -- Jedaï

Chaddaï Fouché wrote:
2007/7/11, Andrew Coppin
: Ouch! That's gotta sting...
I wasn't aware that this function was so leathal. I use it constantly all the time...
It isn't that "lethal" usually. It's only because he was using it on an infinite stream that it hurt so much... If you use it on a normal stdin or a hGetContents on a file it will be fine (though you will lose the advantage of its laziness, for example constant memory treatment).
Loose lazyness? Oh wait - you mean the inadvertent length thing? We already have null, but how about a standard function in Data.List for testing whether the length is longer than some upper limit? lengthUpTo :: Int -> [x] -> Int lengthUpTo n = length . take n shorterThan :: Int -> Bool shorterThan n = (n >) . lengthUpTo (n+1) longerThan :: Int -> Bool longerThan n = (n <) . lengthUpTo n lengthEquals :: Int -> Bool lengthEquals n = (n ==) . lengthUpTo (n+1) (Perhaps need better names...)

There is already many thing in standard library. The balance is important. You can write : longerThan n = (> n) . length . take (n+1) and it isn't so current a need that you want it into a library that already has many functions. -- Jedaï

On Wednesday 11 July 2007, Chaddaï Fouché wrote:
There is already many thing in standard library. The balance is important. You can write : longerThan n = (> n) . length . take (n+1) and it isn't so current a need that you want it into a library that already has many functions.
Shorter: longerThan n = not . null . drop n Jonathan Cast http://sourceforge.net/projects/fid-core http://sourceforge.net/projects/fid-emacs

Chaddaï Fouché wrote:
There is already many thing in standard library. The balance is important.
I agree. The question is whether we mind lots of people reimplementing this themselves, each using their own different name for it. I believe I read about some plan to add a trivial function named "on" to one of the standard libraries, because having it there makes code more readable. So the question becomes "does putting this thing in the library make people's code clearer, or is the function trivial enough to reimplement that one can readily see what it's for?" I'd prefer it in the library (probably Data.List), but it's no biggie.

On Wed, Jul 11, 2007 at 09:54:10PM +0100, Andrew Coppin wrote:
Chaddaï Fouché wrote:
There is already many thing in standard library. The balance is important.
I agree.
The question is whether we mind lots of people reimplementing this themselves, each using their own different name for it. I believe I read about some plan to add a trivial function named "on" to one of the standard libraries, because having it there makes code more readable. So the question becomes "does putting this thing in the library make people's code clearer, or is the function trivial enough to reimplement that one can readily see what it's for?"
I'd prefer it in the library (probably Data.List), but it's no biggie.
Interestingly, the function is already there; it's called genericLength. However, the lazy natural type isn't. Stefan

2007/7/11, Stefan O'Rear
Interestingly, the function is already there; it's called genericLength.
However, the lazy natural type isn't.
I'm not sure what you mean there : genericLength is just a length that can return any Num (eg. an Integer) and not just Int, it has nothing to do with what Andrew wanted, which was a function that checked if a list was longer than n without swallowing more of the list than necessary. Is there something I misunderstood in the exchange ? -- Jedaï

On Wednesday 11 July 2007, Chaddaï Fouché wrote:
2007/7/11, Stefan O'Rear
: Interestingly, the function is already there; it's called genericLength.
However, the lazy natural type isn't.
I'm not sure what you mean there : genericLength is just a length that can return any Num (eg. an Integer) and not just Int, it has nothing to do with what Andrew wanted, which was a function that checked if a list was longer than n without swallowing more of the list than necessary. Is there something I misunderstood in the exchange ?
Yeah. The reference to the "lazy natural type", which is: data Nat = Zero | Succ Nat deriving (Eq, Ord, Read, Show) instance Num Nat where fromInteger 0 = Zero fromInteger (n + 1) = Succ (fromInteger n) etc. then genericLength xn > n does exactly what Andrew wants, when n :: Nat. Jonathan Cast http://sourceforge.net/projects/fid-core http://sourceforge.net/projects/fid-emacs

Jonathan Cast wrote:
On Wednesday 11 July 2007, Chaddaï Fouché wrote:
Is there something I misunderstood in the exchange ?
Yeah. The reference to the "lazy natural type", which is:
data Nat = Zero | Succ Nat deriving (Eq, Ord, Read, Show)
instance Num Nat where fromInteger 0 = Zero fromInteger (n + 1) = Succ (fromInteger n) etc.
then genericLength xn > n does exactly what Andrew wants, when n :: Nat.
Wow. Show me a simple problem, and some Haskeller somewhere will find a completely unexpected way to solve it... LOL! OTOH, doesn't that just mean that Nat is itself a degenerate list, and genericList is just converting one list to another, and the Ord instance for Nat is doing the short-cut stuff?

On Thursday 12 July 2007, Andrew Coppin wrote:
Jonathan Cast wrote:
On Wednesday 11 July 2007, Chaddaï Fouché wrote:
Is there something I misunderstood in the exchange ?
Yeah. The reference to the "lazy natural type", which is:
data Nat = Zero
| Succ Nat
deriving (Eq, Ord, Read, Show)
instance Num Nat where fromInteger 0 = Zero fromInteger (n + 1) = Succ (fromInteger n) etc.
then genericLength xn > n does exactly what Andrew wants, when n :: Nat.
Wow.
Show me a simple problem, and some Haskeller somewhere will find a completely unexpected way to solve it... LOL!
OTOH, doesn't that just mean that Nat is itself a degenerate list, and genericList is just converting one list to another, and the Ord instance for Nat is doing the short-cut stuff?
Yes. Nat ~ [()], where ~ means `is isomorphic to'. But Nat is also the obvious way to encode Peano arithmetic in Haskell, so this is a deep thought, not a shallow one. (Properly speaking, the set of total values of Nat is the set of natural numbers + infinity (infinity = x where x = Succ x), and the set of total lists of type [alpha] is sum (n :: Nat). f :: {m :: Nat | m < n} -> alpha where f and n are total. sum is a dependent sum, which is just a product, and the only total function with co-domain () is const () (well, and (`seq` ()), but they're equal on total arguments), so that type is just sum (n :: Nat^inf). {const ()} which is isomorphic to Nat^inf. But you can see that this is a deep thought, not a shallow one. . .) Jonathan Cast http://sourceforge.net/projects/fid-core http://sourceforge.net/projects/fid-emacs

Jonathan Cast wrote:
On Thursday 12 July 2007, Andrew Coppin wrote:
Wow.
Show me a simple problem, and some Haskeller somewhere will find a completely unexpected way to solve it... LOL!
OTOH, doesn't that just mean that Nat is itself a degenerate list, and genericList is just converting one list to another, and the Ord instance for Nat is doing the short-cut stuff?
Yes. Nat ~ [()], where ~ means `is isomorphic to'. But Nat is also the obvious way to encode Peano arithmetic in Haskell, so this is a deep thought, not a shallow one.
That thought was not lost on me. ;-) I was just thinking that in mundane machine terms, we're not doing anything especially remarkable here...

On Wed, Jul 11, 2007 at 11:46:10PM +0200, Chaddaï Fouché wrote:
2007/7/11, Stefan O'Rear
: Interestingly, the function is already there; it's called genericLength.
However, the lazy natural type isn't.
I'm not sure what you mean there : genericLength is just a length that can return any Num (eg. an Integer) and not just Int, it has nothing to do with what Andrew wanted, which was a function that checked if a list was longer than n without swallowing more of the list than necessary. Is there something I misunderstood in the exchange ?
stefan@stefans:/tmp$ cat Z.hs import List data Nat = Z | S Nat deriving(Eq, Ord, Show) instance Num Nat where Z + x = x S x + y = S (x + y) Z * x = Z S x * y = y + (x * y) fromInteger 0 = Z fromInteger (n+1) = S (fromInteger n) main = print $ genericLength (1 : 2 : undefined) > (1 :: Nat) stefan@stefans:/tmp$ runghc Z.hs Z.hs:5:0: Warning: No explicit method nor default method for `abs' In the instance declaration for `Num Nat' Z.hs:5:0: Warning: No explicit method nor default method for `signum' In the instance declaration for `Num Nat' True stefan@stefans:/tmp$ Stefan

Beautiful ! :-) Could Haskell define this lazy Natural in a more efficient fashion ? It seems like an useful thing to have in a standard library (or is it in one of those ?). -- Jedaï

On Wed, Jul 11, 2007 at 10:33:06PM +0200, Chaddaï Fouché wrote:
2007/7/11, Andrew Coppin
: Ouch! That's gotta sting...
I wasn't aware that this function was so leathal. I use it constantly all the time...
It isn't that "lethal" usually. It's only because he was using it on an infinite stream that it hurt so much... If you use it on a normal stdin or a hGetContents on a file it will be fine (though you will lose the advantage of its laziness, for example constant memory treatment).
It was not infinite. This has nothing to do with infiniteness. This has to do with Lazy lists and IO. Specifically, reading to the end of a list of responses - before sending all the requests. Waiting for the second responce before sending the second request caused a deadlock, even though only a finite number of responces would be received. Stefan

2007/7/11, Stefan O'Rear
It was not infinite. This has nothing to do with infiniteness.
This has to do with Lazy lists and IO.
Specifically, reading to the end of a list of responses - before sending all the requests.
Waiting for the second responce before sending the second request caused a deadlock, even though only a finite number of responces would be received.
Ah, ok, I read too quickly... Still not the most current case. -- Jedaï

Totally off-topic. I'm just curious. On Wed, Jul 11, 2007 at 22:49:58 +0200, Chaddaï Fouché wrote: [..]
Jedaï
Chaddaï, I just noticed you sign your emails with "Jedaï". Being the curious person I am I wonder, why? /M -- Magnus Therning (OpenPGP: 0xAB4DFBA4) magnus@therning.org Jabber: magnus.therning@gmail.com http://therning.org/magnus

On Wed, 2007-07-11 at 22:33 +0200, Chaddaï Fouché wrote:
2007/7/11, Andrew Coppin
: Ouch! That's gotta sting...
I wasn't aware that this function was so leathal. I use it constantly all the time...
It isn't that "lethal" usually. It's only because he was using it on an infinite stream that it hurt so much... If you use it on a normal stdin or a hGetContents on a file it will be fine (though you will lose the advantage of its laziness, for example constant memory treatment).
Nevertheless, length is a function you should rarely use.

Derek Elkins wrote:
On Wed, 2007-07-11 at 22:33 +0200, Chaddaï Fouché wrote:
2007/7/11, Andrew Coppin
: Ouch! That's gotta sting...
I wasn't aware that this function was so leathal. I use it constantly all the time...
It isn't that "lethal" usually. It's only because he was using it on an infinite stream that it hurt so much... If you use it on a normal stdin or a hGetContents on a file it will be fine (though you will lose the advantage of its laziness, for example constant memory treatment).
Nevertheless, length is a function you should rarely use.
Amen. (I believe the Wiki mentions this concept somewhere... Maybe we should rename it unsafeLength? No, OK, how about... um... slowLength?)

Nevertheless, length is a function you should rarely use.
Amen.
(I believe the Wiki mentions this concept somewhere... Maybe we should rename it unsafeLength? No, OK, how about... um... slowLength?)
It isn't actually slow... how about beSureYouReallyWantIntBeforeUsingThisLength? =)

Brent Yorgey wrote:
> Nevertheless, length is a function you should rarely use. >
Amen.
(I believe the Wiki mentions this concept somewhere... Maybe we should rename it unsafeLength? No, OK, how about... um... slowLength?)
It isn't actually slow... how about beSureYouReallyWantIntBeforeUsingThisLength? =)
O RLY?
length [1..]
Takes almost *forever* on my machine. ;-)

On Thu, 12 Jul 2007, Andrew Coppin wrote:
(I believe the Wiki mentions this concept somewhere... Maybe we should rename it unsafeLength? No, OK, how about... um... slowLength?)
http://www.haskell.org/haskellwiki/Things_to_avoid#Don.27t_ask_for_the_lengt... http://www.haskell.org/haskellwiki/Peano_numbers

On 7/10/07, Ronald Guida
Hi Everyone,
A few weeks ago, I started learning Haskell (and functional programming) on my own from the wealth if information on the internet. I recently read the paper "Why Functional Programming Matters" [1] and it led me to wonder how to input a lazy list.
Another way to do this using my HCL[1] library: import HCL main = do total <- runRequest $ reqLift sum (reqList $ prompt "Please enter an integer value (or enter to quit): " reqInteger) putStrLn $ "Your entries totaled: " ++ (maybe "nothing!" show total) Justin [1] http://hackage.haskell.org/cgi-bin/hackage-scripts/package/HCL-1.1
participants (12)
-
Andrew Coppin
-
Brent Yorgey
-
Chaddaï Fouché
-
Dan Piponi
-
Derek Elkins
-
Felipe Almeida Lessa
-
Henning Thielemann
-
Jonathan Cast
-
Justin Bailey
-
Magnus Therning
-
Ronald Guida
-
Stefan O'Rear