Re: [Haskell-cafe] Abstraction leak

2007-07-04 Thread Malcolm Wallace
Andrew Coppin [EMAIL PROTECTED] wrote:

 While we're on the subject... am I the first person to notice that 
 Haskell doesn't appear to have much support for fiddling with streams
 of  bits?

See
  The Bits Between The Lambdas: Binary Data in a Lazy Functional Language
  Malcolm Wallace and Colin Runciman,
  International Symposium on Memory Management, Vancouver, Canada, Oct 1998
  ftp://ftp.cs.york.ac.uk/pub/malcolm/ismm98.html

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


Re: [Haskell-cafe] Abstraction leak

2007-07-01 Thread Andrew Coppin

Bulat Ziganshin wrote:

Hello Andrew,

  

I see. So build a table of codes and bitmasks and test against that...



decodeSymbol = do
  n - returnNextNBits MaxBits  -- this operation doesn't forward input pointer!
  symbol - table1 ! n
  bits   - table2 ! symbol
  skipNBits bits
  return symbol
  


I see.

While we're on the subject... am I the first person to notice that 
Haskell doesn't appear to have much support for fiddling with streams of 
bits?


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


Re: [Haskell-cafe] Abstraction leak

2007-07-01 Thread Josef Svenningsson

On 6/30/07, Jon Cast [EMAIL PROTECTED] wrote:

On Friday 29 June 2007, Jon Cast wrote:
 Here's my solution (drawn from a library I'll be posting Real Soon Now):
snip solution

I forgot to point out that this is 75-90% drawn from a library called
Fudgets[1], which is probably the most extended practical meditation to date
on programming with lazy streams in Haskell.  Embedding that approach in a
monadic interface seems to be my own idea, though.


Koen Claessen had the same idea. He used it for designing parsers. See:
http://www.cs.chalmers.se/~koen/pubs/entry-jfp04-parser.html


Jonathan Cast
http://sourceforge.net/projects/fid-core
http://sourceforge.net/projects/fid-emacs

[1] http://www.md.chalmers.se/Cs/Research/Functional/Fudgets/


Cheers,

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


Re: [Haskell-cafe] Abstraction leak

2007-06-30 Thread Bulat Ziganshin
Hello Andrew,

Friday, June 29, 2007, 10:39:28 PM, you wrote:

 I'm writing a whole bunch of data compression programs.

me too :)  but i never used Haskell for compression itself, only for
managing archives. fast compression routines are written in C++

http://www.haskell.org/bz

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Abstraction leak

2007-06-30 Thread Andrew Coppin

Bulat Ziganshin wrote:

Hello Andrew,

Friday, June 29, 2007, 10:39:28 PM, you wrote:

  

I'm writing a whole bunch of data compression programs.



me too :)  but i never used Haskell for compression itself, only for
managing archives. fast compression routines are written in C++
  


What, you're telling me that fast software cannot be written in 
Haskell? :-P


Well anyway, speed is not my aim. My aim is to play with various 
textbook algorithms an examine how well they work for various types of 
data. As long as the code isn't *absurdly* slow that'll be just fine.


(I forget who it was, but a while back somebody pointed out the wisdom 
of using Data.Map. It certainly makes the LZW implementation about 400% 
faster! To say nothing of Huffman...)


BTW, how do the pros do Huffman coding? Presumably not by traversing 
trees of pointer-linked nodes to process things 1 bit at a time...


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


Re: [Haskell-cafe] Abstraction leak

2007-06-29 Thread Miles Sabin
Andrew Coppin wrote,
 If this was Java, you would write all these compression and
 decompression stages as stream wrappers. So you wrap the raw input
 stream with an RLE decoder, have the function read the Huffman table,
 and then take off the RLE decoder and process the rest of the stream.

Except that if the RLE decoding stream wrapper contains any internal 
buffering, then stripping it off would very likely result in data loss. 
What you actually have to do is have the RLE decoding stream wrapper 
build and return you a stream wrapper which delivers the remainder of 
the stream.

Which I think shows that the abstraction isn't leaky ... where the 
remainder starts is very much dependent on the precise encoding of the 
prefix of the stream.

Cheers,


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


Re: [Haskell-cafe] Abstraction leak

