Re: [Haskell-cafe] Simple network client

2008-02-01 Thread Jules Bean

Jonathan Cast wrote:

On 31 Jan 2008, at 1:23 AM, Reinier Lamers wrote:


Bayley, Alistair wrote:
More than one person has posted previously about the flaws and traps 
of lazy IO. A common position seems to be "don't do lazy IO".


Still, when I was browsing the Haskell' wiki a few days ago, I 
couldn't find any proposal to remove lazy I/O or move it into some 
special System.IO.Lazy (or 
System.IO.UnsafeEvilFunctionsThatSacrificeBabies) ...


Sacrificing babies is not a unique characteristic of lazy IO, of course; 
it's true of any file IO on a non-versioning file system.



However you can contain the pain if it's in the IO monad, and be in no 
worse situation than conventional languages.


If the pain is unsafeInterleaved all over the place, then you actually 
*are* in a worse situation.


ObHaskell' : lazy IO shouldn't be in any haskell standard, since it's 
not referentially transparent. It should be a powerful but dangerous 
feature enabled by certain implementations in an implementation specfic 
way. (unsafeInterleaveIO itself is not haskel98, I'm fairly sure)


Jules

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Simple network client

2008-01-31 Thread Jonathan Cast

On 31 Jan 2008, at 1:23 AM, Reinier Lamers wrote:


Bayley, Alistair wrote:
More than one person has posted previously about the flaws and  
traps of lazy IO. A common position seems to be "don't do lazy IO".


Still, when I was browsing the Haskell' wiki a few days ago, I  
couldn't find any proposal to remove lazy I/O or move it into some  
special System.IO.Lazy (or  
System.IO.UnsafeEvilFunctionsThatSacrificeBabies) ...


Sacrificing babies is not a unique characteristic of lazy IO, of  
course; it's true of any file IO on a non-versioning file system.


jcc


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Simple network client

2008-01-31 Thread Adam Langley
On Jan 31, 2008 5:07 AM, Gary Bickford <[EMAIL PROTECTED]> wrote:
> Wasn't there a Linux file system (possibly a FUSE user-space one) that
> worked on writable CDs?  IIRC it worked by marking the previous copy of
> the file as erased, and writing a new copy.

Probably you're thinking of layering a unionfs over the top. It works
well in my experience.



AGL

-- 
Adam Langley  [EMAIL PROTECTED]
http://www.imperialviolet.org   650-283-9641
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Simple network client

2008-01-31 Thread Gary Bickford
Wasn't there a Linux file system (possibly a FUSE user-space one) that
worked on writable CDs?  IIRC it worked by marking the previous copy of
the file as erased, and writing a new copy.

On Wed, 2008-01-30 at 23:05 -0500, [EMAIL PROTECTED]
wrote:
> > PS: I would love to see an immutable filesystem that does not allow
> writing to files, it only creates new files and garbage collects files
> that have no incoming reference anymore... Just like a garbage
> collected heap, and a bit like an OLAP databases (as far as I remember
> my DB theory...) Besides the performance bottleneck, does something
> like that exists?
> 
> Plan 9's venti is somewhat similar to this.  though it's really a
> storage backend that you implement a filesystem on top of, and the fs
> winds up having a write cache, which is mutable in practice.  The
> interesting thing is that the block's location is the cryptographic
> hash of its contents, which leads to all sorts of neat properties (as
> well as requiring immutability).
> 
-- 
"Isn't it funny how the Global Village includes everybody but the
villagers?" (http://wiki.laptop.org/go/OLPC_Publications)

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Simple network client

2008-01-31 Thread Reinier Lamers

Bayley, Alistair wrote:

More than one person has posted previously about the flaws and traps of lazy IO. A common 
position seems to be "don't do lazy IO".
  
Still, when I was browsing the Haskell' wiki a few days ago, I couldn't 
find any proposal to remove lazy I/O or move it into some special 
System.IO.Lazy (or System.IO.UnsafeEvilFunctionsThatSacrificeBabies) ...


Reinier
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Simple network client

2008-01-30 Thread Evan Laforge
> PS: I would love to see an immutable filesystem that does not allow writing 
> to files, it only creates new files and garbage collects files that have no 
> incoming reference anymore... Just like a garbage collected heap, and a bit 
> like an OLAP databases (as far as I remember my DB theory...) Besides the 
> performance bottleneck, does something like that exists?

Plan 9's venti is somewhat similar to this.  though it's really a
storage backend that you implement a filesystem on top of, and the fs
winds up having a write cache, which is mutable in practice.  The
interesting thing is that the block's location is the cryptographic
hash of its contents, which leads to all sorts of neat properties (as
well as requiring immutability).
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Simple network client

2008-01-30 Thread Jules Bean

Dan Weston wrote:

Now I'm confused (which happens quite a lot, I'm afraid!)

