
Well, I eventually got it to work correctly... (!) My goal is to be able to stack multiple parsers one on top of the other - but be able to *change* the stack half way through parsing if needed. This I eventually succeeded in doing. The external interface is fairly simple, but the type signatures are NOT. (!!) My basic idea was to abstract the data source that a parser gets its data from: class Source s where empty :: s x -> Bool fetch :: s x -> (x, s x) instance Source [] where -- Nice syntax... :-S empty = null fetch xs = (head xs, tail xs) Now I can define a parser type. But... uh... there's a slight glitch. What I *want* to say is Parser state in out = ... But what I ended up with is newtype Parser state src x y = Parser ((state, src x) -> (state, src x, y)) I then make Parser a monad, write some functions to get/set the state parameter, and token_get :: (Source src) => Parser state src x x token_get = Parser (\(state, tokens) -> let (t,ts) = fetch tokens in (state, ts, t)) Anyway, all of that more or less works. Then I begin the utterly psychopathic stuff: data Stack state0 src0 t0 t1 = ... instance Source (Stack state0 src0 t0) where ... stacked :: st0 -> Parser st0 src0 t0 [t1] -> st1 -> Parser st1 (Stack st0 src0 t0) t1 x -> Parser st9 src0 t0 x By this point, my brain is in total agony! >_< But, almost unbelievably, all this psychotic code actually *works*... (Well, there were a few bugs, they're fixed now.) Essentially, I have the "stacked" function, where if I do x <- stacked foo parser1 bar parser2 y <- parser3 then it runs parser2, but it uses parser1 to transform the data first. Which is what I actually wanted in the first place... Most critically, when parser2 *stops* demanding tokens, parser3 is run, picking up from where parser1 left off. (Confused yet? Wait til you see the code to implement this insanity!) One problem remains... That pesky source type. Every time I mention a parser, I have to say what kind of course object it reads from - even though all parsers work with *any* source object! (That's the whole point of the Source class.) I really want to get rid of this. (See, for example, the type signature for "stacked". Yuck!) Also, every time I write a simple parser, I get a compile-time error saying something about a "monomorphism restriction" or something... If I add an explicit type it goes away, but it's very annoying to keep typing things like test7 :: (Source src) => Parser state src Int Int and so forth. And I can't help thinking if I could just get *rid* of that stupid source type in the signature, there wouldn't be a problem... Anybody have a solution to this?

On Wednesday 04 July 2007, Andrew Coppin wrote:
Well, I eventually got it to work correctly... (!)
My goal is to be able to stack multiple parsers one on top of the other - but be able to *change* the stack half way through parsing if needed. This I eventually succeeded in doing. The external interface is fairly simple, but the type signatures are NOT. (!!)
My basic idea was to abstract the data source that a parser gets its data from:
class Source s where empty :: s x -> Bool fetch :: s x -> (x, s x)
instance Source [] where -- Nice syntax... :-S empty = null fetch xs = (head xs, tail xs)
Now I can define a parser type. But... uh... there's a slight glitch. What I *want* to say is
Parser state in out = ...
But what I ended up with is
newtype Parser state src x y = Parser ((state, src x) -> (state, src x, y))
<snip>
One problem remains... That pesky source type. Every time I mention a parser, I have to say what kind of course object it reads from - even though all parsers work with *any* source object! (That's the whole point of the Source class.) I really want to get rid of this. (See, for example, the type signature for "stacked". Yuck!) Also, every time I write a simple parser, I get a compile-time error saying something about a "monomorphism restriction" or something... If I add an explicit type it goes away, but it's very annoying to keep typing things like
test7 :: (Source src) => Parser state src Int Int
and so forth. And I can't help thinking if I could just get *rid* of that stupid source type in the signature, there wouldn't be a problem...
Anybody have a solution to this?
newtype Parser state x y = Parser (forall src. Source src => (state, src x) -> (state, src x, y)) Definition of monad functions, etc, works exactly as for your version, but this way all your parsers have polymorphic implementation types, but none has a type that trips the monomorphism restriction. There's some kind of argument here in the debate about the monomorphism restriction, but I'm not sure if it's for or against . . . [1] Jonathan Cast http://sourceforge.net/projects/fid-core http://sourceforge.net/projects/fid-emacs [1] http://www.lysator.liu.se/c/duffs-device.html

Jonathan Cast wrote:
On Wednesday 04 July 2007, Andrew Coppin wrote:
Anybody have a solution to this?
newtype Parser state x y = Parser (forall src. Source src => (state, src x) -> (state, src x, y))
...OK, anybody have a solution that works in Haskell 98?
Definition of monad functions, etc, works exactly as for your version.
Not so. In fact, doing this causes all mannar of malfunctions. First I get lots of messages of the form "Cannot (yet) use update syntax on non-Haskell98 types." Then I get lots of "Cannot use function 'foo' as a selector." And then I get "My brain has exploded. I can't handle pattern bindings in existentially-quantified type constructors." (?!) And after that I get "Type variable 'bar' escapes pattern binding." And finally, after I correct all of those, I get an error saying that the compiler can't match [the hidden type variable] against [some suitable type for that variable]. And in a pattern of all things! (Surely if it's not the right type at runtime, it should generate an exception, just like if you use the wrong constructor...?) In all, the whole thing just malfunctions horribly and I can get no useful work done! >_< So my next plan was to write the code as normal, and then create a front-end module which "hides" all the messy types. But then I just get a whole bunch of "escaping type variable" errors again. Basically everything I tried make the code drastically more complicated, and even *then* certain parts of it (most especially the stack function) wouldn't compile. So *neeer* :-P

On Thursday 05 July 2007, Andrew Coppin wrote:
Jonathan Cast wrote:
On Wednesday 04 July 2007, Andrew Coppin wrote:
Anybody have a solution to this?
newtype Parser state x y = Parser (forall src. Source src => (state, src x) -> (state, src x, y))
...OK, anybody have a solution that works in Haskell 98?
Rank-2 types are perhaps /the/ most common, widely accepted extension to Haskell 98, after the approved addendum for FFI and the draft addendum for hierarchical modules. I would really be concerned about using them (it's certainly not like they're going to just disappear on you one day, like say functional dependencies almost certainly will). But that's just me.
Definition of monad functions, etc, works exactly as for your version.
Not so.
In fact, doing this causes all mannar of malfunctions. First I get lots of messages of the form
"Cannot (yet) use update syntax on non-Haskell98 types."
Then I get lots of
"Cannot use function 'foo' as a selector."
And then I get
"My brain has exploded. I can't handle pattern bindings in existentially-quantified type constructors."
(?!)
And after that I get
"Type variable 'bar' escapes pattern binding."
And finally, after I correct all of those, I get an error saying that the compiler can't match [the hidden type variable] against [some suitable type for that variable]. And in a pattern of all things! (Surely if it's not the right type at runtime, it should generate an exception, just like if you use the wrong constructor...?)
Just a side point but: how would it know? Leaving aside the dictionary-passing used for type classes, Haskell has (and has always had) a type-erasure semantics, which rules out runtime type errors.
In all, the whole thing just malfunctions horribly and I can get no useful work done! >_<
So my next plan was to write the code as normal, and then create a front-end module which "hides" all the messy types. But then I just get a whole bunch of "escaping type variable" errors again.
Basically everything I tried make the code drastically more complicated, and even *then* certain parts of it (most especially the stack function) wouldn't compile.
So *neeer* :-P
My first thought is that surely you must have said newtype Parser state x y = forall src. Source src => Parser ((state, src x) -> (state, src x, y)) when you meant newtype Parser state x y = Parser (forall src. Source src => (state, src x) -> (state, src x, y)) The relative order of the constructor name and the forall is very important! If you got the answer right, I can't see why you'd be getting unmistakable existential-type errors; there are no existential quantifiers in my proposal. But I'll try to implement it myself and see what I get. Jonathan Cast http://sourceforge.net/projects/fid-core http://sourceforge.net/projects/fid-emacs

Jonathan Cast wrote:
On Thursday 05 July 2007, Andrew Coppin wrote:
...OK, anybody have a solution that works in Haskell 98?
Rank-2 types are perhaps /the/ most common, widely accepted extension to Haskell 98, after the approved addendum for FFI and the draft addendum for hierarchical modules. I would really be concerned about using them (it's certainly not like they're going to just disappear on you one day, like say functional dependencies almost certainly will). But that's just me.
Personally, I just try to avoid *all* language extensions - mainly because most of them are utterly incomprehensible. (But then, perhaps that's just because they all cover extremely rare edge cases?) MPTCs and ATs look useful. The rest... hmm. If I ever figure out what they do, maybe I can comment.
And finally, after I correct all of those, I get an error saying that the compiler can't match [the hidden type variable] against [some suitable type for that variable]. And in a pattern of all things! (Surely if it's not the right type at runtime, it should generate an exception, just like if you use the wrong constructor...?)
Just a side point but: how would it know? Leaving aside the dictionary-passing used for type classes, Haskell has (and has always had) a type-erasure semantics, which rules out runtime type errors.
Usually if you have something like let (Foo x) = process x y z and it turns out that the 'process' function returns another constructor, you get an error. Well you'd expect the same thing to happen if the result type happens to be a 'hidden' type. But apparently not...
So *neeer* :-P
My first thought is that surely you must have said
newtype Parser state x y = forall src. Source src => Parser ((state, src x) -> (state, src x, y))
when you meant
newtype Parser state x y = Parser (forall src. Source src => (state, src x) -> (state, src x, y))
The relative order of the constructor name and the forall is very important!
Care to explain what's different about these apparently identical declarations?

On Thursday 05 July 2007, Andrew Coppin wrote:
Jonathan Cast wrote:
On Thursday 05 July 2007, Andrew Coppin wrote:
...OK, anybody have a solution that works in Haskell 98?
Rank-2 types are perhaps /the/ most common, widely accepted extension to Haskell 98, after the approved addendum for FFI and the draft addendum for hierarchical modules. I would really be concerned about using them (it's certainly not like they're going to just disappear on you one day, like say functional dependencies almost certainly will). But that's just me.
Personally, I just try to avoid *all* language extensions - mainly because most of them are utterly incomprehensible.
Ah, there's your problem :)
(But then, perhaps that's just because they all cover extremely rare edge cases?)
I wouldn't call rank-2 types extremely rare . . . <snip>
So *neeer* :-P
My first thought is that surely you must have said
newtype Parser state x y = forall src. Source src => Parser ((state, src x) -> (state, src x, y))
when you meant
newtype Parser state x y = Parser (forall src. Source src => (state, src x) -> (state, src x, y))
The relative order of the constructor name and the forall is very important!
Care to explain what's different about these apparently identical declarations?
Sure. Given newtype Parser0 state x y = forall src. Source src => Parser0 ((state, src x) -> (state, src x, y)) we get Parser0 :: forall src. Source src => ((state, src x) -> (state, src x, y)) -> Parser0 state x y which type assignment is isomorphic to (note: not legal Haskell!) Parser0 :: (exists src. Source src => (state, src x) -> (state, src x, y)) -> Parser0 state x y Given newtype Parser1 state x y = Parser1 (forall src. Source src => (state, src x) -> (state, src x, y)) we get Parser1 :: (forall src. Source src => (state, src x) -> (state, src x, y)) -> Parser state x y The key difference is in the quantifier in the type of the constructor's argument. The exists quantifier (on types) is a tupling operator; Parser0 takes three arguments: a type (elided at run time!), an instance for the Source class (not elided at run time!), and a function implementing the parser. The forall quantifier is a function-forming operator; Parser1 takes one argument, which is a function on a type (elided at run time!) and an instance for the Source class (not elided at run time!), yielding a function implementing the parser. Using a (thoroughly invalid Haskell) record syntax, we could write the two versions Parser0 :: { type src :: *, dict :: Source src, fun :: (state, src x) -> (state, src x, y)} -> Parser0 state x y Parser1 :: ({ type src :: *, dict :: Source src, input :: (state, src x)} -> (state, src x, y)) -> Parser1 state x y which may make the distinction a bit clearer (or not). Jonathan Cast http://sourceforge.net/projects/fid-core http://sourceforge.net/projects/fid-emacs

Jonathan Cast wrote:
I wouldn't call rank-2 types extremely rare . . .
Well now, my parser is annoyingly clunky to use, but it *works*. However, I just found something where it seems to be *impossible* to write the necessary code without rank-2 types... I tried to write this type: data Encoder2 = Encoder2 {stage1 :: [Word8] -> x, stage2 :: x -> [Word8] -> [Word8]} However, that doesn't work. All type variables on the right must appear on the left: data Encoder2 x = Encoder2 {stage1 :: [Word8] -> x, stage2 :: x -> [Word8] -> [Word8]} Now I have a problem. I want to put several of these puppies into a big list - and I do *not* want to force the type variable 'x' to be the same in all cases! (Although one can easily imagine situations where you might want this.) So as of now, my code uses rank-2 types - despite the fact that I don't actually know what a rank-2 type *is* yet! o_O This is rather troubling...

On Jul 8, 2007, at 3:21 , Andrew Coppin wrote:
this.) So as of now, my code uses rank-2 types - despite the fact that I don't actually know what a rank-2 type *is* yet! o_O This is rather troubling...
Bah --- I use monads all the time and still don't have much of a clue about category theory. :) (For that matter, I can drive a car without understanding what's going on under the hood.) -- 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