2007-06-29 Thread David Roundy
On Fri, Jun 29, 2007 at 07:39:28PM +0100, Andrew Coppin wrote:
 Now I have a problem. It's easy enough to pass the entire data stream 
 through an RLE decoder and feed that to the Huffman table deserialize 
 function, and it will give be back the table. But I now have *no clue* 
 where the table ends in the original stream!

Sounds to me like you want a parsing monad.  Generally, when you want
state, you want a monad, and the field of parsing monads is pretty mature.
You can either write up a monad of your own, or use one of the existing
ones (parsec, frisby, read).
-- 
David Roundy
Department of Physics
Oregon State University
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Abstraction leak

2007-06-29 Thread Jon Cast
On Friday 29 June 2007, Andrew Coppin wrote:
 ...and again today I found myself trying to do something that would be
 very easy in an imperative language, but I cannot think of a single good
 way of doing it in Haskell. Hopfully somebody can give me some hints.

snip long and helpful explanation

Here's my solution (drawn from a library I'll be posting Real Soon Now):

import Control.Monad
import Control.Monad.Trans

data SPMT iota omicron m alpha
  = ReturnSP alpha
   | LiftSP (m (SPMT iota omicron m alpha))
   | GetSP (iota - SPMT iota omicron m alpha))
   | PutSP omicron (SPMT iota omicron m alpha)
instance Monad m = Monad (SPMT iota omicron m) where
  return x = ReturnSP x
  ReturnSP x = f = f x
  LiftSP a = f = LiftSP (liftM (= f) a)
  GetSP a = f = GetSP (\ x - a x = f)
  PutSP x a = f = PutSP x (a = f)
instance MonadTrans (SPMT iota omicron) where
  lift a = LiftSP (liftM ReturnSP a)

getSP :: SPMT iota omicron m iota
getSP = GetSP ReturnSP

putSP :: omicron - SPMT iota omicron m ()
putSP x = PutSP x (ReturnSP ())

(^^) :: Monad m = SPMT iota omicron m alpha - SPMT omicron omicron' m beta
 - SPMT iota omicron' m beta
a ^^ ReturnSP x = ReturnSP x
a ^^ LiftSP b = LiftSP (liftM (a ^^) b)
a ^^ PutSP x b = PutSP x (a ^^ b)
LiftSP a ^^ GetSP b = LiftSP (liftM (^^ GetSP b) a)
GetSP a ^^ GetSP b = GetSP (\ x - a x ^^ GetSP b)
PutSP x a ^^ GetSP b = a ^^ b x

If the signature of SPMT suffices to write decodeRLE and decodeHeader, the 
task of applying RLE decoding just to the header can be implemented by using 
decodeRLE ^^ decodeHeader in place of just decodeHeader.  Extension to 
situations left un-implemented above I leave for your ingenuity and/or 
release of my library.

HTH.

Jonathan Cast
http://sourceforge.net/projects/fid-core
http://sourceforge.net/projects/fid-emacs
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Abstraction leak

2007-06-29 Thread Jon Cast
On Friday 29 June 2007, Jon Cast wrote:
 Here's my solution (drawn from a library I'll be posting Real Soon Now):
snip solution

I forgot to point out that this is 75-90% drawn from a library called 
Fudgets[1], which is probably the most extended practical meditation to date 
on programming with lazy streams in Haskell.  Embedding that approach in a 
monadic interface seems to be my own idea, though.

Jonathan Cast
http://sourceforge.net/projects/fid-core
http://sourceforge.net/projects/fid-emacs

[1] http://www.md.chalmers.se/Cs/Research/Functional/Fudgets/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Abstraction leak

2007-06-29 Thread Andrew Coppin

David Roundy wrote:

On Fri, Jun 29, 2007 at 07:39:28PM +0100, Andrew Coppin wrote:
  
Now I have a problem. It's easy enough to pass the entire data stream 
through an RLE decoder and feed that to the Huffman table deserialize 
function, and it will give be back the table. But I now have *no clue* 
where the table ends in the original stream!



Sounds to me like you want a parsing monad.  Generally, when you want
state, you want a monad, and the field of parsing monads is pretty mature.
You can either write up a monad of your own, or use one of the existing
ones (parsec, frisby, read).
  


Perhaps. But how do you run a parser on top of another parser? More 
importantly, how do you stack several parsers one on top of the other, 
get the top-most one to return the thing it parsed, and then make a 
completely different stack of parsers process the remainder?


I'm sure it can be done, but... I'm having trouble wrapping my mind 
around that at this time of night... :-S


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