Prelude> readFile undefined
*** Exception: Prelude.undefined

Prelude> readFile undefined >>= \cs -> putStrLn "Hello"
*** Exception: Prelude.undefined

It seems that readFile is strict in its argument. As for getLine, it has 
no argument to be strict in.



This is the confusion between strict/lazy in the ordinary language 
semantics sense, and strictIO/ 
lazyBrokenDangerousHereBeGremlinsSemanticallyUnsoundIO


Jules
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Simple network client

2008-01-30 Thread Dan Weston

Peter Verswyvelen wrote:

main = do
cs <- getLine
putStrLn ("Hello "++cs)

looks so much like

main = do
cs <- readFile "foo"
writeFile "foo" cs

but in the first one cs is strict, while the second it is lazy... But that's
not obvious.



Now I'm confused (which happens quite a lot, I'm afraid!)

Prelude> readFile undefined
*** Exception: Prelude.undefined

Prelude> readFile undefined >>= \cs -> putStrLn "Hello"
*** Exception: Prelude.undefined

It seems that readFile is strict in its argument. As for getLine, it has 
no argument to be strict in.


What am I missing?

Dan


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Simple network client

2008-01-30 Thread Peter Verswyvelen
> And even better is
> 
> main = do
>cs <- strictReadFile "L:/Foo.txt"
>writeFile "L:/Foo.txt" cs

Yes. By making these mistakes I understand the problem very well now. But it
*is* hard to see if the function in question is strict or lazy. 

For example, the problem to me appears to be that this code:

main = do
cs <- getLine
putStrLn ("Hello "++cs)

looks so much like

main = do
cs <- readFile "foo"
writeFile "foo" cs

but in the first one cs is strict, while the second it is lazy... But that's
not obvious. It would be if it looked like e.g:

main = do
cs <- getLine!
putStrLn! ("Hello "++cs)

or something similar.

Also, once I'm in the "do" syntax, my mind seems to switch to "imperative
mode", while of course, it is still purely functional code in desguise :)

Cheers,
Peter


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Simple network client

2008-01-30 Thread Bryan O'Sullivan
Adam Langley wrote:
> On Jan 30, 2008 1:07 PM, Adam Langley <[EMAIL PROTECTED]> wrote:
>> So, if I don't hear otherwise soon, I'll probably push a new version
>> of binary-strict later on today with the interface above.
> 
> It's in the darcs now, http://darcs.imperialviolet.org/binary-strict

Thanks!

http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Simple network client

2008-01-30 Thread Adam Langley
On Jan 30, 2008 1:07 PM, Adam Langley <[EMAIL PROTECTED]> wrote:
> So, if I don't hear otherwise soon, I'll probably push a new version
> of binary-strict later on today with the interface above.

It's in the darcs now, http://darcs.imperialviolet.org/binary-strict


AGL

-- 
Adam Langley  [EMAIL PROTECTED]
http://www.imperialviolet.org   650-283-9641
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Simple network client

2008-01-30 Thread Adam Langley
On Jan 30, 2008 12:04 PM, Bryan O'Sullivan <[EMAIL PROTECTED]> wrote:
> Adam Langley wrote:
> I'd have expected it to look more like this:
>
> data Result a = Failed String
>   | Finished B.ByteString a
>   | Partial (B.ByteString -> Result a)
>
> (The change here is from a list to a singleton.)  I don't think I care
> much for the extra boxing and reversing this involves.

Well, since you're probably the /only/ user you can pretty much say
how it works ;) The original interface was designed so that you can
yield a list of results as you parse. I guess that, since you get the
remainder anyway, you can chain these together if you like anyway.

So, if I don't hear otherwise soon, I'll probably push a new version
of binary-strict later on today with the interface above.



AGL


-- 
Adam Langley  [EMAIL PROTECTED]
http://www.imperialviolet.org   650-283-9641
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Simple network client

2008-01-30 Thread Bryan O'Sullivan
Adam Langley wrote:

> Also, if you want the above approach (read a bit, see if it's enough),
> see IncrementalGet in the binary-strict package which is a Get with a
> continuation monad that stops when it runs out of bytes and returns a
> continuation that you can give more data to in the future.

I've used this now, and it's really rather nice: exactly the sort of
thing one needs if multiplexing streams, or reading incomplete chunks,
and with a simple interface that doesn't force users to know or care
about Cont.  The one thing I found curious was the Result type: it's
oriented towards returning a list of results.

data Result a = Failed String
  | Finished B.ByteString [a]
  | Partial (B.ByteString -> Result a) [a]

I'd have expected it to look more like this:

data Result a = Failed String
  | Finished B.ByteString a
  | Partial (B.ByteString -> Result a)

(The change here is from a list to a singleton.)  I don't think I care
much for the extra boxing and reversing this involves.

http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Simple network client

2008-01-30 Thread Gary Bickford
One rather funky  but effective solution might be to use the tftp
protocol.  No security, but simple, flexible and efficient.  I think
there are C libraries that implement it.  This would take care of
handshaking binary data.  I have no idea if anyone has ever used it in
Haskell.
GB
On Wed, 2008-01-30 at 12:50 -0500, [EMAIL PROTECTED]
wrote:
> robably not all of them, but some of them, definitely.
> 
> If you want to transmit an arbitrary bytestring then I'm pretty sure 
> that transmitting a length word first is the way to go. An arbitrary 
> bytestring can have any value in it, so there are no values left to
> act 
> as delimiters :) You'd have to have some kind of escaping mechanism, 
> like show, which is expensive.
-- 
"Isn't it funny how the Global Village includes everybody but the
villagers?" (http://wiki.laptop.org/go/OLPC_Publications)

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Simple network client

2008-01-30 Thread Jules Bean

Judah Jacobson wrote:

On Jan 30, 2008 8:31 AM, Bryan O'Sullivan <[EMAIL PROTECTED]> wrote:

Peter Verswyvelen wrote:


Then I tried the "seq" hack to force the handle opened by readFile to be 
closed, but that did not seem to work either. For example, the following still gave 
access denied:

main = do
  cs <- readFile "L:/Foo.txt"
  writeFile "L:/Foo.txt" $ seq (length cs) cs

This is unfortunately a classic beginner's mistake.  You got the seq
wrong here, which is very common.
[...]
You need to float the call to seq out so that it's evaluated before the
call to writeFile:

  length cs `seq` writeFile cs



Another way of doing things: I've recently become a fan of
Control.Exception.evaluate:

main = do
  cs <- readFile "L:/Foo.txt"
  evalute (length cs)
  writeFile "L:/Foo.txt" cs

This might be easier for beginners to understand than messing around
with seq's (as long as you're already in the IO monad).



And even better is

main = do
  cs <- strictReadFile "L:/Foo.txt"
  writeFile "L:/Foo.txt" cs

which can be rewritten as

main = writeFile "L:/Foo.txt" =<< strictReadFile "L:/Foo.txt"

if you like such things.

The problem is that strictReadFile isn't in the standard lib. My opinion 
is that readFile should *be* strict, and the lazy version should be an 
option with caveats.


In bos's notation, I'd say that readFile should be strict, and on level 
1. It does what people expect. Sure it runs out of memory if the file is 
very big, but I don't find that unexpected. lazyReadFile can go on level 
2 after the boss.


Jules
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Simple network client

2008-01-30 Thread Judah Jacobson
On Jan 30, 2008 8:31 AM, Bryan O'Sullivan <[EMAIL PROTECTED]> wrote:
> Peter Verswyvelen wrote:
>
> > Then I tried the "seq" hack to force the handle opened by readFile to be 
> > closed, but that did not seem to work either. For example, the following 
> > still gave access denied:
> >
> > main = do
> >   cs <- readFile "L:/Foo.txt"
> >   writeFile "L:/Foo.txt" $ seq (length cs) cs
>
> This is unfortunately a classic beginner's mistake.  You got the seq
> wrong here, which is very common.
> [...]
> You need to float the call to seq out so that it's evaluated before the
> call to writeFile:
>
>   length cs `seq` writeFile cs
>

Another way of doing things: I've recently become a fan of
Control.Exception.evaluate:

main = do
  cs <- readFile "L:/Foo.txt"
  evalute (length cs)
  writeFile "L:/Foo.txt" cs

This might be easier for beginners to understand than messing around
with seq's (as long as you're already in the IO monad).

-Judah
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Simple network client