Brandon S. Allbery KF8NH wrote:
On Jul 8, 2007, at 3:21 , Andrew Coppin wrote:
this.) So as of now, my code uses rank-2 types - despite the fact that I don't actually know what a rank-2 type *is* yet! o_O This is rather troubling...
Bah --- I use monads all the time and still don't have much of a clue about category theory. :) (For that matter, I can drive a car without understanding what's going on under the hood.)
Aye, you drive a car without knowing how it works - but it was put together by some people who *do* know these things. Would you drive a car you built yourself? ;-)

On Jul 8, 2007, at 8:12 , Andrew Coppin wrote:
Brandon S. Allbery KF8NH wrote:
On Jul 8, 2007, at 3:21 , Andrew Coppin wrote:
this.) So as of now, my code uses rank-2 types - despite the fact that I don't actually know what a rank-2 type *is* yet! o_O This is rather troubling...
Bah --- I use monads all the time and still don't have much of a clue about category theory. :) (For that matter, I can drive a car without understanding what's going on under the hood.)
Aye, you drive a car without knowing how it works - but it was put together by some people who *do* know these things. Would you drive a car you built yourself? ;-)
No :) --- but depending on what you're doing, you can use rank-2 types without knowing what's under the hood. In fact, I'd say the fact that you're using them is evidence of that. (Aside --- looking at your problem description, I wonder if GADTs would be a better fit.) -- 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

Brandon S. Allbery KF8NH wrote:
On Jul 8, 2007, at 8:12 , Andrew Coppin wrote:
Aye, you drive a car without knowing how it works - but it was put together by some people who *do* know these things. Would you drive a car you built yourself? ;-)
No :) --- but depending on what you're doing, you can use rank-2 types without knowing what's under the hood. In fact, I'd say the fact that you're using them is evidence of that.
(Aside --- looking at your problem description, I wonder if GADTs would be a better fit.)
Oh, I don't mind not knowing how rank-2 types are *implemented*. ;-) But it would be nice to know what they *are*... :-S (Thus far, they just seem to be some incomprehensible syntax that makes the compiler stop complaining. In particular, I have no idea what the difference between rank-2, rank-N and existentially quantified is...)

Andrew Coppin wrote:
Oh, I don't mind not knowing how rank-2 types are *implemented*. ;-) But it would be nice to know what they *are*... :-S
(Thus far, they just seem to be some incomprehensible syntax that makes the compiler stop complaining. In particular, I have no idea what the difference between rank-2, rank-N and existentially quantified is...)
Most Haskell extensions are more like restriction removals from a application programmer's point of view. If you are fully ignorant of the matter and never realized there was a restriction, you have no reason to fear the removal of the restriction, since it enables you to stay ignorant of the matter. All you have to do is to pass some flag to the compiler for historical reasons. (Ok, there is the question of portability to other compilers...) The idea about higher-ranked types is to allow explicit forall keywords in types wherever you like. The restriction about rank-1-types is to disallow forall keywords almost everywhere. So higher-ranked types aren't a edge-case extension, they are a sensible lifting of some edge-case restriction. (Of course, for compiler writers and the like, lifting this restrictions means extending the type system and underlying theory. But why should you care?) So instead of learning about higher-ranked types, I would learn about the forall keyword, getting higher-ranked types for free, by using it in some former illegal positions out of ignorance of the former restriction. Most programming language extensions seem to arise like this: Wouldn't it be nice if I could write this and it would mean that. Maybe if I steal something from category theory, it could be possible... Tillmann

Hello Andrew, Sunday, July 8, 2007, 4:31:32 PM, you wrote:
Oh, I don't mind not knowing how rank-2 types are *implemented*. ;-) But it would be nice to know what they *are*... :-S
concrete types are rank-0: sin :: Double->Double polymorphic types are rank-1: length :: forall a . [a] -> Int functions which arguments are rank-1 types are rank-2: f :: (forall a . [a] -> Int) -> Int and so on. rank-2 and rank-N considered separately because it's easier to implement only rank-2 polymorphism and some compilers stops here (and rank-2 polymorphism used in ST monad which is pretty standard feature, while higher-rank functions are rarely required) -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

On Sunday 08 July 2007, Andrew Coppin wrote:
Jonathan Cast wrote:
I wouldn't call rank-2 types extremely rare . . .
Well now, my parser is annoyingly clunky to use, but it *works*. However, I just found something where it seems to be *impossible* to write the necessary code without rank-2 types...
I tried to write this type:
data Encoder2 = Encoder2 {stage1 :: [Word8] -> x, stage2 :: x -> [Word8] -> [Word8]}
However, that doesn't work. All type variables on the right must appear on the left:
data Encoder2 x = Encoder2 {stage1 :: [Word8] -> x, stage2 :: x -> [Word8] -> [Word8]}
Now I have a problem. I want to put several of these puppies into a big list - and I do *not* want to force the type variable 'x' to be the same in all cases! (Although one can easily imagine situations where you might want this.) So as of now, my code uses rank-2 types - despite the fact that I don't actually know what a rank-2 type *is* yet! o_O This is rather troubling...
I think surely you're using existential data types rather than rank-2 types. Existential types: each application of Encoder2 is to arguments which require a specific value of x. Rank-2 types (polymorphic fields, actually): each application of Encoder2 is to arguments which work with any value of x. Jonathan Cast http://sourceforge.net/projects/fid-core http://sourceforge.net/projects/fid-emacs

Jonathan Cast wrote:
I think surely you're using existential data types rather than rank-2 types.
You expect *me* to know?
Existential types: each application of Encoder2 is to arguments which require a specific value of x.
Rank-2 types (polymorphic fields, actually): each application of Encoder2 is to arguments which work with any value of x.
All I know is it didn't compile, so I added {-# LANGUAGE Rank2Types #-}, and now it works. *shrugs*

On Sunday 08 July 2007, Andrew Coppin wrote:
Jonathan Cast wrote:
I think surely you're using existential data types rather than rank-2 types.
You expect *me* to know?
Surely not :) That's why I tried briefly explaining the ideas again.
Existential types: each application of Encoder2 is to arguments which require a specific value of x.
Rank-2 types (polymorphic fields, actually): each application of Encoder2 is to arguments which work with any value of x.
All I know is it didn't compile, so I added {-# LANGUAGE Rank2Types #-}, and now it works. *shrugs*
If you're happy, then I guess I can accept the situation. I think you'll trip over the distinction again, but that's just me. Jonathan Cast http://sourceforge.net/projects/fid-core http://sourceforge.net/projects/fid-emacs

Jonathan Cast wrote:
On Sunday 08 July 2007, Andrew Coppin wrote:
Jonathan Cast wrote:
I think surely you're using existential data types rather than rank-2 types.
You expect *me* to know?
Surely not :) That's why I tried briefly explaining the ideas again.
LOL! Thanks...
All I know is it didn't compile, so I added {-# LANGUAGE Rank2Types #-}, and now it works. *shrugs*
If you're happy, then I guess I can accept the situation. I think you'll trip over the distinction again, but that's just me.
I must admit, the code compiles, but I have not yet attempted to *use* it for anything... (It's the code for supporting 2-pass encoders, and I haven't written any yet.)

andrewcoppin:
Jonathan Cast wrote:
On Thursday 05 July 2007, Andrew Coppin wrote:
...OK, anybody have a solution that works in Haskell 98?
Rank-2 types are perhaps /the/ most common, widely accepted extension to Haskell 98, after the approved addendum for FFI and the draft addendum for hierarchical modules. I would really be concerned about using them (it's certainly not like they're going to just disappear on you one day, like say functional dependencies almost certainly will). But that's just me.
Personally, I just try to avoid *all* language extensions - mainly because most of them are utterly incomprehensible. (But then, perhaps that's just because they all cover extremely rare edge cases?)
Some cover edge cases, some are just useful. What about: * the FFI * bang patterns * pattern guards * newtype deriving Surely, fairly simple, useful. Used a lot? :-) -- Don

On Fri, Jul 06, 2007 at 10:56:43AM +1000, Donald Bruce Stewart wrote:
andrewcoppin:
Jonathan Cast wrote:
On Thursday 05 July 2007, Andrew Coppin wrote:
...OK, anybody have a solution that works in Haskell 98?
Rank-2 types are perhaps /the/ most common, widely accepted extension to Haskell 98, after the approved addendum for FFI and the draft addendum for hierarchical modules. I would really be concerned about using them (it's certainly not like they're going to just disappear on you one day, like say functional dependencies almost certainly will). But that's just me.
Personally, I just try to avoid *all* language extensions - mainly because most of them are utterly incomprehensible. (But then, perhaps that's just because they all cover extremely rare edge cases?)
Some cover edge cases, some are just useful. What about:
* the FFI * bang patterns * pattern guards * newtype deriving
Surely, fairly simple, useful. Used a lot? :-)
How about . in module names? Stefan

On Friday 06 July 2007, Andrew Coppin wrote:
Stefan O'Rear wrote:
How about . in module names?
Now I'm almost *certain* that's now officially "in" the language... ;-)
Nope. Never made it past candidate status (or version 0.0, for that matter). http://www.haskell.org/hierarchical-modules/ Jonathan Cast http://sourceforge.net/projects/fid-core http://sourceforge.net/projects/fid-emacs

Donald Bruce Stewart wrote:
andrewcoppin:
Personally, I just try to avoid *all* language extensions - mainly because most of them are utterly incomprehensible. (But then, perhaps that's just because they all cover extremely rare edge cases?)
Some cover edge cases, some are just useful. What about:
* the FFI * bang patterns * pattern guards * newtype deriving
Surely, fairly simple, useful. Used a lot? :-)
* The FFI - isn't that now officially "in" the language? (I thought there was an official report amendment.) Either way, I can't do C, so... it looks pretty incomprehensible from here. ;-) * Bang patterns - what's that? * Pattern guards - that's not in the language? * Newtype deriving - what's that?

