Re: [Haskell-cafe] Converting [Word8] to String

2005-10-03 Thread Tomasz Zielonka
On 10/2/05, Joel Reymont <[EMAIL PROTECTED]> wrote:
Folks,How do I convert a list of bytes to a string?
I assume you don't care about Unicode:

   map (Char.chr . fromIntegral)

or

   map (toEnum . fromEnum)

Best regards
Tomasz

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


Re: [Haskell-cafe] Endian conversion

2005-10-03 Thread Tomasz Zielonka
On 10/3/05, Udo Stenzel <[EMAIL PROTECTED]> wrote:
Joel Reymont wrote:> Are there any endian conversion routines for Haskell? I'm looking to> build binary packets on top of NewBinary.Binary but my data is coming> in little-endian whereas I'll need to send it out big endian.
Why don't you pull out 4 bytes and assemble them manually?  Threeshifts, logical ors and fromIntegrals aren't that much of a burden afterall.
Exactly! Network encodings for integers are precisely, mathematically
defined. Surprisingly, it is very difficult to see (it was a revelation for me
too). Perhaps the reason is that people get used to the mess in C
networking code.
Best regards
Tomasz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Short Cut / Rewrite Rules Problem in GHC

2005-10-03 Thread Chris
Hi All. I am a student and a noob to Haskell. I am having some  
trouble with an example from the paper "Playing by the rules:  
Rewriting as a practical optimisation technique in GHC" by Simon  
Peyton Jones, Andrew Tolmach and Tony Hoare, specifically, the Short- 
cut Deforestation example in section 3.1. I was trying to compile the  
following using GHC version 6.4 on Mac OS X 10.4. The definition for  
build and the rule are from the paper (the rule also appears in the  
GHC online doc in section 7.10.1).


 -
 -- BOF

 -- File: Main.hs

 module Main where

 build :: (forall b. (a->b->b) -> b -> b) -> [a]
 build' g = g (:) []

 {-# RULES
 "foldr/build"
   forall k z (g::forall b. (a->b->b) -> b -> b) .
   foldr k z (build g) = g k z
 #-}

 main  :: IO ()
 main  =  do putStr ""

 -- EOF
 -

When I enable the extensions for GHC I get the following error:

 chris$ ghc -fglasgow-exts --make Main.hs
 Chasing modules from: Main.hs
 Compiling Main ( Main.hs, Main.o )

 Main.hs:15:1: lexical error


When I don't have them enabled it gives this error:

 chris$ ghc --make Main.hs
 Chasing modules from: Main.hs
 Compiling Main ( Main.hs, Main.o )

 Main.hs:8:18: parse error on input `.'


I have also tried moving the RULES option to the top of of the file  
above "module Main", but I still get the same errors.


 Also, should the definition of build be:

 build   :: forall a. (forall b. (a -> b -> b) -> b -> b) -> [a]
 build g = g (:) []

If I try to load the Main.hs file in HUGS with the -98 option and the  
above version of build (with the forall a.), it works without a  
problem. However, it still gives the same errors in GHC.


Additionally, I tried this on a different version of GHC, 6.2.2 on a  
x86 box running Gentoo Linux, and it yielded the same results. I am  
completely lost and would greatly appreciate any help. Thanks so much.


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


Re: [Haskell-cafe] Endian conversion

2005-10-03 Thread Marc Ziegert
nice project. (except that winonly-closedsource-thing. my condolence.)
on which platform are you programming? mac? linux-ppc?

i see that you understood most of that code. 
big-endian-test: the number 1234 has two ends (like a sausage), the end with 
the 1 is the big end (1000), the 4 is the little one. if you save he number 1 
as int in little endian, then you write the bytes 01 00 00 00, and in big 
endian it is 00 00 00 01. so, if you read the first char, then it will either 
be ==1 (little) or /=1 (big).
to write that LittleEndian stuff, you only need to replace Big with Little and 
"if be then" with "if not be then". it is the question wether to use he 
function xyz0(derived) or xyzR(reverse order of bytes). i hope, that the 
compiler optimizes "if True" away.

to use the Storables, read the docu about the libs(functions)
Network.Socket(sendBufTo)
Foreign.Marshal.Utils(with)
Foreign.Storable(peekThis,peekThat)

you just need to read "LittleEndian CInt", remove that 
"LittleEndian"-constructor, work with that CInt, put the 
"BigEndian"-constructor at that CInt, write it...

maybe you need to convert LE and BE enums, too. use "(toEnum . fromEnum)" to 
convert between any enum and CInt.

good n8.
- marc


Joel Reymont wrote:
> Well, I liked that bit of Template Haskell code that Marc sent. I'm  
> now stuck trying to adapt it to read Storables :-).
> 
> It seems, on a second glance, that there's not that much to adapt. If  
> I read Marc's code correctly it "derives" Storable and uses the peek,  
> etc. methods to swap bytes around. Which means to me that so long as  
> the byte swapping methods are implemented and I try to store a  
> BigEndian or LittleEndian it would be stored correctly for me.
> 
> Is this so?
> 
> To recap, I'm trying to read binary packets from a socket and the  
> first thing I do is read the packet length. I then need to read the  
> packet body where the numbers are little or big endian. After  
> processing the packet I need to write it out and the numbers again  
> could be little or big endian.
> 
> I could read a FastString from a socket since it has IO methods but I  
> don't know how to convert the FS into a pointer suitable for  
> Storable. So much to learn :-).
> 
>  Thanks, Joel
> 
> On Oct 3, 2005, at 9:33 PM, Udo Stenzel wrote:
> 
> > Why don't you pull out 4 bytes and assemble them manually?  Three
> > shifts, logical ors and fromIntegrals aren't that much of a burden  
> > after
> > all.
> 
> --
> http://wagerlabs.com/idealab
> 
> 
> 
> 
> 
> ___
> 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] Endian conversion

2005-10-03 Thread Mark Carroll
On Mon, 3 Oct 2005, Joel Reymont wrote:

> On Oct 3, 2005, at 6:51 AM, Marc Ziegert wrote:
> 
> > data (Integral a) => BigEndian a = BigEndian a deriving  
> > (Eq,Ord,Enum,...)
> > be = $( (1::CChar)/=(unsafePerformIO $ with (1::CInt) $ peekByteOff  
> > `flip` 0) ) :: Bool
> 
> Will this always correctly determine if the platform is big-endian?  
> How does it actually work?

I don't know, having not used things like peekByteOff, but my suspicion
would be that it's rather like,

  typedef char byte;

  char cChar = 1;
  int cInt = 1;
  int be = cChar != *(((byte*) &cInt) + 0);

  printf("be = %i\n", be);

  return 0;

in C, so it's looking to see if the first byte of the int representation
of 1 isn't 1.

-- Mark

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


Re: [Haskell-cafe] Endian conversion

2005-10-03 Thread Joel Reymont
Well, I liked that bit of Template Haskell code that Marc sent. I'm  
now stuck trying to adapt it to read Storables :-).


It seems, on a second glance, that there's not that much to adapt. If  
I read Marc's code correctly it "derives" Storable and uses the peek,  
etc. methods to swap bytes around. Which means to me that so long as  
the byte swapping methods are implemented and I try to store a  
BigEndian or LittleEndian it would be stored correctly for me.


Is this so?

To recap, I'm trying to read binary packets from a socket and the  
first thing I do is read the packet length. I then need to read the  
packet body where the numbers are little or big endian. After  
processing the packet I need to write it out and the numbers again  
could be little or big endian.


I could read a FastString from a socket since it has IO methods but I  
don't know how to convert the FS into a pointer suitable for  
Storable. So much to learn :-).


Thanks, Joel

On Oct 3, 2005, at 9:33 PM, Udo Stenzel wrote:


Why don't you pull out 4 bytes and assemble them manually?  Three
shifts, logical ors and fromIntegrals aren't that much of a burden  
after

all.


--
http://wagerlabs.com/idealab





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


Re: [Haskell-cafe] Endian conversion

2005-10-03 Thread Udo Stenzel
Joel Reymont wrote:
> Are there any endian conversion routines for Haskell? I'm looking to  
> build binary packets on top of NewBinary.Binary but my data is coming  
> in little-endian whereas I'll need to send it out big endian.

Why don't you pull out 4 bytes and assemble them manually?  Three
shifts, logical ors and fromIntegrals aren't that much of a burden after
all.


Udo.
-- 
The Second Law of Thermodynamics:
If you think things are in a mess now, just wait!
-- Jim Warner


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


Re: [Haskell-cafe] Endian conversion

2005-10-03 Thread Joel Reymont


On Oct 3, 2005, at 6:51 AM, Marc Ziegert wrote:

data (Integral a) => BigEndian a = BigEndian a deriving  
(Eq,Ord,Enum,...)
be = $( (1::CChar)/=(unsafePerformIO $ with (1::CInt) $ peekByteOff  
`flip` 0) ) :: Bool


Will this always correctly determine if the platform is big-endian?  
How does it actually work?



instance (Storable a) => Storable (BigEndian a) where
 sizeOf (BigEndian a) = sizeOf a
 alignment (BigEndian a) = alignment a
 peek = if be then peek0 else peekR
  where
   peek0 (BigEndian a) = peek a
   peekR = peekByteOff `flip` 0
 peekByteOff = if be then peekByteOff0 else peekByteOffR
  where
   peekByteOff0 (BigEndian a) = peekByteOff a
   peekByteOffR (BigEndian a) i = peekByteOff a (sizeOf a - 1 - i)
...poke...


So I would need to implement the various functions from storable, right?

Also, what's the easiest way to implement LittleEndian on top of  
this? Just change peekByteOf, etc.?


Thanks, Joel

--
http://wagerlabs.com/idealab





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


[Haskell-cafe] Replacing a shovel (was Re: Endian conversion)

2005-10-03 Thread Joel Reymont
Well, I can make the problem a little more complex to give you a  
better picture of where Haskell fits in...


I need to write a simulation environment to be able to run bots  
against a poker server and reproduce this intermittent memory  
corruption that happens within it. The poker server is written in C++  
on Windows. There's no documentation and all I have is the source  
code to the communications layer of the server and an older test tool.


I'm currently in discovery mode as I need to figure out the protocol,  
the format of each packet, etc. Haskell should let me write down the  
bits of info as I discover them, as a specification of sorts. I would  
describe each packet as I learn its format, etc. Work from the top down.


Erlang would be perfect for all the binary parsing but... I  
intuitively fell that Haskell will let me "document" the hairy C++  
poker server and its non-intuitive ways.


I'm still now sure if I could write a high-performance server in  
Haskell, that's the task for another project that I have (the binary  
protocol converter/proxy) but in this particular case all I'll be  
doing is launching bots in separate threads and have them follow some  
scenarious or maybe just decide what to do using their internal  
logic. Thus I'm not too concerned with performance.


I'm putting an onus here on clarity and endowing my bots with some  
complex brains to be able to explore the hidden crannies of the  
target poker server to make it crash. It seems to me that Haskell is  
best for bot logic and documentation so it's more like using mars- 
rover-technology to explore Mars and getting stuck on a wee bit of  
sand shoveling.


Joel

On Oct 3, 2005, at 11:54 AM, Marc Ziegert wrote:

for just making IO and a little bit-conversion, i would use c++ or  
even c. for such a problem you have to be near the machine, not  
necessarily near mathematical abstraction.
there exist assembler-commands to flip endians of register-values,  
so i would just search in /usr/include/*/* for a platform  
independent c-function, and either pipe a proxy through such a  
little prog, or patch an existing proxy, like "tinyproxy".
of course, if you want to make more than just a proxy, or if you  
want to play with different languages, be welcome to use haskell.  
but remind, it is not easy to use high-developed-mars-rover- 
technology to replace a shovel for playing with sand at the beach.


--
http://wagerlabs.com/idealab





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


Re: [Haskell-cafe] Endian conversion

2005-10-03 Thread Marc Ziegert
for just making IO and a little bit-conversion, i would use c++ or even c. for 
such a problem you have to be near the machine, not necessarily near 
mathematical abstraction.
there exist assembler-commands to flip endians of register-values, so i would 
just search in /usr/include/*/* for a platform independent c-function, and 
either pipe a proxy through such a little prog, or patch an existing proxy, 
like "tinyproxy".
of course, if you want to make more than just a proxy, or if you want to play 
with different languages, be welcome to use haskell. but remind, it is not easy 
to use high-developed-mars-rover-technology to replace a shovel for playing 
with sand at the beach.

- marc

Joel Reymont wrote:
> Well, I'm looking for suggestions on how to implement this. I'll  
> basically get a chunk of data from the socket that will have things  
> little-endian and will need to send out a chunk that will have the  
> numbers big-endian.
> 
> This is a proxy server that does binary protocol conversion. It's a  
> breeze to implement in Erlang but I'm partial to Haskell and trying  
> to apply it to all sorts of problems. Please, let me know if this is  
> not the type of problem to apply Haskell to ;-).
> 
>  Thanks, Joel
> 
> On Oct 3, 2005, at 8:35 AM, Tomasz Zielonka wrote:
> 
> > Having htonl/ntohl as pure functions in Haskell would be a bit  
> > ugly, because
> > they would be defined differently on different platforms, and  
> > putting them in the
> > IO monad would make them barely usable.
> 
> --
> http://wagerlabs.com/idealab
> 
> 
> 
> 
> 
> ___
> 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] Endian conversion

2005-10-03 Thread Joel Reymont
Well, I'm looking for suggestions on how to implement this. I'll  
basically get a chunk of data from the socket that will have things  
little-endian and will need to send out a chunk that will have the  
numbers big-endian.


This is a proxy server that does binary protocol conversion. It's a  
breeze to implement in Erlang but I'm partial to Haskell and trying  
to apply it to all sorts of problems. Please, let me know if this is  
not the type of problem to apply Haskell to ;-).


Thanks, Joel

On Oct 3, 2005, at 8:35 AM, Tomasz Zielonka wrote:

Having htonl/ntohl as pure functions in Haskell would be a bit  
ugly, because
they would be defined differently on different platforms, and  
putting them in the

IO monad would make them barely usable.


--
http://wagerlabs.com/idealab





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


Re: [Haskell-cafe] Endian conversion

2005-10-03 Thread Marc Ziegert
well, fastest conversion to compute could be an assembler-command, but if we 
don't use that, it could be converted via Foreign.Storable and sth like the 
following: (i did not test it, and i hope, TH works like this...)

data (Integral a) => BigEndian a = BigEndian a deriving (Eq,Ord,Enum,...)
be = $( (1::CChar)/=(unsafePerformIO $ with (1::CInt) $ peekByteOff `flip` 0) ) 
:: Bool
instance (Storable a) => Storable (BigEndian a) where
 sizeOf (BigEndian a) = sizeOf a
 alignment (BigEndian a) = alignment a
 peek = if be then peek0 else peekR
  where
   peek0 (BigEndian a) = peek a
   peekR = peekByteOff `flip` 0
 peekByteOff = if be then peekByteOff0 else peekByteOffR
  where
   peekByteOff0 (BigEndian a) = peekByteOff a
   peekByteOffR (BigEndian a) i = peekByteOff a (sizeOf a - 1 - i)
...poke...

- marc


Tomasz Zielonka wrote:
> On 10/3/05, Joel Reymont <[EMAIL PROTECTED]> wrote:
> >
> > Folks,
> >
> > Are there any endian conversion routines for Haskell? I'm looking to
> > build binary packets on top of NewBinary.Binary but my data is coming
> > in little-endian whereas I'll need to send it out big endian.
> 
> 
> >From your question I assume you want functions like htonl / ntohl.
> I think the cleanest approach is to always have yours Ints, etc in host
> order, and place
> the endianness stuff in serialization / deserialization code, ie. on the
> Number <-> Byte
> sequence boundary.
> 
> Having htonl/ntohl as pure functions in Haskell would be a bit ugly, because
> they would be defined differently on different platforms, and putting them
> in the
> IO monad would make them barely usable.
> 
> Best regards
> Tomasz
> 
> ___
> 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