2008-01-30 Thread Adam Langley
On Jan 30, 2008 4:32 AM, Jules Bean <[EMAIL PROTECTED]> wrote:
> The third, but more sophisticated answer is to use non-blocking IO, read
>   'only what is available', decide if it's enough to process, if not
> store it in some local buffer until next time. This is much more work
> and easy to implement bugs in, but you need it for true streaming
> protocols.  In that case hGetBufNonBlocking is your friend.

If using bytestrings from the network, the network-bytestring package
is what you need.

If you're parsing small lumps from the network, Data.Binary's failures
will probably make life harder than it should be for you since they
can only be caught in IO. See
http://www.haskell.org/haskellwiki/DealingWithBinaryData about a
strict Get which might work for you.

Also, if you want the above approach (read a bit, see if it's enough),
see IncrementalGet in the binary-strict package which is a Get with a
continuation monad that stops when it runs out of bytes and returns a
continuation that you can give more data to in the future.


AGL

-- 
Adam Langley  [EMAIL PROTECTED]
http://www.imperialviolet.org   650-283-9641
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Simple network client

2008-01-30 Thread Bryan O'Sullivan
Peter Verswyvelen wrote:

> Then I tried the "seq" hack to force the handle opened by readFile to be 
> closed, but that did not seem to work either. For example, the following 
> still gave access denied:
> 
> main = do
>   cs <- readFile "L:/Foo.txt"
>   writeFile "L:/Foo.txt" $ seq (length cs) cs

This is unfortunately a classic beginner's mistake.  You got the seq
wrong here, which is very common.

If you think about the way Haskell evaluates your code, writeFile isn't
going to need the data that it's writing until after it's opened the
file.  Thus the seq won't be reduced until writeFile needs to write the
file.  The file is still open behind the scenes when writeFile begins,
since the contents of cs have not yet been demanded, so writeFile's
attempt to open the file fails.

You need to float the call to seq out so that it's evaluated before the
call to writeFile:

  length cs `seq` writeFile cs

Almost everyone makes this mistake early on.  Quite often, it's
*exactly* this mistake that is made, with just the sequence of
transformations you described.  There's nothing wrong with hGetContents
or readFile.  They just ought to appear on level two, after you've
defeated the lazy evaluation boss at the end of level one.

http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Simple network client

2008-01-30 Thread Bayley, Alistair
> From: [EMAIL PROTECTED] 
> [mailto:[EMAIL PROTECTED] On Behalf Of Peter 
> Verswyvelen
> 
> As a newbie I made a nice little program that called readFile 
> and writeFile on the same filename, but of course the file 
> handle of the readFile was not closed yet => access denied. A 
> nice case of getting bitten by my imperative background.
> 
> So I guess hGet/hGetNonBlocking/ByteString is also the 
> correct way to solve this?

More than one person has posted previously about the flaws and traps of lazy 
IO. A common position seems to be "don't do lazy IO".
  http://article.gmane.org/gmane.comp.lang.haskell.cafe/20106/

Peter Simons has this library:
  http://cryp.to/blockio/

BTW, where's the tutorial that Peter wrote?
  http://article.gmane.org/gmane.comp.lang.haskell.cafe/4011/

And there are other IO libraries out there. Bulat has done a lot of work on 
stream IO, I recall.


> PS: I would love to see an immutable filesystem that does not 
> allow writing to files, it only creates new files and garbage 
> collects files that have no incoming reference anymore... 
> Just like a garbage collected heap, and a bit like an OLAP 
> databases (as far as I remember my DB theory...) Besides the 
> performance bottleneck, does something like that exists?

This might interest you:
http://okmij.org/ftp/Computation/Continuations.html#zipper-fs

Alistair
*
Confidentiality Note: The information contained in this message,
and any attachments, may contain confidential and/or privileged
material. It is intended solely for the person(s) or entity to
which it is addressed. Any review, retransmission, dissemination,
or taking of any action in reliance upon this information by
persons or entities other than the intended recipient(s) is
prohibited. If you received this in error, please contact the
sender and delete the material from any computer.
*

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Simple network client

2008-01-30 Thread Peter Verswyvelen
Yes, and if I'm correct this hGetContents is used by many other functions, such 
as readFile...

As a newbie I made a nice little program that called readFile and writeFile on 
the same filename, but of course the file handle of the readFile was not closed 
yet => access denied. A nice case of getting bitten by my imperative background.

Then I tried the "seq" hack to force the handle opened by readFile to be 
closed, but that did not seem to work either. For example, the following still 
gave access denied:

main = do
  cs <- readFile "L:/Foo.txt"
  writeFile "L:/Foo.txt" $ seq (length cs) cs

This is (I guess) because the writeFile *still* happens before the seq, so the 
readFile handle is still not closed.

The following does work:

main = do
  cs <- readFile "L:/Foo.txt"
  (seq (length cs) writeFile) "L:/Foo.txt" cs

This all looks a lot like hacking a side effect :)

So I guess hGet/hGetNonBlocking/ByteString is also the correct way to solve 
this?

Thanks,
Peter

PS: I would love to see an immutable filesystem that does not allow writing to 
files, it only creates new files and garbage collects files that have no 
incoming reference anymore... Just like a garbage collected heap, and a bit 
like an OLAP databases (as far as I remember my DB theory...) Besides the 
performance bottleneck, does something like that exists?

> -Original Message-
> From: [EMAIL PROTECTED] [mailto:haskell-cafe-
> [EMAIL PROTECTED] On Behalf Of Jules Bean
> Sent: Wednesday, January 30, 2008 1:03 PM
> To: "Timo B. Hübel"
> Cc: haskell-cafe@haskell.org
> Subject: Re: [Haskell-cafe] Simple network client
> 
> Your bug here is hGetContents.
> 
> Don't use it.
> 
> Lazy IO gremlins bite once again.
> 
> Your client is waiting for the server to close the socket before it
> prints anything. But your server is waiting for the client to close the
> socket before *it* prints anything.
> 
> Just don't use hGetContents in any serious code, or any program longer
> than 4 lines.
> 
> Jules
> 
> Timo B. Hübel wrote:
> > Hello,
> >
> > I am using the very simple interactTCP example from [1] to play
> around with
> > Haskell network programming but I just can't get a simple client for
> that
> > example to work (it works like a charm with my telnet client, as
> described in
> > the article).
> >
> > This is what I am trying to do with the client:
> >
> >   main = withSocketsDo $ do
> >  hdl <- connectTo "localhost" (PortNumber 1234)
> >  hSetBuffering hdl NoBuffering
> >  hPutStr hdl "test message"
> >  res <- hGetContents hdl
> >  putStrLn (show res)
> >
> > The server looks like this:
> >
> >   interactTCP :: Int -> (String -> IO String) -> IO ()
> >   interactTCP port f = withSocketsDo $ do
> >   servSock <- listenOn $ PortNumber (fromIntegral port)
> >   waitLoop f servSock
> >
> >   waitLoop f servSock = do
> >   bracket (fmap (\(h,_,_)->h) $ accept servSock)
> >   hClose
> >   (\h -> do
> >   hSetBuffering h NoBuffering
> >   hGetContents h >>= f >>= hPutStr h)
> >   waitLoop f servSock
> >
> >   main = interactTCP 1234 (return . map toUpper)
> >
> > But is seems as some deadlocking occurs. Both programs just hang
> around doing
> > nothing. By inserting some debug output I was able to make sure that
> the
> > client successfully connects, but the data interchange just does not
> start.
> > Because the whole thing works using telnet, I suspect that I am doing
> > something fundamentally wrong in the client ...
> >
> > Any hints are greatly appreciated.
> >
> > Thanks,
> > Timo
> >
> > [1]
> >
> http://stephan.walter.name/blog/computers/programming/haskell/interactt
> cp.html
> > ___
> > Haskell-Cafe mailing list
> > Haskell-Cafe@haskell.org
> > http://www.haskell.org/mailman/listinfo/haskell-cafe
> 
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
> 
> 
> 
> --
> Internal Virus Database is out-of-date.
> Checked by AVG Free Edition.
> Version: 7.5.516 / Virus Database: 269.19.9/1239 - Release Date:
> 1/23/2008 10:24 AM


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Simple network client

2008-01-30 Thread Timo B. Hübel
On Wednesday 30 January 2008 14:09:31 you wrote:
> > This sounds good, but don't I throw away all (possible) performance gains
> > of transmitting ByteStrings directly when using show/read to convert them
> > to ordinary strings and back?
>
> Probably not all of them, but some of them, definitely.
>
> If you want to transmit an arbitrary bytestring then I'm pretty sure
> that transmitting a length word first is the way to go. An arbitrary
> bytestring can have any value in it, so there are no values left to act
> as delimiters :) You'd have to have some kind of escaping mechanism,
> like show, which is expensive.

Okay, then I will go this way. Thank you very much!

Timo
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Simple network client

2008-01-30 Thread Jules Bean

Timo B. Hübel wrote:

On Wednesday 30 January 2008 13:51:58 you wrote:

Okay, but then I have to make sure that my strings won't contain any
newline characters, right? If this is the case, another question raises
up: I am using Data.Binary to do the serialization of my data structures
to ByteString, so does anybody know if this makes guarantees about
newline characters in the resulting ByteString?
Otherwise I would go for the "transmit the length of what to
expect"-solution.

Fortunately there is an easy way to hide newlines.

Use "show"

That will wrap newlines as \n, as well as coping with other odd
characters like NULL which might upset a C library (if you're talking to
C at any point).

Then you use "read" on the far end.


This sounds good, but don't I throw away all (possible) performance gains of 
transmitting ByteStrings directly when using show/read to convert them to 
ordinary strings and back?


Probably not all of them, but some of them, definitely.

If you want to transmit an arbitrary bytestring then I'm pretty sure 
that transmitting a length word first is the way to go. An arbitrary 
bytestring can have any value in it, so there are no values left to act 
as delimiters :) You'd have to have some kind of escaping mechanism, 
like show, which is expensive.