On Friday 06 July 2007, Andrew Coppin wrote:
Donald Bruce Stewart wrote:
andrewcoppin:
Personally, I just try to avoid *all* language extensions - mainly because most of them are utterly incomprehensible. (But then, perhaps that's just because they all cover extremely rare edge cases?)
Some cover edge cases, some are just useful. What about:
* the FFI * bang patterns * pattern guards * newtype deriving
Surely, fairly simple, useful. Used a lot? :-)
* The FFI - isn't that now officially "in" the language? (I thought there was an official report amendment.) Either way, I can't do C, so... it looks pretty incomprehensible from here. ;-)
It's in Haskell, but not Haskell 98:
The benefit of a H98 Addendum over any random language extension provided by some Haskell implementation is that a H98 Addendum is a standardised design, and programs coded against such an addendum can be expected to be portable across implementations that support this standard. Generally, implementations of H98 are not required to implement all H98 ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ Addenda, ^^^^^^^ but if such an implementation does provide a feature that is covered by an addendum, it is expected that this extension conforms to that addendum (in the same way as it is expected to abide by the H98 language definition).
http://haskell.org/haskellwiki/Language_and_library_specification
* Bang patterns - what's that?
If you stick a ! in front of a variable in a pattern, or in front of a pattern in a let-binding, whatever that variable is getting bound to, or whatever that pattern is getting matched against, is evaluated before the binding takes place (rather than being suspended in a thunk, as normal). So if you say foldl' f z [] = z foldl' f !z (x:xn) = foldl' f (f z x) xn foldl' is always strict in its second argument (which produces a tremendous speed-up; compare foldl (+) 0 with foldl' (+) 0 as definitions of sum).
* Pattern guards - that's not in the language?
Nope. Not even a candidate extension. (I assume you know that pattern guards are guards of the form -- | Cut-off subtraction function cutOffSub :: Integegral alpha => alpha -> alpha -> Maybe alpha cutOffSub x y = do let d = x - y guard $ d >= 0 return d genericDrop :: Integral int => int -> [alpha] -> [alpha] genericDrop _ [] = [] genericDrop 0 xn = [] genericDrop n (x:xn) | Just n' <- cutOffSub n 1 = genericDrop n' xn ^^^^^^^^^^^^^^^^^^^^^^^^ pattern guard Guards on case expression patterns /are/ part of the language, but isn't what is meant by `pattern guards'.)
* Newtype deriving - what's that?
Given that C is a (well-behaved) type class, and T is an instance of that class, newtype S = S T deriving C will always make S and T isomorphic in C in GHC. Exceptions: classes too funky for GHC to figure out what the class methods for S should be, and Read and Show, which by the definition of deriving (and the expectations of 90% of the classes' users) lack isomorphic instances entirely. So, we can define the RWS monad as newtype RWS r w s alpha = RWS (ReaderT r (WriterT w (State s)) alpha) deriving Monad for example. Jonathan Cast http://sourceforge.net/projects/fid-core http://sourceforge.net/projects/fid-emacs

Hello Andrew, Thursday, July 5, 2007, 11:45:14 PM, you wrote:
Personally, I just try to avoid *all* language extensions - mainly because most of them are utterly incomprehensible. (But then, perhaps that's just because they all cover extremely rare edge cases?)
MPTCs and ATs look useful. The rest... hmm. If I ever figure out what they do, maybe I can comment.
but afair you don't yet have too much experience even with H98 language? from my POV, H98 as is useful for learning, but not for real apps. there is wide common subset of GHC and Hugs language extensions and this set (with exception for FD) will probably become new Haskell' standard one problem of Haskell popularity is that language is rather complex to learn. but one doesn't need to learn it all from the beginning. in my *application* program i don't used even type classes but when i've started to write general-purpose libs, aspiration to develop as general solution as possible quickly leads to using all kinds of Haskell type hackery -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

but afair you don't yet have too much experience even with H98 language? from my POV, H98 as is useful for learning, but not for real apps. there is wide common subset of GHC and Hugs language extensions and this set (with exception for FD) will probably become new Haskell' standard
The problem I face is that most (all?) Haskell books I could find deal with Haskell 98... Are there any books out that cover the "modern" Haskell extensions? Peter -----Original Message----- From: haskell-cafe-bounces@haskell.org [mailto:haskell-cafe-bounces@haskell.org] On Behalf Of Bulat Ziganshin Sent: Friday, July 06, 2007 10:33 To: Andrew Coppin Cc: haskell-cafe@haskell.org Subject: Re[2]: [Haskell-cafe] A very nontrivial parser Hello Andrew, Thursday, July 5, 2007, 11:45:14 PM, you wrote:
Personally, I just try to avoid *all* language extensions - mainly because most of them are utterly incomprehensible. (But then, perhaps that's just because they all cover extremely rare edge cases?)
MPTCs and ATs look useful. The rest... hmm. If I ever figure out what they do, maybe I can comment.
but afair you don't yet have too much experience even with H98 language? from my POV, H98 as is useful for learning, but not for real apps. there is wide common subset of GHC and Hugs language extensions and this set (with exception for FD) will probably become new Haskell' standard one problem of Haskell popularity is that language is rather complex to learn. but one doesn't need to learn it all from the beginning. in my *application* program i don't used even type classes but when i've started to write general-purpose libs, aspiration to develop as general solution as possible quickly leads to using all kinds of Haskell type hackery -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe No virus found in this incoming message. Checked by AVG Free Edition. Version: 7.5.476 / Virus Database: 269.10.1/888 - Release Date: 06/07/2007 06:36 No virus found in this outgoing message. Checked by AVG Free Edition. Version: 7.5.476 / Virus Database: 269.10.1/888 - Release Date: 06/07/2007 06:36

Hello peterv,
The problem I face is that most (all?) Haskell books I could find deal with Haskell 98... Are there any books out that cover the "modern" Haskell extensions?
chapter 7 of ghc manual, *old* hugs manual, and hundreds of papers on haskell site :) -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

bf3:
but afair you don't yet have too much experience even with H98 language? from my POV, H98 as is useful for learning, but not for real apps. there is wide common subset of GHC and Hugs language extensions and this set (with exception for FD) will probably become new Haskell' standard
The problem I face is that most (all?) Haskell books I could find deal with Haskell 98... Are there any books out that cover the "modern" Haskell extensions?
Not yet! (But see realworldhaskell.org... :) To make up for it we have a mass of online material: The amazing Haskell wikibook * http://en.wikibooks.org/wiki/Haskell All the Haskell bloggers, sorted by topic * http://haskell.org/haskellwiki/Blog_articles Collected research papers about Haskell, by topic * http://haskell.org/haskellwiki/Research_papers Wiki articles, by category * http://haskell.org/haskellwiki/Category:Haskell Books that we do have * http://haskell.org/haskellwiki/Books_and_tutorials -- Don

dons:
bf3:
but afair you don't yet have too much experience even with H98 language? from my POV, H98 as is useful for learning, but not for real apps. there is wide common subset of GHC and Hugs language extensions and this set (with exception for FD) will probably become new Haskell' standard
The problem I face is that most (all?) Haskell books I could find deal with Haskell 98... Are there any books out that cover the "modern" Haskell extensions?
Not yet! (But see realworldhaskell.org... :)
To make up for it we have a mass of online material:
The amazing Haskell wikibook * http://en.wikibooks.org/wiki/Haskell
All the Haskell bloggers, sorted by topic * http://haskell.org/haskellwiki/Blog_articles
Collected research papers about Haskell, by topic * http://haskell.org/haskellwiki/Research_papers
Wiki articles, by category * http://haskell.org/haskellwiki/Category:Haskell
Books that we do have * http://haskell.org/haskellwiki/Books_and_tutorials
Oh, Bulat's right. Also: GHC User's guide -- type system extensions * http://www.haskell.org/ghc/docs/latest/html/users_guide/type-extensions.html GHC User's guide -- syntax extensions * http://www.haskell.org/ghc/docs/latest/html/users_guide/syntax-extns.html Specific extensions: GADTs * http://www.haskell.org/ghc/docs/latest/html/users_guide/gadt.html Bang patterns * http://www.haskell.org/ghc/docs/latest/html/users_guide/sec-bang-patterns.ht... Special primops * http://www.haskell.org/ghc/docs/latest/html/users_guide/special-ids.html Parallel Haskell * http://www.haskell.org/ghc/docs/latest/html/users_guide/lang-parallel.html FFI * http://www.haskell.org/ghc/docs/latest/html/users_guide/ffi.html Its all there somewhere.

Yes, thanks, but those internet pages don't read that well on the train to work ;) For example, for the brand new F# language I bought the book http://www.amazon.com/Foundations-F-Robert-Pickering/dp/1590597575 which covers almost everything you need to create real-world applications, from GUIs to databases to 2D/3D graphics to custom languages. Okay, it's a bit buggy here and there, but it's a great overview. Ah well, I'll abuse the printer at work to print out those internet pages then; somehow reading from a computer screen just doesn't work for me. -----Original Message----- From: Donald Bruce Stewart [mailto:dons@cse.unsw.edu.au] Sent: Friday, July 06, 2007 11:22 To: peterv Cc: 'Bulat Ziganshin'; haskell-cafe@haskell.org Subject: Re: [Haskell-cafe] RE: Modern Haskell books (was "Re: A very nontrivial parser") dons:
bf3:
but afair you don't yet have too much experience even with H98 language? from my POV, H98 as is useful for learning, but not for real
apps. there is wide common subset of GHC and Hugs language extensions and this set (with exception for FD) will probably become new Haskell' standard
The problem I face is that most (all?) Haskell books I could find deal with Haskell 98... Are there any books out that cover the "modern" Haskell extensions?
Not yet! (But see realworldhaskell.org... :)
To make up for it we have a mass of online material:
The amazing Haskell wikibook * http://en.wikibooks.org/wiki/Haskell
All the Haskell bloggers, sorted by topic * http://haskell.org/haskellwiki/Blog_articles
Collected research papers about Haskell, by topic * http://haskell.org/haskellwiki/Research_papers
Wiki articles, by category * http://haskell.org/haskellwiki/Category:Haskell
Books that we do have * http://haskell.org/haskellwiki/Books_and_tutorials
Oh, Bulat's right. Also: GHC User's guide -- type system extensions * http://www.haskell.org/ghc/docs/latest/html/users_guide/type-extensions.html GHC User's guide -- syntax extensions * http://www.haskell.org/ghc/docs/latest/html/users_guide/syntax-extns.html Specific extensions: GADTs * http://www.haskell.org/ghc/docs/latest/html/users_guide/gadt.html Bang patterns * http://www.haskell.org/ghc/docs/latest/html/users_guide/sec-bang-patterns.ht ml Special primops * http://www.haskell.org/ghc/docs/latest/html/users_guide/special-ids.html Parallel Haskell * http://www.haskell.org/ghc/docs/latest/html/users_guide/lang-parallel.html FFI * http://www.haskell.org/ghc/docs/latest/html/users_guide/ffi.html Its all there somewhere. No virus found in this incoming message. Checked by AVG Free Edition. Version: 7.5.476 / Virus Database: 269.10.1/888 - Release Date: 06/07/2007 06:36 No virus found in this outgoing message. Checked by AVG Free Edition. Version: 7.5.476 / Virus Database: 269.10.1/888 - Release Date: 06/07/2007 06:36

Hello peterv, Friday, July 6, 2007, 2:03:24 PM, you wrote:
For example, for the brand new F# language I bought the book http://www.amazon.com/Foundations-F-Robert-Pickering/dp/1590597575 which covers almost everything you need to create real-world applications, from GUIs to databases to 2D/3D graphics to custom languages. Okay, it's a bit buggy here and there, but it's a great overview.
as we many times said, there is need in two rather different books: one about "advanced haskell type hackery", which covers type and syntax extensions, smart ways of using types/classes, type system theory and so on. it is one we talked about in this thread. now this sort of information spread in thin air - places mentioned by Dons and me, haskell mail lists and so on another, very different - "real world haskell" about commercial and semi-commercial program development. it should cover gui, db, web, networking, multithreading, parsing and other practical topics, focusing on libraries, tools, and changing programmers' thinking. currently this information is even more spread - you can read 15-year old books such as SOE and SICP for learning FP programming style, and various docs and tutorials for info about using each tool and library -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Andrew Coppin wrote:
Personally, I just try to avoid *all* language extensions - mainly because most of them are utterly incomprehensible. (But then, perhaps that's just because they all cover extremely rare edge cases?)
Haskell is an extremely rare edge case to begin with. Non-strict (most implementations lazy): rarely useful if you ask the mainstream. Static typing: extreme paranoia. Purely functional: vocal minority of edgy people. Haskell syntax: "map f xs" is utterly incomprehensible to both the mainstream "why not map(f,xs)" and the Schemers "why not (map f xs)". Great way to alienate everyone out there. Haskell is its own niche. Every aspect of it tries very hard to be alternative (as in "alternative medicine") to some existing camp (and therefore considered a nutcase by that camp), and the whole is alternative to all existing camps. Haskell is a truly edgy language.

trebla:
Andrew Coppin wrote:
Personally, I just try to avoid *all* language extensions - mainly because most of them are utterly incomprehensible. (But then, perhaps that's just because they all cover extremely rare edge cases?)
Haskell is an extremely rare edge case to begin with.
Non-strict (most implementations lazy): rarely useful if you ask the mainstream.
Static typing: extreme paranoia.
Purely functional: vocal minority of edgy people.
Haskell syntax: "map f xs" is utterly incomprehensible to both the mainstream "why not map(f,xs)" and the Schemers "why not (map f xs)". Great way to alienate everyone out there.
Give #haskell is a far larger community than: #lisp #erlang #scheme #ocaml As well as #java #javascript #ruby #lua #d #perl6 Maybe we need to reconsider where the (FP) mainstream is now? :-) -- Don

Donald Bruce Stewart wrote:
Give #haskell is a far larger community than:
#lisp #erlang #scheme #ocaml
As well as
#java #javascript #ruby #lua #d #perl6
Maybe we need to reconsider where the (FP) mainstream is now? :-)
I don't know. #math is larger than #accounting. Is it because math is more mainstream than accounting? I bet it is because math is more fringe, and so more people ask for help, and mathophiles are less busy. #math is comparable in size to #haskell.

trebla:
Donald Bruce Stewart wrote:
Give #haskell is a far larger community than:
#lisp #erlang #scheme #ocaml
As well as
#java #javascript #ruby #lua #d #perl6
Maybe we need to reconsider where the (FP) mainstream is now? :-)
I don't know. #math is larger than #accounting. Is it because math is more mainstream than accounting? I bet it is because math is more
math is more *interesting* than accounting? :-) -- Don

On Sat, 2007-07-07 at 15:08 +1000, Donald Bruce Stewart wrote: . . .
I don't know. #math is larger than #accounting. Is it because math is more mainstream than accounting? I bet it is because math is more
math is more *interesting* than accounting? :-)
If we gotta have a theory, I'll go with this one! -- Bill Wood

Donald Bruce Stewart wrote:
trebla:
I don't know. #math is larger than #accounting. Is it because math is more mainstream than accounting? I bet it is because math is more
math is more *interesting* than accounting? :-)
With all due respect to accounting, which is a fine profession and a great contributor to society, it is still pretty much secular. Math and Haskell are more ideal interests. That is why we like them, and that is also why they are less known.

