
$ cat > foo.c
#include

Your "gsi> " is buffered because there's no newline at the end. To flush
the buffer and force it to be printed immediately, use 'hFlush' from the
System.IO library, or use 'hSetBuffering' from that same library:
http://haskell.org/ghc/docs/latest/html/libraries/base/System-IO.html
I believe you can observe the same behavior in C.
- Phil
On Feb 8, 2008 4:14 PM, Jonathan Cast
$ cat > foo.c #include
int main() { char s[1024]; printf("gsi> "); gets(s); printf("%s\n", s); return 0; } $ make foo cc gsi.c -o gsi $ ./foo warning: this program uses gets(), which is unsafe. gsi> hello hello $ cat > foo.hs main = do putStr "gsi> " s <- getLine putStrLn s $ ghc foo.hs -o foo $ ./foo hello gsi> hello
(This is on MacOS X). It strikes me that GHC is being extraordinarily unhelpful here. Is there anyone on the planet who ever actually wants this behavior?
jcc
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Feb 8, 2008, at 19:41 , Philip Weaver wrote:
Your "gsi> " is buffered because there's no newline at the end. To flush the buffer and force it to be printed immediately, use 'hFlush' from the System.IO library, or use 'hSetBuffering' from that same library: http://haskell.org/ghc/docs/latest/html/ libraries/base/System-IO.html
I believe you can observe the same behavior in C.
Most C stdio libraries in my experience have extra code in the functions that read stdin to flush stdout first, specifically because of lazy people who don't pay attention to buffering. -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

On 8 Feb 2008, at 4:50 PM, Brandon S. Allbery KF8NH wrote:
On Feb 8, 2008, at 19:41 , Philip Weaver wrote:
Your "gsi> " is buffered because there's no newline at the end. To flush the buffer and force it to be printed immediately, use 'hFlush' from the System.IO library, or use 'hSetBuffering' from that same library: http://haskell.org/ghc/docs/latest/html/ libraries/base/System-IO.html
I believe you can observe the same behavior in C.
Most C stdio libraries in my experience have extra code in the functions that read stdin to flush stdout first, specifically because of lazy people who don't pay attention to buffering.
Why can't GHC implement the same thing? jcc