Jules
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Simple network client

2008-01-30 Thread Timo B. Hübel
On Wednesday 30 January 2008 13:51:58 you wrote:
> > Okay, but then I have to make sure that my strings won't contain any
> > newline characters, right? If this is the case, another question raises
> > up: I am using Data.Binary to do the serialization of my data structures
> > to ByteString, so does anybody know if this makes guarantees about
> > newline characters in the resulting ByteString?
> > Otherwise I would go for the "transmit the length of what to
> > expect"-solution.
>
> Fortunately there is an easy way to hide newlines.
>
> Use "show"
>
> That will wrap newlines as \n, as well as coping with other odd
> characters like NULL which might upset a C library (if you're talking to
> C at any point).
>
> Then you use "read" on the far end.

This sounds good, but don't I throw away all (possible) performance gains of 
transmitting ByteStrings directly when using show/read to convert them to 
ordinary strings and back?

Thanks,
Timo
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Simple network client

2008-01-30 Thread Jules Bean

Timo B. Hübel wrote:

On Wednesday 30 January 2008 13:32:42 you wrote:

Timo B. Hübel wrote:

On Wednesday 30 January 2008 13:03:27 you wrote:

Just don't use hGetContents in any serious code, or any program longer
than 4 lines.

What else do you suggest? I just want to read something out of the socket
without knowing it's length beforehand (my example here used ordinary
Strings, but actually I want to do it with ByteStrings).