On Sat, 2007-07-07 at 13:39 +1000, Donald Bruce Stewart wrote:
Give #haskell is a far larger community than:
Well, Haskell clearly has a well developed IRC community. Using Google to search Usenet posts in 2007: Haskell: 21000 Lisp: 29000 Erlang: 2500 Ocaml: 7000 Ruby: 145000 Python: 154000 Perl: 390000 (This includes fa.haskell and probably other mailing list gateways as well.) Using Google Scholar to search for papers from 2007: Haskell: 1310 Ruby: 1670 Lisp: 316 Ocaml: 38 Java: 7650 Unfortunately, all this proves is that if your language shares its name with a large number of people, it will be mentioned a lot in scientific papers :-)
Maybe we need to reconsider where the (FP) mainstream is now? :-)
Getting there, at least. -k

Donald Bruce Stewart wrote:
Give #haskell is a far larger community than:
#lisp #erlang #scheme #ocaml
As well as
#java #javascript #ruby #lua #d #perl6
Maybe we need to reconsider where the (FP) mainstream is now? :-)
Yeah, #haskell is pretty big - 300 people idling and 1-3 people actually talking. :-P

andrewcoppin:
Donald Bruce Stewart wrote:
Give #haskell is a far larger community than:
#lisp #erlang #scheme #ocaml
As well as
#java #javascript #ruby #lua #d #perl6
Maybe we need to reconsider where the (FP) mainstream is now? :-)
Yeah, #haskell is pretty big - 300 people idling and 1-3 people actually talking. :-P
Hey! We answer questions and write code for free, and you misrepresent the population anyway: Maximum users seen in #haskell: 354, currently: 318 (97.8%), active: 53 (16.7%) ^^^^^^^^^^ In fact, a lot of your exploratory/introductory questions would be most efficiently answered on irc. Do drop by! http://haskell.org/haskellwiki/IRC_channel Cheers, Don

Donald Bruce Stewart wrote:
andrewcoppin:
Yeah, #haskell is pretty big - 300 people idling and 1-3 people actually talking. :-P
Hey! We answer questions and write code for free, and you misrepresent the population anyway:
Maximum users seen in #haskell: 354, currently: 318 (97.8%), active: 53 (16.7%) ^^^^^^^^^^
In fact, a lot of your exploratory/introductory questions would be most efficiently answered on irc. Do drop by!
Unfortunately, when I ask questions most people seem to either ignore me or not know what the answer is. :-( Also, it's quite fiddly to ask long and/or complicated question in IRC. Gotta type really fast. ;-)

I notice that when I try to execute a non-existing command with runInteractiveProcess, nasty things happen when I close the input. To be exact, the whole program terminates. Is this the intended behavior, and if so, what is the correct way to work around it? Sample sessions below, "cat" is a valid executable, while "asdf" is not. -k % ghci ___ ___ _ / _ \ /\ /\/ __(_) / /_\// /_/ / / | | GHC Interactive, version 6.6, for Haskell 98. / /_\\/ __ / /___| | http://www.haskell.org/ghc/ \____/\/ /_/\____/|_| Type :? for help. Loading package base ... linking ... done. Prelude> :m + System.IO Prelude System.IO> :m + System.Process Prelude System.IO System.Process> (i,o,e,p) <- runInteractiveCommand "asdf" Prelude System.IO System.Process> hPutStr i "foo" Prelude System.IO System.Process> hClose i % ghci ___ ___ _ / _ \ /\ /\/ __(_) / /_\// /_/ / / | | GHC Interactive, version 6.6, for Haskell 98. / /_\\/ __ / /___| | http://www.haskell.org/ghc/ \____/\/ /_/\____/|_| Type :? for help. Loading package base ... linking ... done. Prelude> :m + System.Process Prelude System.Process> :m + System.IO Prelude System.Process System.IO> (i,o,e,p) <- runInteractiveCommand "cat" Prelude System.Process System.IO> hPutStr i "foo" Prelude System.Process System.IO> hClose i Prelude System.Process System.IO> Prelude System.Process System.IO> x<- waitForProcess p ExitSuccess

Am Samstag, 7. Juli 2007 11:27 schrieb Ketil Malde:
I notice that when I try to execute a non-existing command with runInteractiveProcess, nasty things happen when I close the input. To be exact, the whole program terminates. Is this the intended behavior, and if so, what is the correct way to work around it?
Loading package base ... linking ... done. Prelude> :m + System.IO Prelude System.IO> :m + System.Process Prelude System.IO System.Process> (i,o,e,p) <- runInteractiveCommand "asdf" Prelude System.IO System.Process> hPutStr i "foo" Prelude System.IO System.Process> hClose i
If you look at the exit status of ghci, you'll see that it was terminated by SIGPIPE. This happens because you're trying to write to a pipe that has no reader on the other end (because "asdf" doesn't exist/run). It happens in hClose because i is buffered, so the hPutStr doesn't actually send anything. hClose tries to flush the buffer, which triggers the SIGPIPE. The solution is to install a signal handler for SIGPIPE, even if it just ignores the signal; something like: installHandler sigPIPE Ignore Nothing This should make write() fail with EPIPE, which should be turned into an IO exception by hClose (ok, so you still need to catch that but at least it doesn't kill your whole program). HTH, Lukas

Give #haskell is a far larger community than: As well as
#java #javascript #ruby Try #ruby-lang instead ;) At least assuming you were talking about the
Donald Bruce Stewart
#lua #d #perl6
Maybe we need to reconsider where the (FP) mainstream is now?
Maybe so.

On 7/7/07, Albert Y. C. Lai
Non-strict (most implementations lazy): rarely useful if you ask the mainstream.
<mild-rant> Of your propositions, I must say this one has the most merit, though not exactly as stated. :-) Being non-strict does allow some nice expressiveness, but has one teeny tiny downside - the performance model for haskell programs is at best inscrutable. Even using the decent profiling tools in GHC, it can be almost impossible to understand why a non-trivial program behaves the way it does. In my current project, we restart the server periodically because there's a memory leak in there somewhere that I can't track down. Now, I'm not saying that someone else might not spot it easily, but I hope you see my point: I can look at the source code of a C function, and I can pretty much guess what machine code will be generated for it (issues like instruction scheduling and register allocation aside). The same is essentially true for C++, Lisp, Prolog, Java, Mercury, &c, &c, &c, but not for Haskell. I wind up using -prof -auto-all as standard GHC flags so that if error gets called, I have a vague chance of figuring out what's going on. </mild-rant>
Static typing: extreme paranoia.
I've been working in a mostly Python shop this last year, and it reinforces my belief that people who don't like strong static typing are yahoos, not professionals interested in producing high quality code. Maybe I just don't get the line between professionalism and paranoia. ;-)
Purely functional: vocal minority of edgy people.
Ever used Prolog? Compromising purity in a declarative language can seem like a good idea in the short term, but in the long term, it usually causes untold grief. Especially, in the case of Prolog, the cut operator which interferes with the natural operation of backtracking. It overflows into the operation of negation, and creates all kinds of bother. <war-story> So I did my PhD in the Mercury group at .mu.oz.au. Mercury is a retake on logic programing. It is pure. In 1995 I arrived in the US for my first logic programming conference, and on the first evening, before the conference proper began, went out with a bunch of attendees. I got chatting with a really nice Canadian guy, Jamie Andrews, and five minutes into the conversation, on finding out he was a semantics researcher, asked what I thought was a terribly witty question "So are you presenting *another* semantics for the 'cut' operator?" "Um, well, yes, actually" was his reply. Apart from showing what a precocious prat I was, OMG 12 years ago, it tells you something about what happens when you ride rough-shod over purity. It creates gainful employment for hundreds of researchers for decades trying to put the genie back in the bottle. </war-story> ML and friends have had a much easier time of it than Prolog, I concede, but the problem of finding practical paradigms of programming in pure languages that combine expressiveness with clean semantics is actually well worth the short term inconvenience. Those with good memories will know that the use of monads to express IO took some time, and that there were several less successful, though more-or-less pure attempts before. There was the pair of lazy streams model; the continuation passing model; the linear types model (deployed by Clean, of course); and maybe others. The cool thing is that they were all fairly painful to use, and rather than give up, the researchers kept trying new things and came upon monads. The extra cool thing is that monads have turned out to be really useful for a whole lot of other things than just a way of expressing IO or even IO and mutable state (which linear types captures). As SPJ notes in his Hair Shirt talk, monads are not perfect, since they are often used in ways which over-sequentialize code using them, so we have people working on arrows, and other more sophisticated mechanisms, which in time will probably lead to more expressive paradigms. cheers, T. -- Thomas Conway drtomc@gmail.com Silence is the perfectest herald of joy: I were but little happy, if I could say how much.

On Jul 7, 2007, at 4:23 AM, Thomas Conway wrote:
the performance model for haskell programs is at best inscrutable
I punched my first Basic program by hand with a paper clip, in my high school library. Even after experiencing an APL interpreter at 19, it has taken half my life to fully internalize that how long a language takes with a machine isn't the issue, what matters is how long a language takes with ME. I was beginning to accept that I might die before clearing my pipeline of research projects I want to code up. Haskell has given me new hope. Haskell is like ice sailing, where one can reach 100 mph on a 15 mph breeze. A few months ago, I watched a colleague write a significant code experiment in Haskell in an hour, and I was stunned. Now, I routinely write reasonable code experiments in an hour to help learn the language, and I'm still a beginner. It pays to "time" all executions, one can sometimes knock a factor of ten out of a given algorithm with a modest amount of tweaking. One learns in the process how to write faster code next time on the first try. GHC is very impressive if one pays a little attention to one's code. This of course sets up the best answer to this debate: For a hard problem, one can express better algorithms in Haskell that would simply be too painful to code in other languages, swamping any considerations about the speed of Haskell versus C for a given algorithm. This is not where I'm personally at. I want Haskell to work math examples for me that would take months to work by hand. With current processor speeds, the bottleneck is how quickly I can specify to the computer what I want. Haskell is the perfect language for this. For this purpose, concise readable code I can understand later beats hell out of a better algorithm. My evolution as a Haskell programmer is to say things more clearly with less fuss, not to get the machine to go faster.

Dave Bayer wrote:
I was beginning to accept that I might die before clearing my pipeline of research projects I want to code up.
...so it's *not* just me!
Haskell has given me new hope.
Indeed. ;-) Today I hve implemented encoders and decoders for RLE, MTF, Fibonacci codes, and LZW. Next on my list is BWT, Huffman codes and arithmetic coding. (That last is *very* hard though...)

On Sat, Jul 07, 2007 at 06:49:25PM +0100, Andrew Coppin wrote:
Dave Bayer wrote:
I was beginning to accept that I might die before clearing my pipeline of research projects I want to code up.
...so it's *not* just me!
Haskell has given me new hope.
Indeed. ;-)
Today I hve implemented encoders and decoders for RLE, MTF, Fibonacci codes, and LZW. Next on my list is BWT, Huffman codes and arithmetic coding. (That last is *very* hard though...)
You should look at Jeremy Gibbons' paper "Arithmetic coding with folds and unfolds". www.comlab.ox.ac.uk/oucl/work/jeremy.gibbons/publications/arith.pdf For your more general parsing troubles, have you considered making you lower level parsers copy the rest of the underlying input stream into each token they produce? After that transformation a simple string might look something like [(c,rest) | (c:rest) <- init (tails "Some characters of input")]. Brandon