GHC certain *could* do this, but it's arguably not the right thing to do.
For performance, the operating system buffers writes until it is ready to
write large chunks at a time. If you do not want this behavior, change the
buffering mode from its default.
- Phil
On Feb 8, 2008 5:07 PM, Jonathan Cast
On 8 Feb 2008, at 4:50 PM, Brandon S. Allbery KF8NH wrote:
On Feb 8, 2008, at 19:41 , Philip Weaver wrote:
Your "gsi> " is buffered because there's no newline at the end. To flush the buffer and force it to be printed immediately, use 'hFlush' from the System.IO library, or use 'hSetBuffering' from that same library: http://haskell.org/ghc/docs/latest/html/ libraries/base/System-IO.html
I believe you can observe the same behavior in C.
Most C stdio libraries in my experience have extra code in the functions that read stdin to flush stdout first, specifically because of lazy people who don't pay attention to buffering.
Why can't GHC implement the same thing?
jcc
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On 8 Feb 2008, at 5:29 PM, Philip Weaver wrote:
GHC certain *could* do this, but it's arguably not the right thing to do. For performance, the operating system buffers writes until it is ready to write large chunks at a time. If you do not want this behavior, change the buffering mode from its default.
To what? BlockBuffering is worse, not better, and the docs *explicitly* say that switching to NoBuffering will break ^D (if it wasn't broken already...) My specification for a working program is `one that works exactly like every other program on my machine'. I don't see how to produce such a program with GHC.(1) jcc (1) Using readline might work (although I'm kind of sceptical given what's preceded it), but I haven't gotten it to link thus far...

import System.IO
myGetLine = hFlush stdout >> getLine
-- ryan
On 2/8/08, Jonathan Cast
On 8 Feb 2008, at 5:29 PM, Philip Weaver wrote:
GHC certain *could* do this, but it's arguably not the right thing to do. For performance, the operating system buffers writes until it is ready to write large chunks at a time. If you do not want this behavior, change the buffering mode from its default.
To what?
BlockBuffering is worse, not better, and the docs *explicitly* say that switching to NoBuffering will break ^D (if it wasn't broken already...) My specification for a working program is `one that works exactly like every other program on my machine'. I don't see how to produce such a program with GHC.(1)
jcc
(1) Using readline might work (although I'm kind of sceptical given what's preceded it), but I haven't gotten it to link thus far...
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On 8 Feb 2008, at 6:34 PM, Ryan Ingram wrote:
import System.IO
myGetLine = hFlush stdout >> getLine
That fixes this issue, certainly (although it's superfluous; my program really does contain only a single call to getLine)... Nevertheless, it would be nice to at least have it in the standard library; it's much more useful than any of the input functions that already exist. jcc

On 8 Feb 2008, at 6:50 PM, Jonathan Cast wrote:
On 8 Feb 2008, at 6:34 PM, Ryan Ingram wrote:
import System.IO
myGetLine = hFlush stdout >> getLine
That fixes this issue, certainly (although it's superfluous; my program really does contain only a single call to getLine)...
Nevertheless, it would be nice to at least have it in the standard library; it's much more useful than any of the input functions that already exist.
Also, for some reason, this doesn't seem to be necessary inside an Emacs buffer... Do we not care about performance in that case? jcc

On a lark, I loaded this into Hugs this morning, and it didn't complain: data Thing = Thing (Integer -> Integer) But, I've never seen that sort of construct in an example. Do people ever embed functions in ADTs? Michael

2008/2/10, Michael Feathers
On a lark, I loaded this into Hugs this morning, and it didn't complain:
data Thing = Thing (Integer -> Integer)
But, I've never seen that sort of construct in an example. Do people ever embed functions in ADTs?
Yes, anyway you can embed function in Maybe a or Either a b for example, since they're polymorphic. Embedding functions in ADT purposefully happens quite often too, just look at the State Monad, the functionnal references proposal and so on... Recently I embedded functions into a denotational semantic ADT for a tiny DSL, there's plenty of use cases. -- Jedaï

On Feb 10, 2008 1:34 PM, Michael Feathers
On a lark, I loaded this into Hugs this morning, and it didn't complain:
data Thing = Thing (Integer -> Integer)
But, I've never seen that sort of construct in an example. Do people ever embed functions in ADTs?
Yes, this is quite common. Here's a quick example (untested): data MyMap key value = M (key -> Maybe value) lookup (M m) key = m key insert (M m) key value = M (\key' -> if key' == key then Just value else m key') This is a naive data structure for storing a map as a function from the key to the value. Not very efficient, perhaps, but you use similar concepts in more useful scenarios (e.g. the State monad). -- Sebastian Sylvan +44(0)7857-300802 UIN: 44640862

On Feb 10, 2008 1:42 PM, Sebastian Sylvan
On Feb 10, 2008 1:34 PM, Michael Feathers
wrote: On a lark, I loaded this into Hugs this morning, and it didn't complain:
data Thing = Thing (Integer -> Integer)
But, I've never seen that sort of construct in an example. Do people ever embed functions in ADTs?
Yes, this is quite common. Here's a quick example (untested):
data MyMap key value = M (key -> Maybe value)
lookup (M m) key = m key insert (M m) key value = M (\key' -> if key' == key then Just value else m key')
This is a naive data structure for storing a map as a function from the key to the value. Not very efficient, perhaps, but you use similar concepts in more useful scenarios (e.g. the State monad).
Perhaps I should add an empty MyMap too: empty = M (\_-> Nothing ) -- Sebastian Sylvan +44(0)7857-300802 UIN: 44640862

Quite frequently. Here are a few examples from my own code: For "functional references" (representing a bidirectional function from a data type to a part of itself (for example the first element of a pair)).
data Accessor s a = Accessor { get :: s -> a , set :: a -> s -> s }
My quantum computation arrow (really in the realm of "concrete, useful things", huh? :-)
data Operator b c = Op (forall d. QStateVec (b,d) -> IO (QStateVec (c,d))) | ...
The ubiquitous FRP Behavior, comprising a current value and a function which takes a timestep and returns the next value.
data Behavior a = Behavior a (Double -> Behavior a)
The "suspend" monad, representing a computation which can either finish now with a value of type a, or suspends to request a value of type v before continuing.
data Suspend v a = Return a | Suspend (v -> Suspend v a)
It seems that most frequently, functions in ADTs are used when
implementing monads or arrows, but that doens't need to be the case.
A lot of times a function is the best way to represent a particular
part of a data structure :-)
Luke
On Feb 10, 2008 1:34 PM, Michael Feathers
On a lark, I loaded this into Hugs this morning, and it didn't complain:
data Thing = Thing (Integer -> Integer)
But, I've never seen that sort of construct in an example. Do people ever embed functions in ADTs?
Michael
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Great. Thanks to everyone! Michael Luke Palmer wrote:
Quite frequently.
Here are a few examples from my own code:
For "functional references" (representing a bidirectional function from a data type to a part of itself (for example the first element of a pair)).
data Accessor s a = Accessor { get :: s -> a , set :: a -> s -> s }
My quantum computation arrow (really in the realm of "concrete, useful things", huh? :-)
data Operator b c = Op (forall d. QStateVec (b,d) -> IO (QStateVec (c,d))) | ...
The ubiquitous FRP Behavior, comprising a current value and a function which takes a timestep and returns the next value.
data Behavior a = Behavior a (Double -> Behavior a)
The "suspend" monad, representing a computation which can either finish now with a value of type a, or suspends to request a value of type v before continuing.
data Suspend v a = Return a | Suspend (v -> Suspend v a)
It seems that most frequently, functions in ADTs are used when implementing monads or arrows, but that doens't need to be the case. A lot of times a function is the best way to represent a particular part of a data structure :-)
Luke
On Feb 10, 2008 1:34 PM, Michael Feathers
wrote: On a lark, I loaded this into Hugs this morning, and it didn't complain:
data Thing = Thing (Integer -> Integer)
But, I've never seen that sort of construct in an example. Do people ever embed functions in ADTs?
Michael
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

How bad is this: addProduct :: [Product] -> Product -> [Product] addProduct inventory product = nub (product : inventory) compared to this: addProduct :: [Product] -> Product -> [Product] addProduct inventory p | isNothing (find (==p) inventory) = p : inventory | otherwise = inventory My guess is that the latter is more efficient, but then when I think about laziness, I wonder whether the first is a fair trade. Michael

On Feb 10, 2008 1:07 PM, Michael Feathers
How bad is this:
addProduct :: [Product] -> Product -> [Product] addProduct inventory product = nub (product : inventory)
O(n²) as is nub.
compared to this:
addProduct :: [Product] -> Product -> [Product] addProduct inventory p | isNothing (find (==p) inventory) = p : inventory | otherwise = inventory
O(n) as is find.
My guess is that the latter is more efficient, but then when I think about laziness, I wonder whether the first is a fair trade.
I don't think so =). Still, you should be using Data.Set which will take you to O(log n). -- Felipe.

2008/2/10, Michael Feathers
How bad is this:
addProduct :: [Product] -> Product -> [Product] addProduct inventory product = nub (product : inventory)
This is pretty terrible, if the list is consumed afterward (which we assume it will be) we should have something like a O(n^3) complexity... Since nub is O(n^2).
compared to this:
addProduct :: [Product] -> Product -> [Product] addProduct inventory p | isNothing (find (==p) inventory) = p : inventory | otherwise = inventory
This is much better, though probably better writed :
addProduct :: [Product] -> Product -> [Product] addProduct inventory p | elem p inventory = p : inventory | otherwise = inventory
and probably even better with a Set instead of a List... -- Jedaï

On Feb 10, 2008 1:14 PM, Chaddaï Fouché
This is much better, though probably better writed :
addProduct :: [Product] -> Product -> [Product] addProduct inventory p | elem p inventory = p : inventory | otherwise = inventory
Maybe addProduct :: [Product] -> Product -> [Product] addProduct inventory p = p : delete p inventory
and probably even better with a Set instead of a List...
import qualified Data.Set as S addProduct :: S.Set Product -> Product -> S.Set Product addProduct = flip S.insert -- Felipe.

On Feb 10, 2008 1:20 PM, Felipe Lessa
Maybe
addProduct :: [Product] -> Product -> [Product] addProduct inventory p = p : delete p inventory
Oh, forget this, it will keep rewriting the tail of the list, which is a Bad Thing (TM). -- Felipe.

On Sun, 10 Feb 2008, Michael Feathers wrote:
How bad is this:
addProduct :: [Product] -> Product -> [Product] addProduct inventory product = nub (product : inventory)
compared to this:
addProduct :: [Product] -> Product -> [Product] addProduct inventory p | isNothing (find (==p) inventory) = p : inventory | otherwise = inventory
Data.Set is first choice, 'elem' is second choice, but still better than 'isNothing (find ...)'.

On Sun, 10 Feb 2008, Luke Palmer wrote:
Quite frequently.
Here are a few examples from my own code:
For "functional references" (representing a bidirectional function from a data type to a part of itself (for example the first element of a pair)).
data Accessor s a = Accessor { get :: s -> a , set :: a -> s -> s }
My quantum computation arrow (really in the realm of "concrete, useful things", huh? :-)
The pattern seems to be common enough to be turned into a package. http://www.haskell.org/haskellwiki/?title=Record_access&action=history

On Sun, 10 Feb 2008, Henning Thielemann wrote:
On Sun, 10 Feb 2008, Luke Palmer wrote:
Quite frequently.
Here are a few examples from my own code:
For "functional references" (representing a bidirectional function from a data type to a part of itself (for example the first element of a pair)).
data Accessor s a = Accessor { get :: s -> a , set :: a -> s -> s }
My quantum computation arrow (really in the realm of "concrete, useful things", huh? :-)
The pattern seems to be common enough to be turned into a package.
http://www.haskell.org/haskellwiki/?title=Record_access&action=history

mfeathers:
On a lark, I loaded this into Hugs this morning, and it didn't complain:
data Thing = Thing (Integer -> Integer)
But, I've never seen that sort of construct in an example. Do people ever embed functions in ADTs?
Michael
What's the use of a functional language if you can't treat functions as first class values :) -- Don

On 9 Feb 2008, at 2:29 pm, Philip Weaver wrote:
GHC certain *could* do this, but it's arguably not the right thing to do.
I have reminded the GHC maintainers before that the Haskell specification *REQUIRES* a Haskell system to support this; there is an example that makes no sense whatever without it. (And the other Haskell systems I use get it right.) I note that David Bacon's SETL implementation has explicit support for tying an input stream and an output stream together so that any time input is done on the input stream the output stream is flushed; this is done automatically for sockets and is *seriously* useful in avoiding mistakes. Note that this should make essentially no difference to performance because (a) the flushing is only needed when the input buffer is exhausted, which happens once per line, (b) the kinds of streams where you want it (terminals, STREAMs, sockets, serial ports, &c) generally have other costs so high you won't be able to measure this one, (c) it *only* applies to bidirectional streams or to explicitly coupled streams, so I/O to disc files or memory sticks or other high speed block devices should never be affected at all (unless someone chooses to do it explicitly, in which case it's still going to be faster than anything they could have done by hand).

Hi Richard, On Mon, Feb 11, 2008 at 12:37:27PM +1300, Richard A. O'Keefe wrote:
On 9 Feb 2008, at 2:29 pm, Philip Weaver wrote:
GHC certain *could* do this, but it's arguably not the right thing to do.
I have reminded the GHC maintainers before that the Haskell specification *REQUIRES* a Haskell system to support this;
["this" is flushing stdout when we read from stdin, if I have followed correctly] Can you please say where the report says this? I've just skimmed http://haskell.org/onlinereport/io.html and didn't see it mentioned. Also, if there's a GHC bug about this, can you please point me to it? A quick search didn't find anything.
there is an example that makes no sense whatever without it.
I'm not sure which example you're referring to, but the first example on the above page 21.10.1 Summing Two Numbers starts off by doing hSetBuffering stdout NoBuffering which implies to me that implementations are not expected to do the flushing hack. Thanks Ian
participants (13)
-
Brandon S. Allbery KF8NH
-
Chaddaï Fouché
-
Don Stewart
-
Felipe Lessa
-
Henning Thielemann
-
Ian Lynagh
-
Jonathan Cast
-
Luke Palmer
-
Michael Feathers
-
Philip Weaver
-
Richard A. O'Keefe
-
Ryan Ingram
-
Sebastian Sylvan