
Hi. First of all, I'm new to Haskell, so greetings to all listeners. And I come from the oh-so-ever-present world of C/C++ and such. Thinking in Haskell is quite different, so if you see me thinking in the wrong way, please, do point it out. That said, I want to make it clear that I'm seriously trying to understand the inner workings of a language like Haskell (I've already implemented a little toy lazy evaluator, which was great in understanding how this can all work). Only recently have I come to really understand (I hope) what a monad is (and it was extremely elusive for a while). It was a real struggle for a while :-) At 01:36 PM 5/14/2001 -0700, Bryn Keller wrote:
The only concrete example of something that confuses me I can recall is the fact that this compiles:
main = do allLines <- readLines; putStr $ unlines allLines where readLines = do eof <- isEOF if eof then return [] else do line <- getLine allLines <- readLines return (line : allLines)
but this doesn't:
main = do putStr $ unlines readLines where readLines = do eof <- isEOF if eof then return [] else do line <- getLine allLines <- readLines return (line : allLines)
Evidently this is wrong, but my intuition is that <- simply binds a name to a value, and that:
foo <- somefunc bar foo
should be identical to:
bar somefunc
Yes. I'd even shorten that to: --- Valid readLines = do eof <- isEOF if eof then ... --- as opposed to: --- invalid readLines = do if isEOF then ... --- The reason behind this is, evidently, due to the fact that the do-notation is just a little bit of syntactic sugar for monads. It can't "look into" the parameter to "if" to do the monad transfer. In fact, even if it could look into the if, it wouldn't work without heavy processing. It would need to do it EXACTLY in that manner (providing a hidden binding before expression that uses the bound value). And you'd still have lots of problems dealing with order of execution. Just think of this example: --- myfunction = do if readChar > readChar then ... --- our hypothetical smarter-do-notation would need to generate one of the following: --- myfunction = do char1 <- readChar char2 <- readChar if char1 < char2 then ... --- or: --- myfunction = do char2 <- readChar char1 <- readChar if char1 < char2 then ... --- but which is the correct? In this case, you might want to define rules saying that the first is 'obviously' the correct one. But with more complex operations and expressions it might not be possible. Or you might want to leave it ambiguous. But that is quite against the spirit of Haskell, I believe. In any case, forcing the programmer to be more explicit in these matters is, I believe, a good thing. Same as not allowing circular references between modules, for example. Anyway... I have been toying a bit with Haskell lately, and I have several questions: First, about classes of heavily parametric types. Can't be done, I believe. At least, I haven't been able to. What I was trying to do (as an exercise to myself) was reconverting Graham Hutton and Erik Meijer's monadic parser library into a class. Basically, I was trying to convert the static: --- newtype Parser a = P (String -> [(a,String)]) item :: Parser Char force :: Parser a -> Parser a first :: Parser a -> Parser a papply :: Parser a -> String -> [(a,String)] --- --- class (MonadPlus (p s v)) => Parser p where item :: p s v v force :: p s v a -> p s v a first :: p s v a -> p s v a papply :: p s v a -> s -> [(a,s)] --- I have at home the actual code I tried to make work, so I can't just copy/paste it, but it looked something like this. Anyway, this class would allow me to define parsers that parse any kind of thing ('s', which was 'String' in the original lib), from which you can extract any kind of element ('v', which was 'Char') and parse it into arbitrary types (the original parameter 'a'). For example, with this you could parse, say, a recursive algebraic data structure into something else. Nhc98 wouldn't take it. I assume this is NOT proper Haskell. The questions are: Is this doable? If so, how? Is this not recommendable? If not, why? I had an idea about how to make this much more palatable. It would be something like: --- class (MonadPlus p) => Parser p where type Source type Value item :: p Value force :: p a -> p a first :: p a -> p a papply :: p a -> Source -> [(a,Source)] --- So individual instances of Parser would define the actual type aliases Source and Value. Again, though, this is NOT valid Haskell. Questions: Am I being unreasonable here? Why? Ok, last, I wanted to alias a constructor. So: --- module MyModule(Type, TypeCons) where newtype Type = TypeCons Integer instance SomeClass Type where .... --- --- module Main where import MyModule newtype NewType = NewTypeCons Type --- So, now, if I want to construct a NewType, I need to do something like: --- kk = NewTypeCons (TypeCons 5) --- And if I want to pattern-match a NewType value, I have to use both constructors again. It's quite a pain. I've tried to make a constructor that can do it in one shot, but I've been unable. Tried things like: --- AnotherCons i = NewTypeCons (TypeCons i) --- but nothing works. Again, the same questions: Is it doable? Am I being unreasonable here? Salutaciones, JCAB --------------------------------------------------------------------- Juan Carlos "JCAB" Arevalo Baeza | http://www.roningames.com Senior Technology programmer | mailto:jcab@roningames.com Ronin Entertainment | ICQ: 10913692 (my opinions are only mine) JCAB's Rumblings: http://www.metro.net/jcab/Rumblings/html/index.html

Is there an efficient way to make simple databases in Haskell? I mean something like a dictionary, hash table or associative container of some kind. I'm aware that Haskell being pure functional means that those things are not as easily implemented as they can be in other languages, in fact, I've implemented a simple one myself, using a list of pairs (key,value) (which means it's slow on lookup) and an optional monad to handle the updates/lookups. I guess what I'm wondering is what has been done in this respect. There is no such thing in the standard library, as far as I can see, and my search through the web has turned up nothing. Salutaciones, JCAB --------------------------------------------------------------------- Juan Carlos "JCAB" Arevalo Baeza | http://www.roningames.com Senior Technology programmer | mailto:jcab@roningames.com Ronin Entertainment | ICQ: 10913692 (my opinions are only mine) JCAB's Rumblings: http://www.metro.net/jcab/Rumblings/html/index.html

Juan Carlos Arevalo Baeza writes: : | First, about classes of heavily parametric types. Can't be done, I | believe. At least, I haven't been able to. What I was trying to do (as an | exercise to myself) was reconverting Graham Hutton and Erik Meijer's | monadic parser library into a class. Basically, I was trying to convert the | static: | | --- | newtype Parser a = P (String -> [(a,String)]) | item :: Parser Char | force :: Parser a -> Parser a | first :: Parser a -> Parser a | papply :: Parser a -> String -> [(a,String)] | --- | | --- | class (MonadPlus (p s v)) => Parser p where | item :: p s v v | force :: p s v a -> p s v a | first :: p s v a -> p s v a | papply :: p s v a -> s -> [(a,s)] | --- | | I have at home the actual code I tried to make work, so I can't just | copy/paste it, but it looked something like this. Anyway, this class would | allow me to define parsers that parse any kind of thing ('s', which was | 'String' in the original lib), from which you can extract any kind of | element ('v', which was 'Char') and parse it into arbitrary types (the | original parameter 'a'). For example, with this you could parse, say, a | recursive algebraic data structure into something else. | | Nhc98 wouldn't take it. I assume this is NOT proper Haskell. The | questions are: Is this doable? If so, how? Is this not recommendable? If | not, why? I did something similar recently, but took the approach of adding more parameters to newtype Parser, rather than converting it into a class. Here's how it begins: type Indent = Int type IL a = [(a, Indent)] newtype Parser a m b = P (Indent -> IL a -> m (b, Indent, IL a)) instance Monad m => Monad (Parser a m) where return v = P (\ind inp -> return (v, ind, inp)) (P p) >>= f = P (\ind inp -> do (v, ind', inp') <- p ind inp let (P p') = f v p' ind' inp') fail s = P (\ind inp -> fail s) instance MonadPlus m => MonadPlus (Parser a m) where mzero = P (\ind inp -> mzero) (P p) `mplus` (P q) = P (\ind inp -> (p ind inp `mplus` q ind inp)) item :: MonadPlus m => Parser a m a item = P p where p ind [] = mzero p ind ((x, i):inp) | i < ind = mzero | otherwise = return (x, ind, inp) This differs from Hutton's and Meijer's original in these regards: - It's generalised over the input token type: the `a' in `Parser a m b' is not necessarily Char. - It's generalised over the MonadPlus type in which the result is given: the `m' in `Parser a m b' is not necessarily []. - It's specialised for parsing with a layout rule: there's an indentation level in the state, and each input token is expected to be accompanied by an indentation level. You could try something similar for your generalisations: newtype Parser ct r = P (ct -> [(r, ct)]) -- ct: collection of tokens, r: result instance SuitableCollection ct => Monad (Parser ct) where ... instance SuitableCollection ct => MonadPlus (Parser ct) where ... item :: Collects ct t => Parser ct t force :: Parser ct r -> Parser ct r first :: Parser ct r -> Parser ct r papply :: Parser ct r -> ct -> [(r, ct)] The `SuitableCollection' class is pretty hard to define, though. Either it constrains its members to be list-shaped, or it prevents you from reusing functions like `item'. Hmmm... I think I've just stumbled across your reason for treating Parser as a class. When the input isn't list-shaped, is the activity still called parsing? Or is it a generalised fold (of the input type) and unfold (of the result type)? Regards, Tom

At 04:50 PM 5/15/2001 +1200, Tom Pledger wrote:
I did something similar recently, but took the approach of adding more parameters to newtype Parser, rather than converting it into a class.
Yes, that's how I started.
You could try something similar for your generalisations:
newtype Parser ct r = P (ct -> [(r, ct)]) -- ct: collection of tokens, r: result
This is EXACTLY how I started :)
instance SuitableCollection ct => Monad (Parser ct) where ...
instance SuitableCollection ct => MonadPlus (Parser ct) where ...
item :: Collects ct t => Parser ct t force :: Parser ct r -> Parser ct r first :: Parser ct r -> Parser ct r papply :: Parser ct r -> ct -> [(r, ct)]
The `SuitableCollection' class is pretty hard to define, though. Either it constrains its members to be list-shaped, or it prevents you from reusing functions like `item'. Hmmm... I think I've just stumbled across your reason for treating Parser as a class.
:) Maybe. Thanx for your help, though.
When the input isn't list-shaped, is the activity still called parsing? Or is it a generalised fold (of the input type) and unfold (of the result type)?
Actually, I guess you can call it destructive pattern-matching. Salutaciones, JCAB --------------------------------------------------------------------- Juan Carlos "JCAB" Arevalo Baeza | http://www.roningames.com Senior Technology programmer | mailto:jcab@roningames.com Ronin Entertainment | ICQ: 10913692 (my opinions are only mine) JCAB's Rumblings: http://www.metro.net/jcab/Rumblings/html/index.html

At 04:50 PM 5/15/2001 +1200, Tom Pledger wrote:
| --- | class (MonadPlus (p s v)) => Parser p where | item :: p s v v | force :: p s v a -> p s v a | first :: p s v a -> p s v a | papply :: p s v a -> s -> [(a,s)] | ---
[...]
The `SuitableCollection' class is pretty hard to define, though. Either it constrains its members to be list-shaped, or it prevents you from reusing functions like `item'. Hmmm... I think I've just stumbled across your reason for treating Parser as a class.
When the input isn't list-shaped, is the activity still called parsing? Or is it a generalised fold (of the input type) and unfold (of the result type)?
Well, it looks like Justin's answer to my "Databases" thread gave me the clue. What I want is called "Multiple parameter classes". Okasaki's code for implementing sets uses this extension to make a Set class. It wouldn't compile with nhc98 either, so I tried Hugs, which does support it if extensions are enabled, and has, in its documentation, a very nice explanation of the tradeoffs that using this extension entails. So, what I really want is something like: class (MonadPlus (p s v)) => Parser p s v | s -> v where item :: p s v v force :: p s v a -> p s v a first :: p s v a -> p s v a papply :: p s v a -> s -> [(a,s)] I haven't had the time to play with this yet, but it sounds promising... In case anyone is interested in the Hugs documentation of the feature: http://www.cse.ogi.edu/PacSoft/projects/Hugs/pages/hugsman/exts.html#exts Salutaciones, JCAB --------------------------------------------------------------------- Juan Carlos "JCAB" Arevalo Baeza | http://www.roningames.com Senior Technology programmer | mailto:jcab@roningames.com Ronin Entertainment | ICQ: 10913692 (my opinions are only mine) JCAB's Rumblings: http://www.metro.net/jcab/Rumblings/html/index.html

Mon, 14 May 2001 20:26:21 -0700, Juan Carlos Arevalo Baeza
class (MonadPlus (p s v)) => Parser p where item :: p s v v force :: p s v a -> p s v a first :: p s v a -> p s v a papply :: p s v a -> s -> [(a,s)]
This MonadPlus superclass can't be written. The Parser class is overloaded only on p and must work uniformly on s and v, which can be expressed for functions (by using s and v as here: type variables not mentioned elsewhere), but can't for superclasses. What you want here is this: class (forall s v. MonadPlus (p s v)) => Parser p where which is not supported by any Haskell implementation (but I hope it will: it's not the first case when it would be useful). This should work on implementations supporting multiparameter type classes (ghc and Hugs): class (MonadPlus (p s v)) => Parser p s v where item :: p s v v force :: p s v a -> p s v a first :: p s v a -> p s v a papply :: p s v a -> s -> [(a,s)] Well, having (p s v) in an argument of a superclass context is not standard too :-( Haskell98 requires types here to be type variables. It requires that each parser type is parametrized by s and v; a concrete parser type with hardwired String can't be made an instance of this class, unless wrapped in a type which provides these parameters. The best IMHO solution uses yet another extension: functional dependencies. class (MonadPlus p) => Parser p s v | p -> s v where item :: p v force :: p a -> p a first :: p a -> p a papply :: p a -> s -> [(a,s)] Having a fundep allows to have methods which don't have v and s in their types. The fundep states that a single parser parses only one type of input and only one type of tokens, so the type will be implicitly deduced from the type of parser itself, basing on available instances. Well, I think that s will always be [v], so it can be simplified thus: class (MonadPlus p) => Parser p v | p -> v where item :: p v force :: p a -> p a first :: p a -> p a papply :: p a -> [v] -> [(a,[v])] Without fundeps it could be split into classes depending on which methods require v: class (MonadPlus p) => BasicParser p where force :: p a -> p a first :: p a -> p a class (BasicParser p) => Parser p v where item :: p v papply :: p a -> [v] -> [(a,[v])] This differs from the fundep solution that sometimes an explicit type constraint must be used to disambiguate the type of v, because the declaration states that the same parser could parse different types of values. Well, perhaps this is what you want and item :: SomeConcreteParser Char could give one character where item :: SomeConcreteParser (Char,Char) gives two? In any case using item in a way which doesn't tell which item type to use is an error.
Ok, last, I wanted to alias a constructor. So:
There is no such thing. A constructor can't be renamed. You would have to wrap the type inside the constructor in a new constructor. -- __("< Marcin Kowalczyk * qrczak@knm.org.pl http://qrczak.ids.net.pl/ \__/ ^^ SYGNATURA ZASTÊPCZA QRCZAK

I have made something very similar, and it worked. That work is reported in the paper "Generic Parser Combinators" published in the 2nd Latin-American Conference on Functional Programming (CLaPF). You can download it from ftp://sol.info.unlp.edu.ar/pub/papers/theory/fp/2ndCLaPF/Papers/mlopez2.ps.gz There I have made Hutton's parsers, Fokker's parsers and Rojemo's parsers instances of a class Parser that looks similar to what you have attempted. But it uses multiparameter type clases. Sadly, Swiestra's parsers cannot be made instances of this class, because they are not monads. I hope this will help you. FF Juan Carlos Arevalo Baeza wrote:
First, about classes of heavily parametric types. Can't be done, I believe. At least, I haven't been able to. What I was trying to do (as an exercise to myself) was reconverting Graham Hutton and Erik Meijer's monadic parser library into a class. Basically, I was trying to convert the static:
--- newtype Parser a = P (String -> [(a,String)]) item :: Parser Char force :: Parser a -> Parser a first :: Parser a -> Parser a papply :: Parser a -> String -> [(a,String)] ---
--- class (MonadPlus (p s v)) => Parser p where item :: p s v v force :: p s v a -> p s v a first :: p s v a -> p s v a papply :: p s v a -> s -> [(a,s)] ---
I have at home the actual code I tried to make work, so I can't just copy/paste it, but it looked something like this. Anyway, this class would allow me to define parsers that parse any kind of thing ('s', which was 'String' in the original lib), from which you can extract any kind of element ('v', which was 'Char') and parse it into arbitrary types (the original parameter 'a'). For example, with this you could parse, say, a recursive algebraic data structure into something else.
Nhc98 wouldn't take it. I assume this is NOT proper Haskell. The questions are: Is this doable? If so, how? Is this not recommendable? If not, why?
participants (4)
-
Juan Carlos Arevalo Baeza
-
Marcin 'Qrczak' Kowalczyk
-
Pablo E. Martinez Lopez
-
Tom Pledger