Andrew Coppin wrote:
Dave Bayer wrote:
I was beginning to accept that I might die before clearing my pipeline of research projects I want to code up. Haskell has given me new hope.
Indeed. ;-)
Today I hve implemented encoders and decoders for RLE, MTF, Fibonacci codes, and LZW. Next on my list is BWT, Huffman codes and arithmetic coding. (That last is *very* hard though...)
In case anybody cares... darcs get http://www.orphi.me.uk/darcs/ToyCompression ghc -O2 --make Encode ghc -O2 --make Decode You can now do Encode LZW foo Will look for a file named "foo", and generate a file called "foo-LZW" containing the LZW-compressed version of it. Also "foo-LZW.log.txt", which contains some statistics. Similarly, Decode LZW foo-LZW will make a file "foo-LZW-unLZW", which should *hopefully* be identical to the original one. (!) It didn't occur to me, but I should probably go add some way to discover a list of available algorithms! LOL. Anyway, currently working: RLE (Run Length Encoding). Counts runs of symbols. Considers 8 bits to be one "symbol". The maximum run length is 255. MTF (Move To Front). Takes an input file and produces an output file of exactly the same size, but containing mostly *low* numbers. Works well with RLE or Fib. BWT (Burners-Wheeler Transform). Like MTF, does no actual compression, but makes the file more "compressible". Fib (Fibonacci codes). Stores numbers using Fibonacci codes instead of unsigned binary. This makes low numbers smaller and high numbers bigger. (Use it with MTF...) LZW (Lempel-Ziv-Welch). The daddy. Looks for repeated input strings and compresses them. Caution: Encoding or decoding BWT currently requires absurd amounts of time and space. (Like, > 2 GB RAM and 8 minutes wall time to process 12 KB of text.) I hope to fix that soon... Currently it's unclear whether LZW or BWT+MTF+Fib gives the best compression. (Mainly because BWT is so hard to run!) I hope to implement a few other algorithms soonly. (Note: LZW is typically used with a variable number of bits per output symbol. I haven't done this yet. It simply uses 16 bits in all cases. Once I fix this, compression will go up. Also, once the symbol dictionary is full, the encoder just resets itself.)

