Things and limitations...

Juan Carlos Arevalo Baeza jcab@roningames.com
Mon, 14 May 2001 20:26:21 -0700


    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