[...]

I strongly suspect for your example you want solution 1 and hGetLine,
though. (Which works just as well with or without ByteString)


Okay, but then I have to make sure that my strings won't contain any newline 
characters, right? If this is the case, another question raises up: I am 
using Data.Binary to do the serialization of my data structures to 
ByteString, so does anybody know if this makes guarantees about newline 
characters in the resulting ByteString? 
Otherwise I would go for the "transmit the length of what to expect"-solution.


Fortunately there is an easy way to hide newlines.

Use "show"

That will wrap newlines as \n, as well as coping with other odd 
characters like NULL which might upset a C library (if you're talking to 
C at any point).


Then you use "read" on the far end.

Otherwise, you make your protocol more sophisticated in some way, like 
"messages is ended by a line which only contains '.'", which is the SMTP 
and, AFAICR, NNTP solution to this particular sub-problem.


Of course show/read *is* one way of making your protocol more 
sophisticated. It just happens to be a really easy hack, for haskell 
users :)


Jules
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Simple network client

2008-01-30 Thread Timo B. Hübel
On Wednesday 30 January 2008 13:32:42 you wrote:
> Timo B. Hübel wrote:
> > On Wednesday 30 January 2008 13:03:27 you wrote:
> >> Just don't use hGetContents in any serious code, or any program longer
> >> than 4 lines.
> >
> > What else do you suggest? I just want to read something out of the socket
> > without knowing it's length beforehand (my example here used ordinary
> > Strings, but actually I want to do it with ByteStrings).
>
> [...]
>
> I strongly suspect for your example you want solution 1 and hGetLine,
> though. (Which works just as well with or without ByteString)

Okay, but then I have to make sure that my strings won't contain any newline 
characters, right? If this is the case, another question raises up: I am 
using Data.Binary to do the serialization of my data structures to 
ByteString, so does anybody know if this makes guarantees about newline 
characters in the resulting ByteString? 
Otherwise I would go for the "transmit the length of what to expect"-solution.

Thanks,
Timo
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Simple network client

2008-01-30 Thread Jules Bean

Timo B. Hübel wrote:

On Wednesday 30 January 2008 13:03:27 you wrote:

Just don't use hGetContents in any serious code, or any program longer
than 4 lines.


What else do you suggest? I just want to read something out of the socket 
without knowing it's length beforehand (my example here used ordinary 
Strings, but actually I want to do it with ByteStrings).


How much shall you read?

Will you wait if not that much data is available?

This is a question all network protocols have to answer!

There are two traditional solutions:

Implement a line based protocol. Read one line at a time. In that case 
hGetLine is your friend. (Actually any delimeter, but it's traditionally 
lines)


Implement a known-chunk-size protocol, either fixed to a constant N, or 
transmit a length word as the first word. In that case, the 
extraordinarly ugly and clumsy hGetBuf is your friend, but you might 
wrap it into something more comfortable.


The third, but more sophisticated answer is to use non-blocking IO, read 
 'only what is available', decide if it's enough to process, if not 
store it in some local buffer until next time. This is much more work 
and easy to implement bugs in, but you need it for true streaming 
protocols.  In that case hGetBufNonBlocking is your friend.


The vast majority of internet protocols are line based, at some level, 
and so use solution 1.


In cases 2 and 3 it happens that ByteString offers a cleaner API than 
System.IO, even if you didn't really want to use ByteString, since it 
provides hGet and hGetNonBlocking, no messing around with Ptrs.


I strongly suspect for your example you want solution 1 and hGetLine, 
though. (Which works just as well with or without ByteString)


Jules

PS "whatever you do, just don't use hGetContents" , print this out onto 
a T-shirt transfer and apply it to the front of your monitor.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Simple network client

2008-01-30 Thread Reinier Lamers

Timo B. Hübel wrote:

On Wednesday 30 January 2008 13:03:27 you wrote:
  

Just don't use hGetContents in any serious code, or any program longer
than 4 lines.



What else do you suggest? I just want to read something out of the socket 
without knowing it's length beforehand (my example here used ordinary 
Strings, but actually I want to do it with ByteStrings).


  
Either tell the receiving end how much it has to receive, or use a 
text-based protocol and getLine.


Reinier
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Simple network client

2008-01-30 Thread Timo B. Hübel
On Wednesday 30 January 2008 13:03:27 you wrote:
> Just don't use hGetContents in any serious code, or any program longer
> than 4 lines.

What else do you suggest? I just want to read something out of the socket 
without knowing it's length beforehand (my example here used ordinary 
Strings, but actually I want to do it with ByteStrings).

Thanks,
Timo
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Simple network client

2008-01-30 Thread Jules Bean

Your bug here is hGetContents.

Don't use it.

Lazy IO gremlins bite once again.

Your client is waiting for the server to close the socket before it 
prints anything. But your server is waiting for the client to close the 
socket before *it* prints anything.


Just don't use hGetContents in any serious code, or any program longer 
than 4 lines.


Jules

Timo B. Hübel wrote:

Hello,

I am using the very simple interactTCP example from [1] to play around with 
Haskell network programming but I just can't get a simple client for that 
example to work (it works like a charm with my telnet client, as described in 
the article). 


This is what I am trying to do with the client:

  main = withSocketsDo $ do
 hdl <- connectTo "localhost" (PortNumber 1234)
 hSetBuffering hdl NoBuffering
 hPutStr hdl "test message"
 res <- hGetContents hdl
 putStrLn (show res)

The server looks like this:

  interactTCP :: Int -> (String -> IO String) -> IO ()
  interactTCP port f = withSocketsDo $ do
  servSock <- listenOn $ PortNumber (fromIntegral port)
  waitLoop f servSock

  waitLoop f servSock = do
  bracket (fmap (\(h,_,_)->h) $ accept servSock)
  hClose
  (\h -> do
  hSetBuffering h NoBuffering
  hGetContents h >>= f >>= hPutStr h)
  waitLoop f servSock

  main = interactTCP 1234 (return . map toUpper)

But is seems as some deadlocking occurs. Both programs just hang around doing 
nothing. By inserting some debug output I was able to make sure that the 
client successfully connects, but the data interchange just does not start. 
Because the whole thing works using telnet, I suspect that I am doing 
something fundamentally wrong in the client ...


Any hints are greatly appreciated.

Thanks,
Timo

[1] 
http://stephan.walter.name/blog/computers/programming/haskell/interacttcp.html

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Simple network client

2008-01-29 Thread Timo B. Hübel
On Tuesday 29 January 2008 17:12:19 you wrote:
> There was a similar bug in lazy bytestring's hGetContents a while back
> which involve it waiting for a whole chunk and not returning short
> reads, but from watching the strace of this code, GHC is reading
> byte-by-byte (which is actually pretty dumb, but functions).