andrewcoppin:
Andrew Coppin wrote:
Dave Bayer wrote:
I was beginning to accept that I might die before clearing my pipeline of research projects I want to code up. Haskell has given me new hope.
Indeed. ;-)
Today I hve implemented encoders and decoders for RLE, MTF, Fibonacci codes, and LZW. Next on my list is BWT, Huffman codes and arithmetic coding. (That last is *very* hard though...)
In case anybody cares...
darcs get http://www.orphi.me.uk/darcs/ToyCompression ghc -O2 --make Encode ghc -O2 --make Decode
You can now do
Encode LZW foo
Will look for a file named "foo", and generate a file called "foo-LZW" containing the LZW-compressed version of it. Also "foo-LZW.log.txt", which contains some statistics.
Similarly,
Decode LZW foo-LZW
will make a file "foo-LZW-unLZW", which should *hopefully* be identical to the original one. (!)
It didn't occur to me, but I should probably go add some way to discover a list of available algorithms! LOL. Anyway, currently working:
RLE (Run Length Encoding). Counts runs of symbols. Considers 8 bits to be one "symbol". The maximum run length is 255. MTF (Move To Front). Takes an input file and produces an output file of exactly the same size, but containing mostly *low* numbers. Works well with RLE or Fib. BWT (Burners-Wheeler Transform). Like MTF, does no actual compression, but makes the file more "compressible". Fib (Fibonacci codes). Stores numbers using Fibonacci codes instead of unsigned binary. This makes low numbers smaller and high numbers bigger. (Use it with MTF...) LZW (Lempel-Ziv-Welch). The daddy. Looks for repeated input strings and compresses them.
Caution: Encoding or decoding BWT currently requires absurd amounts of time and space. (Like, > 2 GB RAM and 8 minutes wall time to process 12 KB of text.) I hope to fix that soon...
Currently it's unclear whether LZW or BWT+MTF+Fib gives the best compression. (Mainly because BWT is so hard to run!) I hope to implement a few other algorithms soonly.
(Note: LZW is typically used with a variable number of bits per output symbol. I haven't done this yet. It simply uses 16 bits in all cases. Once I fix this, compression will go up. Also, once the symbol dictionary is full, the encoder just resets itself.)
Good work. Probably worth benchmarking against the other compression libraries on hackage, just to get a sense for how well your implementations are optimised (and maybe how to best interact with lazy bytestrings?). See for example: zlib http://hackage.haskell.org/cgi-bin/hackage-scripts/package/zlib-0.3 bzlib http://hackage.haskell.org/cgi-bin/hackage-scripts/package/bzlib-0.3 and also: lzf http://hackage.haskell.org/cgi-bin/hackage-scripts/package/Codec-Compression... -- Don

Hello Donald, Sunday, July 8, 2007, 12:50:36 PM, you wrote:
too much quoting :(
Good work. Probably worth benchmarking against the other compression libraries
are you really want to totally discredit Haskell? :) they should be hundreds of times slower than any practical compression algorithm (and btw, zlib/bzlib isn't good performers anyway, my own algorithm is several times faster with the same compression ratio) Haskell isn't a good tool to develop compression algorithms because it's the very well studied area where it has meaning to use all the sorts of optimizations. so it falls in the "low-level algorithms" category where using Haskell means at least 3x slower development and 3x worse performance - or faster development with 100x worse performance. Andrew's code should fall into later category -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Bulat Ziganshin wrote:
Hello Donald,
Good work. Probably worth benchmarking against the other compression libraries
are you really want to totally discredit Haskell? :) they should be hundreds of times slower than any practical compression algorithm (and btw, zlib/bzlib isn't good performers anyway, my own algorithm is several times faster with the same compression ratio)
Haskell isn't a good tool to develop compression algorithms because it's the very well studied area where it has meaning to use all the sorts of optimizations. so it falls in the "low-level algorithms" category where using Haskell means at least 3x slower development and 3x worse performance - or faster development with 100x worse performance. Andrew's code should fall into later category
Indeed. I'm more interested in which algorithms produce the best compression ratios than how to implement them fast. Currently the code uses very general, flexible, polymorphic types all over the place, everything is normal lists, I'm using monadic parsing rather than bit-twiddling, etc etc etc. It goes alright with 100 KB files on my monster PC at home, but toss a 4 MB file over there and it takes a minute or two to compress. Hardly a match for a "practical" compression solution that's been optimised to within inches of its life in C or even assembly. ;-) I mentioned that my LZW algorithm isn't even as efficient as it could be - it uses 16 bits per symbol rather than being variable. Partly that's because it's easier to code. But partly that's so that I can write a 16-bit Huffman compressor and run it over the top. (LZW + Huffman being a very common combination.) And that's really what this is - a toolbox for throwing algorithms together to see what they do. OTOH, if the Gods behind GHC want to take a look and figure out whether there's any magic that can be added to the optimiser, I wouldn't complain... ;-) (Realistically though. My program takes a [Word8] and turns it into a [Bool] before running a parser over it. The GHC optimiser doesn't really stand a hope in hell of optimising that into a program that reads a machine word into a CPU register and starts playing with bit flips on it...) PS. Are those zlib libraries actually written in Haskell? Or are they a thin layer on top of a C library? PPS. Does GHC make use of MMX, SSE, et al?

On Sun, Jul 08, 2007 at 12:10:04PM +0100, Andrew Coppin wrote:
(Realistically though. My program takes a [Word8] and turns it into a [Bool] before running a parser over it. The GHC optimiser doesn't really stand a hope in hell of optimising that into a program that reads a machine word into a CPU register and starts playing with bit flips on it...)
Actually, if you're very lucky (fusion is just as hard in Haskell as it is in real life), it *does*. It seems to fit nicely into the stream-fusion framework.
PS. Are those zlib libraries actually written in Haskell? Or are they a thin layer on top of a C library?
Yup, they wrap C's zlib.
PPS. Does GHC make use of MMX, SSE, et al?
No (in spirit - the native code generator uses 1-element SSE operations for floating point because it's easier to optimize than "FPU" code). Stefan

Stefan O'Rear wrote:
On Sun, Jul 08, 2007 at 12:10:04PM +0100, Andrew Coppin wrote:
(Realistically though. My program takes a [Word8] and turns it into a [Bool] before running a parser over it. The GHC optimiser doesn't really stand a hope in hell of optimising that into a program that reads a machine word into a CPU register and starts playing with bit flips on it...)
Actually, if you're very lucky (fusion is just as hard in Haskell as it is in real life), it *does*. It seems to fit nicely into the stream-fusion framework.
Ooo... really? That's pretty impressive...(!) Is there a way I can check? ;-) More usefully, can I do stuff to my code to make myself more "lucky"? (Love the comment about RL BTW!)
PS. Are those zlib libraries actually written in Haskell? Or are they a thin layer on top of a C library?
Yup, they wrap C's zlib.
Thought so. Comparing native Haskell to a heavily optimised C library would surely be just like comparing native Haskell to a compiled C binary...
PPS. Does GHC make use of MMX, SSE, et al?
No (in spirit - the native code generator uses 1-element SSE operations for floating point because it's easier to optimize than "FPU" code).
Does GHC actually do anything that could usefully use these primitives? (I'm guessing "no"...)

Hello Andrew, Sunday, July 8, 2007, 7:12:38 PM, you wrote:
(Realistically though. My program takes a [Word8] and turns it into a [Bool] before running a parser over it. The GHC optimiser doesn't really stand a hope in hell of optimising that into a program that reads a machine word into a CPU register and starts playing with bit flips on it...)
Actually, if you're very lucky (fusion is just as hard in Haskell as it is in real life), it *does*. It seems to fit nicely into the stream-fusion framework.
Ooo... really? That's pretty impressive...(!)
it's our collective tale for bringing new haskellers. i bet that Stefan never seen asm code generated by ghc :) -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Bulat Ziganshin wrote:
Hello Andrew,
Ooo... really? That's pretty impressive...(!)
it's our collective tale for bringing new haskellers. i bet that Stefan never seen asm code generated by ghc :)
LOL! Once - just once - I did take a look at the C output from GHC. Now, I realise that I can't code in C to save my life, but... it didn't even *look* like C. Even slightly. Wow. (OTOH, reading Core isn't too helpful either. It just looks like the original Haskell...)

On Sun, Jul 08, 2007 at 10:40:10PM +0400, Bulat Ziganshin wrote:
Hello Andrew,
Sunday, July 8, 2007, 7:12:38 PM, you wrote:
(Realistically though. My program takes a [Word8] and turns it into a [Bool] before running a parser over it. The GHC optimiser doesn't really stand a hope in hell of optimising that into a program that reads a machine word into a CPU register and starts playing with bit flips on it...)
Actually, if you're very lucky (fusion is just as hard in Haskell as it is in real life), it *does*. It seems to fit nicely into the stream-fusion framework.
Ooo... really? That's pretty impressive...(!)
it's our collective tale for bringing new haskellers. i bet that Stefan never seen asm code generated by ghc :)
If you check the list archives, you'll see that I've been a major contributer to quite a few threads on the GHC code generator, and I posted to the JHC list months ago. Also, I said it would be read into a register, I never said it wouldn't be spilled two instructions later ;) Stefan (If I'm taking this totally wrong, make sure I know)

Hello Stefan, Sunday, July 8, 2007, 11:03:00 PM, you wrote:
(Realistically though. My program takes a [Word8] and turns it into a [Bool] before running a parser over it. The GHC optimiser doesn't really stand a hope in hell of optimising that into a program that reads a machine word into a CPU register and starts playing with bit flips on it...)
well, can you give us an example of code which does that Andrew said and translates into the simple bit fiddling without battling all around lazy lists which kills performance? -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

On 7/8/07, Dave Bayer
This of course sets up the best answer to this debate: For a hard problem, one can express better algorithms in Haskell that would simply be too painful to code in other languages, swamping any considerations about the speed of Haskell versus C for a given algorithm.
This is certainly true. I've coded up in less than six months, something that uses better algorithms and finer grained concurrency than the software I used to work on, and the latter represented 5 or more man-years of coding. However this is server software, which is long running so performance and memory usage are pretty important, and these are relatively hard to get right in Haskell. OTOH, you can tell, I think it's a good trade off - I did convince the mgt to let me doit in Haskell in the first place. :-) -- Thomas Conway drtomc@gmail.com Silence is the perfectest herald of joy: I were but little happy, if I could say how much.

Hello Thomas, Sunday, July 8, 2007, 2:36:43 AM, you wrote:
This is certainly true. I've coded up in less than six months, something that uses better algorithms and finer grained concurrency than the software I used to work on, and the latter represented 5 or more man-years of coding. However this is server software, which is long running so performance and memory usage are pretty important, and these are relatively hard to get right in Haskell.
i've improved memory usage of my program 3 times one month after i've started to use Haskell, and 4 times more 1.5 years later (the last improvement included development of ByteString-alike library and strictifying some computations). i think that for programming-in-large experienced haskeller may reach C-like level of efficiency, unlike for programming-in-small (i.e. implementation of raw computations) -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

bulat.ziganshin:
Hello Thomas,
Sunday, July 8, 2007, 2:36:43 AM, you wrote:
This is certainly true. I've coded up in less than six months, something that uses better algorithms and finer grained concurrency than the software I used to work on, and the latter represented 5 or more man-years of coding. However this is server software, which is long running so performance and memory usage are pretty important, and these are relatively hard to get right in Haskell.
i've improved memory usage of my program 3 times one month after i've started to use Haskell, and 4 times more 1.5 years later (the last improvement included development of ByteString-alike library and strictifying some computations). i think that for programming-in-large experienced haskeller may reach C-like level of efficiency, unlike for programming-in-small (i.e. implementation of raw computations)
Yes, this agrees with my experience too. Programs of a certain size become unfeasible to improve in C or C++ -- while the Haskell program may be continually refactored and improved. -- Don

Bulat Ziganshin wrote:
i've improved memory usage of my program 3 times one month after i've started to use Haskell, and 4 times more 1.5 years later (the last improvement included development of ByteString-alike library and strictifying some computations). i think that for programming-in-large experienced haskeller may reach C-like level of efficiency, unlike for programming-in-small (i.e. implementation of raw computations)
Yeah, I spent yesterday building a whole toolbox of compression algorithms. However, it turns out that just one algorithm - BWT - is too absurdly slow. You may recall I implemented that a while back, and discovered that making it use a lazy ByteString make it many orders of magnitude faster. Trouble is... the whole of the rest of my toolbox uses normal lists. So I'm going to have to do some horribly ugly hack just to make BWT work properly. (Like, I've built this whole nice abstract framework for all the other algorithms, and I'm going to have to punch a massive hole through the middle of it to make a ByteString BWT fit.) It's a real shame. (OTOH, I waited over 5 minutes for my program to try to take the BWT of a 12 KB file. It used in excess of 2 GB of RAM. That's clearly absurd...) Does anybody have any clue why ByteStrings are actually faster? (And why this information isn't easily findable anywhere - must shorly be a VFAQ.)

andrewcoppin:
Does anybody have any clue why ByteStrings are actually faster? (And why this information isn't easily findable anywhere - must shorly be a VFAQ.)
It's well documented in the API documentation for bytestrings. Start here: http://www.cse.unsw.edu.au/~dons/fps/Data-ByteString-Lazy.html And then read: http://www.cse.unsw.edu.au/~dons/papers/CSL06.html Cheers, Don

Donald Bruce Stewart wrote:
andrewcoppin:
Does anybody have any clue why ByteStrings are actually faster? (And why this information isn't easily findable anywhere - must shorly be a VFAQ.)
It's well documented in the API documentation for bytestrings.
Start here: http://www.cse.unsw.edu.au/~dons/fps/Data-ByteString-Lazy.html
I've read the API and still left wondering...
And then read: http://www.cse.unsw.edu.au/~dons/papers/CSL06.html
Now *that* is far more useful... (And interesting.) So what you're saying is that whereas "fusion" is usually used to mean "that amazing technology that will one day supply us with unlimited amounts of cheap clean energy [shame it doesn't actually work]", in the context of Haskell it seems "fusion" means "that technology that makes all your code 98% faster for free"? ;-) I guess the question that's really burning in my mind is "if ByteString is so much faster than [x], why can't you just do the same optimisations to [x]?" In other words, "why should I need to alter my code to get all this fusion goodness?" Now, as I understand it, a ByteString is a kind of unboxed array (= big RAM savings + big CPU time savings for not building it + big GC savings for not processing millions of list nodes + better cache performance). Or at least, a *strict* ByteString is; I'm very very fuzzy on exactly how a *lazy* ByteString is any different to a normal list. From my reading today, I take it the only real difference is that one is a linked list, whereas the other is a (boxed?) array, so it's smaller. (?) At any rate, currently all my toy compression algorithms run at respectable speeds using [Word8], *except* for the BWT, which is absurdly slow. I've done everything I can think of to it, and it's still too slow. It's no use, I'm going to have to use ByteStrings to get any kind of performance out of it. I'm just wondering whether using getContents :: [Char] and then packing that into a ByteString is going to completely negate all the speed advantages. (I'm really not keen to completely mangle the entire toolbox just to make this one algorithm hurry up.) Also, while I'm here... I can see a sorting algorithm implemented in Data.List, but I don't see any for other structures. For example, there doesn't appear to be any sorting functions for any kind of array. There doesn't appear to be anything for ByteString either. I'd like to see such a thing in the libraries. Yes, you can sort things using (say) Data.Map. But what if you have some data that's already *in* an array or a ByteString and you just want to sort it? (I also notice that the mutable arrays don't seem to provide an in-place map function. Obviously that's only ever going to work for a function that doesn't change the value's type, but even so...) Finally, I don't see anything in the libraries that would efficiently sort (large) strings. Data.List.sort and Data.Map.Map both use an Ord context, and we have instance (Ord x) => Ord [x], but one would think that a [potentially large] list of values could be sorted more efficiently using a radix sort than a quicksort...? An implementation of Data.Map especially for the (common?) case of the keys being a *list* of Ord items would seem useful... (And in my current program, I'm probably going to implement a radix sort on lists of ByteStrings.)

Hi
I guess the question that's really burning in my mind is "if ByteString is so much faster than [x], why can't you just do the same optimisations to [x]?" In other words, "why should I need to alter my code to get all this fusion goodness?"
You already get some benefit of fusion with lists: * http://research.microsoft.com/~simonpj/Papers/rules.htm People are working on more: * http://www-users.cs.york.ac.uk/~ndm/supero/ * http://www.cse.unsw.edu.au/~dons/papers/CLS07.html * many, many others Thanks Neil

Neil Mitchell wrote:
Hi
I guess the question that's really burning in my mind is "if ByteString is so much faster than [x], why can't you just do the same optimisations to [x]?" In other words, "why should I need to alter my code to get all this fusion goodness?"
You already get some benefit of fusion with lists:
* http://research.microsoft.com/~simonpj/Papers/rules.htm
People are working on more:
* http://www-users.cs.york.ac.uk/~ndm/supero/ * http://www.cse.unsw.edu.au/~dons/papers/CLS07.html * many, many others
I always have trouble tracking exactly which version(s) of GHC actually implement all this stuff... ;-) Maybe I'll go find a Linux box sometime and try the head version, just for kicks...

Andrew Coppin wrote:
Now, as I understand it, a ByteString is a kind of unboxed array (= big RAM savings + big CPU time savings for not building it + big GC savings for not processing millions of list nodes + better cache performance). Or at least, a *strict* ByteString is; I'm very very fuzzy on exactly how a *lazy* ByteString is any different to a normal list. From my reading today, I take it the only real difference is that one is a linked list, whereas the other is a (boxed?) array, so it's smaller. (?)
As I understand it (wich may or may not be correct): A normal Haskell string is basically [Word8] A strict ByteString ist basically UArray Int Word8 A lazy ByteString is basically [UArray Int Word8] [Word8] is processed one byte at once UArray Int Word8 is processed all at once [UArray Int Word8] is processed a chunk of bytes at once So loading and processing [Word8] corresponds to while (!eof(file)) { Byte current = readByteFromFile(file); processByte(current); } loading and processing a strict ByteString corresponds to int size = readWholeFileIntoBuffer(file, buffer); for (int i = 0; i < size; i++) processByte(buffer[i]); and loading and processing a lazy ByteString corresponds to while (!eof(file)) { int size = readNextNBytesIntoBuffer(file, buffer, buffersize); for (int i = 0; i < size; i++) processByte(buffer[i]); } in a C-like language. The first is nonsense because of I/O overhead, the second is fine for small files only and the third combines the best of both worlds. Unlike the C examples, Haskell lists face not only I/O overhead, but general overhead of boxed representation and laziness, too. But even in C, the third solution ist the best, but some programs don't use it. So Bytestring powered Haskell programs are able to outperform some C programs. The most important contributions of the ByteStrings library seem to be these: (1) unify lazy and strict Bytestrings interface-wise and (2) allow idiomatic Haskell programs using lazy ByteStrings to be compiled to something like the third c program above. Tillmann

Tillmann Rendel:
As I understand it (wich may or may not be correct):
A normal Haskell string is basically [Word8]
Hm, let's see whether I understand it better or worse. Actually it is [Char], and Char is a Unicode code point in the range 0..1114111 (at least in GHC). Compare: Prelude Data.Word> fromEnum (maxBound :: Char) 1114111 Prelude Data.Word> fromEnum (maxBound :: Word8) 255 So it seems that the Char type abstracts the encoding away. I'm actually a little confused by this, because I haven't found any means to make the I/O functions of the Prelude (getContents etc.) encoding-aware: The string "ä", when read from a UTF-8-encoded file via readFile, has a length of 2. Anyone with a URI to enlighten me? Malte

Hello Malte, Sunday, July 8, 2007, 6:38:19 PM, you wrote:
The string "a", when read from a UTF-8-encoded file via readFile, has a length of 2. Anyone with a URI to enlighten me?
if you need UTF-8 i/o, look at http://hackage.haskell.org/packages/archive/pkg-list.html -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

On Sun, Jul 08, 2007 at 04:38:19PM +0200, Malte Milatz wrote:
Tillmann Rendel:
As I understand it (wich may or may not be correct):
A normal Haskell string is basically [Word8]
Hm, let's see whether I understand it better or worse. Actually it is [Char], and Char is a Unicode code point in the range 0..1114111 (at least in GHC). Compare:
Prelude Data.Word> fromEnum (maxBound :: Char) 1114111 Prelude Data.Word> fromEnum (maxBound :: Word8) 255
So it seems that the Char type abstracts the encoding away. I'm actually a little confused by this, because I haven't found any means to make the I/O functions of the Prelude (getContents etc.) encoding-aware: The string "ä", when read from a UTF-8-encoded file via readFile, has a length of 2. Anyone with a URI to enlighten me?
Not sure of any URIs. Char is just a code point. It's a 32 bit integer (64 on 64-bit platforms due to infelicities in the GHC backend) with a code point. It is not bytes. A Char in the heap also has a tag-pointer, bringing the total to 8 (16) bytes. (However, GHC uses shared Char objects for Latin-1 characters, so a "fresh" Char in that range uses 0 bytes). [a] is polymorphic. It is a linked list, it consumes 12 (24) bytes per element. It just stores pointers to its elements, and has no hope of packing anything. [Char] is a linked list of pointers to heap-allocated fullword integers, 20 (40) bytes per character (assuming non-latin1). The GHC IO functions truncate down to 8 bits. There is no way in GHC to read or write full UTF-8, short of doing the encoding yourself (google for UTF8.lhs). Stefan

Stefan O'Rear:
Char is just a code point. It's a 32 bit integer (64 on 64-bit platforms due to infelicities in the GHC backend) with a code point. [...] The GHC IO functions truncate down to 8 bits. There is no way in GHC to read or write full UTF-8, short of doing the encoding yourself (google for UTF8.lhs).
Thanks, this makes things clear to me.
[Char] is a linked list of pointers to heap-allocated fullword integers, 20 (40) bytes per character (assuming non-latin1).
Hey, I love ByteStrings! ;-) Malte

Malte Milatz wrote:
Stefan O'Rear:
[Char] is a linked list of pointers to heap-allocated fullword integers, 20 (40) bytes per character (assuming non-latin1).
Hey, I love ByteStrings! ;-)
If only there were a way to write functions that transparently work on both [x] and ByteString... (Well, I mean, there *is* - if you want to write *lots* of code by hand yourself...) Anyone have any comments on how ByteString is different from, say, UArray Word8?

On Sun, Jul 08, 2007 at 04:16:46PM +0100, Andrew Coppin wrote:
Malte Milatz wrote:
Stefan O'Rear:
[Char] is a linked list of pointers to heap-allocated fullword integers, 20 (40) bytes per character (assuming non-latin1).
Hey, I love ByteStrings! ;-)
If only there were a way to write functions that transparently work on both [x] and ByteString...
(Well, I mean, there *is* - if you want to write *lots* of code by hand yourself...)
Anyone have any comments on how ByteString is different from, say, UArray Word8?
1. ByteString uses pinned memory, so you can safely pass ByteStrings to C code (as char*) without worrying about the strings moving. 2. ByteString uses foreignptrs, which mean that you can construct bytestrings from any block of memory, and you can associate arbitrary actions (free(), nothing, something fancier, ...) with the ByteString becoming unreferenced. 3. ByteString uses explicit offset and length fields, allowing a O(1) tail operation (very important for functional-style code) 4. Lazy bytestrings are completely different - look elsewhere in this thread. Stefan

Hello Andrew, Sunday, July 8, 2007, 7:16:46 PM, you wrote:
[Char] is a linked list of pointers to heap-allocated fullword integers, 20 (40) bytes per character (assuming non-latin1).
Hey, I love ByteStrings! ;-)
actually only 12 (24 for 64-but cpu) as far as you use latin-1 chars. the same should be true for [word8] but it's better to ask Simon OTOH, using GC makes memory usage 3x larger. in those practical C compression algorithms, memory is controlled manually. so, you have 36x space overhead. now you may guess how i decreased memory usage 12-fold :)
If only there were a way to write functions that transparently work on both [x] and ByteString...
use pack/unpack to convert between them - it's cheap compared to your algorithms
Anyone have any comments on how ByteString is different from, say, UArray Word8?
mainly, algorithms implemented. the only technical difference is that UArray uses ByteArray# and ByteString uses PinnedByteArray#, which has different behavior in GC -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Bulat Ziganshin wrote:
Hello Andrew,
Anyone have any comments on how ByteString is different from, say, UArray Word8?
mainly, algorithms implemented. the only technical difference is that UArray uses ByteArray# and ByteString uses PinnedByteArray#, which has different behavior in GC
I just wish I could have all that ByteString goodness without being limited to only having Word8 to play with. :-( (E.g., the inverse BWT makes use of positive integers that are likely to be way bigger than 255. But there isn't a fast packed Word16 or Word32 array I can use there...)

Hello Andrew, Sunday, July 8, 2007, 9:38:18 PM, you wrote:
(E.g., the inverse BWT makes use of positive integers that are likely to be way bigger than 255. But there isn't a fast packed Word16 or Word32 array I can use there...)
well, that's true as long as you swear to never use UArray :)) -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Bulat Ziganshin wrote:
Hello Andrew,
Sunday, July 8, 2007, 9:38:18 PM, you wrote:
(E.g., the inverse BWT makes use of positive integers that are likely to be way bigger than 255. But there isn't a fast packed Word16 or Word32 array I can use there...)
well, that's true as long as you swear to never use UArray :))
OTOH, everybody uses ByteString rather than UArray Word8. (And, in fact, ByteString *exists* even though UArray Word8 was there first.) So one presumes it's because ByteString has some kind of magic that makes it faster than a UArray...

Hello Andrew, Sunday, July 8, 2007, 10:41:53 PM, you wrote:
OTOH, everybody uses ByteString rather than UArray Word8. (And, in fact, ByteString *exists* even though UArray Word8 was there first.) So one presumes it's because ByteString has some kind of magic that makes it faster than a UArray...
as i already said, it's due to algorithms implemented. when one need UArray operations, it use it. when one need string operations, he use ByteStrings. the rest is marketing hype ands i bet that UArray advertising company was ~15 years ago :) -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Thomas Conway wrote: [great comments on non-strict, static typing, purely functional] Don't worry, I was just writing a sarcasm to an apparent attitude of "X is rare edge iff I can't figure out X". I have always been believing in all the points you make.

On Jul 7, 2007, at 7:23 , Thomas Conway wrote:
I've been working in a mostly Python shop this last year, and it reinforces my belief that people who don't like strong static typing are yahoos, not professionals interested in producing high quality code. Maybe I just don't get the line between professionalism and paranoia. ;-)
Security is one of my "side specialties" (i.e. not my main focus as a sysadmin, but a greater focus than e.g. storage or networking which aren't really my focus at all). And it seems to me that most people treat it about the same way they treat the notion of strong typing. In fact, I could make pretty much the same point about professionalism vs. paranoia with respect to security; the difference being that, thanks to Internet-facing credit card processing systems, at least *some* people have had their faces rubbed in their mistakes. (This correspondence is in fact one of the reasons I became interested in Haskell. http://blog.moertel.com/articles/2006/10/18/a- type-based-solution-to-the-strings-problem is exactly the kind of thing I was hoping to find.) -- 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

Andrew: By the way, could you share your definition of Stack with us? It isn't at all clear to me how stacked actually decides to terminate the underlying parser. Jonathan Cast http://sourceforge.net/projects/fid-core http://sourceforge.net/projects/fid-emacs

Jonathan Cast wrote:
Andrew:
By the way, could you share your definition of Stack with us? It isn't at all clear to me how stacked actually decides to terminate the underlying parser.
Yeah, I'll post the complete source here in a little while. I think that's probably the only way anybody is going to be able to help me effectively... (Netiquette: Is 200 lines too big to past in the body of an email?)

-- This is probably line-wrapped horribly... module Process ( Source (..), PState (), start, Process (run), get_state, set_state, alt_state, get, eof, pure, count, many, stack ) where class Source src where empty :: src x -> Bool fetch :: src x -> (x, src x) instance Source [] where empty = null fetch xs = (head xs, tail xs) data PState st src x = PState {state :: st, source :: src x} start :: (Source src) => st -> src x -> PState st src x start = PState data Process st src x y = Process {run :: PState st src x -> (y, PState st src x)} instance (Source src) => Monad (Process st src x) where return x = Process (\ps -> (x, ps)) p >>= f = Process (\ps -> let (y, xs) = run p ps in run (f y) xs) get_state :: Process st src x st get_state = Process(\ps -> (state ps, ps)) set_state :: st -> Process st src x () set_state st = Process (\ps -> ((), ps {state = st})) alt_state :: (Source src) => (st -> st) -> Process st src x () alt_state f = do st <- get_state set_state (f st) get :: (Source src) => Process st src x x get = Process (\ps -> let (x,xs) = fetch (source ps) in (x, ps {source = xs})) eof :: (Source src) => Process st src x Bool eof = Process (\ps -> (empty (source ps), ps)) pure :: (Source src) => (x -> y) -> Process st src x y pure f = do x <- get return (f x) count :: (Source src, Integral n) => n -> Process st src x y -> Process st src x [y] count 0 _ = return [] count n p = do y <- p ys <- count (n-1) p return (y:ys) many :: (Source src) => Process st src x y -> Process st src x [y] many p = do end <- eof if end then return [] else do y <- p ys <- many p return (y:ys) data Stack st src x y = Stack {pstate :: PState st src x, pro :: Process st src x [y], buffer :: [y]} instance (Source src) => Source (Stack st src x) where empty stack = empty $ source $ pstate stack fetch stack | empty (buffer stack) = let (ys,xs) = run (pro stack) (pstate stack) in fetch (stack {pstate = xs, buffer = ys}) | otherwise = let (y, ys) = fetch (buffer stack) in (y, stack {buffer = ys}) stack :: (Source src0) => st0 -> Process st0 src0 x [y] -> st1 -> Process st1 (Stack st0 src0 x) y z -> Process st9 src0 x z stack st0 p0 st1 p1 = Process (\ps -> let ps0 = PState {state = st0, source = source ps} ps1 = PState {state = st1, source = src1} src1 = Stack {pstate = ps0, pro = p0, buffer = []} (z, ys) = run p1 ps1 in (z, ps {source = source $ pstate $ source ys}) ) -- If you want something to test with... module AlgoRLE where import Data.List import Process encodeRLE :: (Eq x, Integral n) => [x] -> [(n,x)] encodeRLE = map (\xs -> (genericLength xs, head xs)) . group decodeRLE :: (Integral n) => [(n,x)] -> [x] decodeRLE = concatMap (uncurry genericReplicate) encodeRLEb :: (Integral x) => [x] -> [x] encodeRLEb = concatMap work . encodeRLE where work (1,0) = [0,0] work (n,0) = [0,n-1,0] work (n,x) | n > 3 = [0,n-1,x] | otherwise = genericReplicate n x decodeRLEb :: (Integral x) => [x] -> [x] decodeRLEb = concat . fst . run (many decodeRLEb1) . start () decodeRLEb1 :: (Source src, Integral x) => Process st src x [x] decodeRLEb1 = do v <- get if v == 0 then do n <- get if n == 0 then return [0,0] else do x <- get return $ genericReplicate (n+1) x else return [v]

On Thursday 05 July 2007, Andrew Coppin wrote: <snip> This version works (I think). Also, using this syntax may make the distinction between existential constructors and rank-2 constructors a little clearer. *AlgoRLE> run decodeRLEb1 $ start () $ encodeRLEb [1, 2, 3] ([1],PState {state = (), source = [2,3]}) --- Process.hs --- {-# LANGUAGE Rank2Types #-} module Process ( Source (..), PState (), start, Process (run), get_state, set_state, alt_state, get, eof, pure, count, many, stack ) where class Source src where empty :: src x -> Bool fetch :: src x -> (x, src x) instance Source [] where empty = null fetch xs = (head xs, tail xs) data PState st src x = PState {state :: st, source :: src x} deriving (Eq, Ord, Show) start :: (Source src) => st -> src x -> PState st src x start = PState data Process st x y = Process {run :: forall src. Source src => PState st src x -> (y, PState st src x)} instance Monad (Process st x) where return x = Process (\ps -> (x, ps)) p >>= f = Process (\ps -> let (y, xs) = run p ps in run (f y) xs) get_state :: Process st x st get_state = Process(\ps -> (state ps, ps)) set_state :: st -> Process st x () set_state st = Process (\ps -> ((), ps {state = st})) alt_state :: (st -> st) -> Process st x () alt_state f = do st <- get_state set_state (f st) get :: Process st x x get = Process (\ps -> let (x,xs) = fetch (source ps) in (x, ps {source = xs})) eof :: Process st x Bool eof = Process (\ps -> (empty (source ps), ps)) pure :: (x -> y) -> Process st x y pure f = do x <- get return (f x) count :: (Integral n) => n -> Process st x y -> Process st x [y] count 0 _ = return [] count n p = do y <- p ys <- count (n-1) p return (y:ys) many :: Process st x y -> Process st x [y] many p = do end <- eof if end then return [] else do y <- p ys <- many p return (y:ys) data Stack st src x y = Stack { pstate :: PState st src x, pro :: Process st x [y], buffer :: [y]} instance (Source src) => Source (Stack st src x) where empty stack = empty $ source $ pstate stack fetch stack | empty (buffer stack) = let (ys,xs) = run (pro stack) (pstate stack) in fetch (stack {pstate = xs, buffer = ys}) | otherwise = let (y, ys) = fetch (buffer stack) in (y, stack {buffer = ys}) stack :: st0 -> Process st0 x [y] -> st1 -> Process st1 y z -> Process st9 x z stack st0 p0 st1 p1 = Process (\ps -> let ps0 = PState {state = st0, source = source ps} ps1 = PState {state = st1, source = src1} src1 = Stack {pstate = ps0, pro = p0, buffer = []} (z, ys) = run p1 ps1 in (z, ps {source = source $ pstate $ source ys}) ) --- AlgoRLE.hs --- module AlgoRLE where import Data.List import Process encodeRLE :: (Eq x, Integral n) => [x] -> [(n,x)] encodeRLE = map (\xs -> (genericLength xs, head xs)) . group decodeRLE :: (Integral n) => [(n,x)] -> [x] decodeRLE = concatMap (uncurry genericReplicate) encodeRLEb :: (Integral x) => [x] -> [x] encodeRLEb = concatMap work . encodeRLE where work (1,0) = [0,0] work (n,0) = [0,n-1,0] work (n,x) | n > 3 = [0,n-1,x] | otherwise = genericReplicate n x decodeRLEb :: (Integral x) => [x] -> [x] decodeRLEb = concat . fst . run (many decodeRLEb1) . start () decodeRLEb1 :: (Integral x) => Process st x [x] decodeRLEb1 = do v <- get if v == 0 then do n <- get if n == 0 then return [0,0] else do x <- get return $ genericReplicate (n+1) x else return [v] Jonathan Cast http://sourceforge.net/projects/fid-core http://sourceforge.net/projects/fid-emacs

source code is always useful, as it is concrete. but some comments about purpose and important aspects would help, too, lest we optimise away the parts you're most interested in. as it stands, i must assume that 'decodeRLEb' is the purpose of the exercise, and it isn't clear to me why that requires nested or otherwise nontrivial parsers? on lists, it could be coded as a straightforward recursion, but i assume that abstraction over sources, and decomposition of the main function into repeatedly applied parsers is part of the specification, too. still, what's wrong with plain parsing? as has been discussed in previous threads here, (>>=) as a monadic parser combinator would even allow you to compute the second parser from the output of the first parser, should you need that flexibility. but in this particular case, there are just three alternative branches, consuming 2,3, or 1 numbers from the source. btw, MonadPlus and 'fail _ = mzero' allow for handling of alternatives and parse or match failure without lots of ifs getting in the way. the same approach also avoids the separate 'empty' test in Source. claus -----------------------------------------------------code follows {-# OPTIONS_GHC -fglasgow-exts #-} {-# OPTIONS_GHC -fno-monomorphism-restriction #-} import Data.List import Control.Monad import Control.Monad.State encodeRLE = concatMap work . group where work [0] = [0,0] work xs@(x:_) | x==0 = [0,l,0] | l>2 = [0,l,x] | otherwise = xs where l = length xs - 1 type DataStream = [Int] type Parser m a = StateT DataStream m a class Source c where fetch :: Monad m => c a -> m (a,c a) instance Source [] where fetch xs = do { x:xs' <- return xs; return (x,xs') } decodeRLE :: Parser Maybe DataStream decodeRLE = (oneGroup >++ decodeRLE) `mplus` (return []) where oneGroup = encoded `mplus` elem a >++ b = do { as <- a; bs <- b; return (as++bs) } encoded = zero >> (zero `mplus` nx) nx = do { [n]<-elem; [x]<-elem; return (replicate (n+1) x) } elem = StateT $ \nxs-> do { (x,nxs') <- fetch nxs; return ([x],nxs') } zero = StateT $ \nxs-> do { (0,nxs') <- fetch nxs; return ([0],nxs') } x :: DataStream x = map (read . return) "034444220005555500" test = x==x' where Just x' = evalStateT decodeRLE (encodeRLE x)

Claus Reinke wrote:
source code is always useful, as it is concrete. but some comments about purpose and important aspects would help, too, lest we optimise away the parts you're most interested in. as it stands, i must assume that 'decodeRLEb' is the purpose of the exercise, and it isn't clear to me why that requires nested or otherwise nontrivial parsers?
Now take decodeRLEb and feed it's output to some nontrivial parser, and then feed the remainder of the input, unmodified, into another parser: foo = do x <- stack () decodeRLEb () other_stuff y <- bar return (x,y) Since I don't know how much data other_stuff is going to consume - let alone how much of the raw data you have to feed to decodeRLEb to make that much data - we arrive at the structure shown. (This makes it, what, the 5th time I've explained this? LOL...)

Now take decodeRLEb and feed it's output to some nontrivial parser, and then feed the remainder of the input, unmodified, into another parser:
so the code as posted didn't exhibit a full use case. that specification is still a bit vague. assuming that p1: decodeRLE, p2: nontrivial parser, and p3: another parser, it could be interpreted simply as parser combination: do { output <- p1; x <- p2 output; y <- p3; return (x,y) } or perhaps you meant to run p2 over the output of p1 in a separate parser chain, with the remaining input left by p1, not by p2, being fed into p3? do { output <- p1; Just x <- return $ evalStateT p2 output; y <- p3; return (x,y) } then we'd have something like p2 `stack` p1 = do { out <- p1; Just x <- return $ evalStateT p2 out; return x }
Since I don't know how much data other_stuff is going to consume - let alone how much of the raw data you have to feed to decodeRLEb to make that much data - we arrive at the structure shown.
ah, that suggests yet another specification, a variation of the second version above, where the parser in control is not p1 itself, but p2, with p1 acting as an input transformation for p2, and p3 resuming where p1 left off. the difference being that p2's demand is supposed to drive p1's input processing. which is a bit of a problem. parsers are usually data- and grammar-driven, not demand-driven, ie the input consumed by p1 does not usually depend on the demands on p1's output. one could let p1 generate results of increasing length, and let p2 pick a result that fits, but that would involve rerunning p2 on the complete prefix of too-short results, backtracking into p1 until it produces an output useable by p2 - not exactly elegant or efficient, but it would fit the second variant above (one would have to ensure that p1 backtracked only over the length of input consumed, eg, an outermost 'many', and that the shortest alternative was produced first). looking a little bit more closely, however, p1 is used more as a piecewise input transformation for p2 than as a separate parser. so it makes more sense to integrate p1 into p2 (or rather: parts of p1 - if p1 is 'many group', then we should integrate only 'group'; in other words, we'd like to run p1 repeatedly, in minimal-much mode, rather than the more typical once, in maximal-munch mode), so that the latter uses some part of p1 as its item parser (which, in turn, assumes that p2 has a single, identifiable item parser - called 'fetch' here, and no other way to access the parse state). that seems to be what you have in mind with your stacked approach, where the state is read exclusively through the fetch method in the Source interface, and a Source can either be a plain list or buffered item parser stacked on top of a Source (where fetch is served from the buffer, which is replenished by running the item parser over the inner Source; btw, are unused buffer contents discarded when p2 finishes? they can't be transformed back into p1/p3's input format..). instead of using a type class, one could also parameterise p2 by its item parser, 'fetch'. that might make it easier to see that this stacking is a kind of parser composition. unlike the standard function and monad compositions, this one relies on the compositional nature of combinator parsers: there's an item parser, which accesses the input and produces output, and there is a coordination framework (the combinatorial grammar) specifying how the item parser is to be used. function composition allows us to abstract over each part of the composed function, including the inner function in a 'stack' of functions: \x->f (g x) ==> -- abstract over g (f .) we can try to view parsers as composed from a grammar and an item parser, where the latter is the 'inner' part of this composition: \s->(item >> item) s `mplus` item s ==> -- abstract over item \item s->(item >> item) s `mplus` item s turning item/fetch into a type class method is just another way of composing the grammar with an item parser. i had to implement it myself to understand what you were trying to do, and how.. if indeed i have understood?-) hth, claus
(This makes it, what, the 5th time I've explained this? LOL...)
with problem specifications, it isn't quantity that counts. the more ambiguous the specification, the more likely it is that replies interpret it in ways that do not answer the question. the fewer replies seem to address the question, the more likely it is that the specification needs to be clearer. on a high-volume list where readers might dip into and out of long threads at any point, repetition in the form of concise summaries can be helpful, even to those readers who might follow every post in every thread.

Claus Reinke wrote:
ah, that suggests yet another specification, a variation of the second version above, where the parser in control is not p1 itself, but p2, with p1 acting as an input transformation for p2, and p3 resuming where p1 left off. the difference being that p2's demand is supposed to drive p1's input processing. which is a bit of a problem.
Yep, that's the one.
parsers are usually data- and grammar-driven, not demand-driven, ie the input consumed by p1 does not usually depend on the demands on p1's output.
Yeah, I realise that. ;-) I did wonder if Parsec's #include mechanism could do it - but apparently not. So I wrote my own...
looking a little bit more closely, however, p1 is used more as a piecewise input transformation for p2 than as a separate parser. so it makes more sense to integrate p1 into p2.
Possibly - except that I want to be able to stack any decoder on top of any decoder. For *output* this is a trivial matter of function composition. For input, this presents the tricky parsing problem we're now discussing...
that seems to be what you have in mind with your stacked approach, where the state is read exclusively through the fetch method in the Source interface, and a Source can either be a plain list or buffered item parser stacked on top of a Source (where fetch is served from the buffer, which is replenished by running the item parser over the inner Source; btw, are unused buffer contents discarded when p2 finishes? they can't be transformed back into p1/p3's input format..).
That's right. (And yes, the idea is that the buffer should *always* be empty when the top parser exits. Assuming the data stream was built correctly in the first place, this should always hold...)
instead of using a type class, one could also parameterise p2 by its item parser, 'fetch'.
Mmm... that's an interesting idea. I'll have to have a think about that...

Andrew Coppin
My goal is to be able to stack multiple parsers one on top of the other - but be able to *change* the stack half way through parsing if needed.
Essentially, I have the "stacked" function, where if I do
x <- stacked foo parser1 bar parser2 y <- parser3
then it runs parser2, but it uses parser1 to transform the data first.
I can't help thinking that all you really want to do is parse the same data twice, through an intermediate representation. That only requires you to feed the result of one parse into a top-level call to a different parser. For instance: this = do tmp <- parser1 x <- return (runParser parser2 bar tmp) y <- parser3 ... = runParser this foo input In the example, 'parser2' takes a different state type, and a different source token representation from 'parser1' and 'parser3'. No fearsome stack type is needed. :-) Regards, Malcolm

Malcolm Wallace wrote:
I can't help thinking that all you really want to do is parse the same data twice, through an intermediate representation. That only requires you to feed the result of one parse into a top-level call to a different parser. For instance:
this = do tmp <- parser1 x <- return (runParser parser2 bar tmp) y <- parser3
... = runParser this foo input
In the example, 'parser2' takes a different state type, and a different source token representation from 'parser1' and 'parser3'. No fearsome stack type is needed. :-)
For the Nth time... The amount of data processed by parser1 needs to depend on the amount of data processed by parser2. (The amount of data output by each parser is very nontrivially related to the amount of data consumed.) How do you propose to pull that off?

AC> For the Nth time... The amount of data processed by parser1 needs AC> to depend on the amount of data processed by parser2. (The amount AC> of data output by each parser is very nontrivially related to the AC> amount of data consumed.) What about lazyness? Let parser1 process ALL the data and return chunks of output paired with the amount of data read; then, parser2 have to return it's result paired with the amount of data read, known from parser1, allowing parser3 to know where to start. It doesn't matter that parser1 wouldn't recognize the rest of data, since it wouldn't be fed with it due to lazyness.
participants (21)
-
Albert Y. C. Lai
-
Andrew Coppin
-
Bill Wood
-
Brandon Michael Moore
-
Brandon S. Allbery KF8NH
-
Bulat Ziganshin
-
Claus Reinke
-
Dave Bayer
-
donsīŧ cse.unsw.edu.au
-
Jonathan Cast
-
Ketil Malde
-
Logan Capaldo
-
Lukas Mai
-
Malcolm Wallace
-
Malte Milatz
-
Miguel Mitrofanov
-
Neil Mitchell
-
peterv
-
Stefan O'Rear
-
Thomas Conway
-
Tillmann Rendel