I have to apologize, I probably got something wrong when trying the solution 
from Mads. I did it again now and now it seems to work (apart from the client 
still waiting for more data instead of exiting, but thats probably due to the 
way the data is read).

I actually want to transmit ByteStrings in exactly this way (one request to 
the server, the server does some processing and sends a response back), but 
couldn't get it to work and therefore tried with ordinary strings. Now I can 
move forward to ByteStrings.

Thanks!
Timo
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Simple network client

2008-01-29 Thread Adam Langley
On Jan 29, 2008 6:28 AM, Timo B. Hübel <[EMAIL PROTECTED]> wrote:
> Hm, unfortunately not for me (Linux, GHC 6.8.2) ...

That's odd, because it works for me on the exact same setup.

There was a similar bug in lazy bytestring's hGetContents a while back
which involve it waiting for a whole chunk and not returning short
reads, but from watching the strace of this code, GHC is reading
byte-by-byte (which is actually pretty dumb, but functions).

Can you compile both with:
  % ghc --make file.hs

And run them with:
  % strace -o /tmp/trace ./file

(obviously, you're running strace twice, with different binaries and
output files)

and send me the resulting traces? (They'll be quite big, so I don't
know if you want to spam that whole list with them)

Cheers


AGL

-- 
Adam Langley  [EMAIL PROTECTED]
http://www.imperialviolet.org   650-283-9641
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Simple network client

2008-01-29 Thread Timo B. Hübel
On Tuesday 29 January 2008 14:44:42 Mads Lindstrøm wrote:
> If you replace the `putStrLn (show res)` with this:
>
>   mapM_ (\x -> putStr (show x) >> hFlush stdout) res
>
> it works.

Hm, unfortunately not for me (Linux, GHC 6.8.2) ...

> I _think_ the problem is that `putStrLn  (show res)` will wait until it
> has read all of res. But as the client do not know when the server is
> finished sending data, the client will wait forever.

But if this is the cause, it should happen on the server as well, because the 
call to hGetContents on the server side will also continue to wait for data.

I also suspected some laziness issues here (like both sides waiting for each 
other to start evaluating), but lazy network IO doesn't make that much sense, 
does it? If I tell the program to send something, it should send it _now_.

Any further hints are still appreciated :)

Thanks,
Timo
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Simple network client

2008-01-29 Thread Mads Lindstrøm
Hi

Timo B. Hübel wrote:
> Hello,
> 
> I am using the very simple interactTCP example from [1] to play around with 
> Haskell network programming but I just can't get a simple client for that 
> example to work (it works like a charm with my telnet client, as described in 
> the article). 
> 
> This is what I am trying to do with the client:
> 
>   main = withSocketsDo $ do
>  hdl <- connectTo "localhost" (PortNumber 1234)
>  hSetBuffering hdl NoBuffering
>  hPutStr hdl "test message"
>  res <- hGetContents hdl
>  putStrLn (show res)

If you replace the `putStrLn (show res)` with this:

  mapM_ (\x -> putStr (show x) >> hFlush stdout) res

it works.

I _think_ the problem is that `putStrLn  (show res)` will wait until it
has read all of res. But as the client do not know when the server is
finished sending data, the client will wait forever.



Greetings,

Mads Lindstrøm

> 
> The server looks like this:
> 
>   interactTCP :: Int -> (String -> IO String) -> IO ()
>   interactTCP port f = withSocketsDo $ do
>   servSock <- listenOn $ PortNumber (fromIntegral port)
>   waitLoop f servSock
> 
>   waitLoop f servSock = do
>   bracket (fmap (\(h,_,_)->h) $ accept servSock)
>   hClose
>   (\h -> do
>   hSetBuffering h NoBuffering
>   hGetContents h >>= f >>= hPutStr h)
>   waitLoop f servSock
> 
>   main = interactTCP 1234 (return . map toUpper)
> 
> But is seems as some deadlocking occurs. Both programs just hang around doing 
> nothing. By inserting some debug output I was able to make sure that the 
> client successfully connects, but the data interchange just does not start. 
> Because the whole thing works using telnet, I suspect that I am doing 
> something fundamentally wrong in the client ...
> 
> Any hints are greatly appreciated.
> 
> Thanks,
> Timo
> 
> [1] 
> http://stephan.walter.name/blog/computers/programming/haskell/interacttcp.html
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe