1

I try to run snippets from chapter 8 about functional parsers in Graham Hutton's 'Programming in Haskell' both in ghci and frege-repl. I'm not able to sequence parsers using do syntax. I have following definitions in Frege (Haskell version differs only with simpler item definition that doesn't pack and unpack String and Char and is the same as in the book):

module Parser where
type Parser a = String -> [(a, String)]   

return :: a -> Parser a
return v = \inp -> [(v, inp)]

-- this is Frege version
item :: Parser Char
item = \inp ->
  let inp' = unpacked inp
  in
    case inp' of
        [] -> []
        (x:xs) -> [(x,packed xs)]


parse :: Parser a -> String -> [(a, String)]
parse p inp = p inp

-- sequencing
(>>=) :: Parser a -> (a -> Parser b) -> Parser b
p >>= f = \inp -> case (parse p inp) of
  [] -> []
  [(v,out)] -> parse (f v) out

p :: Parser (Char, Char)
p = do x <- Parser.item
       Parser.item
       y <- Parser.item
       Parser.return (x,y)

-- this works
p' :: Parser (Char, Char)
p' = item Parser.>>= \x ->
     item Parser.>>= \_ ->
     item Parser.>>= \y ->
     Parser.return (x,y)

p' works both in ghci and frege-repl. However, when trying loading module I got those messages. First from ghci:

src/Parser.hs:38:8:
    Couldn't match type ‘[(Char, String)]’ with ‘Char’
    Expected type: String -> [((Char, Char), String)]
      Actual type: Parser ([(Char, String)], [(Char, String)])
    In a stmt of a 'do' block: Parser.return (x, y)
    In the expression:
      do { x <- item;
           item;
           y <- item;
           Parser.return (x, y) }
Failed, modules loaded: none.

frege-repl is even less friendly because it simply kicks me out from repl with an error stack trace:

 Exception in thread "main" frege.runtime.Undefined: returnTypeN: too many arguments
    at frege.prelude.PreludeBase.error(PreludeBase.java:18011)
    at frege.compiler.Utilities.returnTypeN(Utilities.java:1937)
    at frege.compiler.Utilities.returnTypeN(Utilities.java:1928)
    at frege.compiler.GenJava7$80.eval(GenJava7.java:11387)
    at frege.compiler.GenJava7$80.eval(GenJava7.java:11327)
    at frege.runtime.Fun1$1.eval(Fun1.java:63)
    at frege.runtime.Delayed.call(Delayed.java:198)
    at frege.runtime.Delayed.forced(Delayed.java:267)
    at frege.compiler.GenJava7$78.eval(GenJava7.java:11275)
    at frege.compiler.GenJava7$78.eval(GenJava7.java:11272)
    at frege.runtime.Fun1$1.eval(Fun1.java:63)
    at frege.runtime.Delayed.call(Delayed.java:200)
    at frege.runtime.Delayed.forced(Delayed.java:267)
    at frege.control.monad.State$IMonad_State$4.eval(State.java:1900)
    at frege.control.monad.State$IMonad_State$4.eval(State.java:1897)
    at frege.runtime.Fun1$1.eval(Fun1.java:63)
    at frege.runtime.Delayed.call(Delayed.java:198)
    at frege.runtime.Delayed.forced(Delayed.java:267)
    at frege.control.monad.State$IMonad_State$4.eval
...

My intuition is that I need something apart >>= and return or there is something I should tell compilers. Or maybe I need to put p definition into State monad?

libnull-dev
  • 881
  • 1
  • 7
  • 19
  • 1
    In any case, the stack trace isn't your fault, its a bug in a past version of the frege compiler. I shall check if and how this works with a newer version. – Ingo Mar 14 '16 at 22:17

2 Answers2

4

This is because String -> a is the monad that is being used in your do notation, since one of the instances of Monad in the Prelude is the function arrow.

Therefore, for example, the x in x <- Parser.item is an argument of type [(Char, String)].

You can get around this by making Parser a newtype and defining your own custom Monad instance for it.

badcook
  • 3,699
  • 14
  • 25
  • 3
    This answer is correct, but it is worth emphasizing this point: simply defining `(>>=)` and `return` is not sufficient; these must be defined as methods in a `Monad` instance declaration to connect these names with `do` notation. – Daniel Wagner Mar 15 '16 at 01:21
  • Or `RebindableSyntax`... But __don't do that here. That would be bad.__ Just make them methods in an instance of `Monad` like @DanielWagner says. – badcook Mar 15 '16 at 01:45
  • @badcook do you mean `newtype Parser a = Parser (String -> [(a, String)])` ; `instance Monad Parser where return :: a -> Parser a; return v = Parser (\inp -> [(v, inp)]); (>>=) :: Parser a -> (a -> Parser b) -> Parser b; p >>= f = \inp -> case parse p inp of [] -> Parser [] [(v,out)] -> Parser ((f v) out)` ? – libnull-dev Mar 15 '16 at 17:09
  • @libnull-dev yup. You'll probably need `Applicative` and `Functor` instances as well, but you can use `ap` and `liftM` for that. – badcook Mar 15 '16 at 17:57
  • thanks, however this makes my head just blowing. is there any solution for someone new to Haskell who has just read 10 chapters of this book? – libnull-dev Mar 15 '16 at 18:27
  • @libnull-dev I'm afraid I might have made things more complicated than they should have been by off-handedly throwing `Applicative` and `Functor` at you. If anything about my response is too complicated, let me know. If we make this comment chain long enough, we can go to chat and I'm happy to explain more there. [I would prefer to directly move it to chat, but I can't...](https://meta.stackexchange.com/questions/106467/how-can-i-move-a-discussion-to-chat-before-being-prompted) – badcook Mar 16 '16 at 05:50
  • @badcook I really appreciate your answer and in fact it pushed me into very interesting investigations. Simply, I'm too novice to use it straight away. I'm sure you will see more weird questions coming from me in the future. – libnull-dev Mar 16 '16 at 11:30
1

The following works with Frege (and should work the same way with GHC language extension RebindableSyntax):

module P
    where


type Parser a = String -> [(a, String)]   

return :: a -> Parser a
return v = \inp -> [(v, inp)]

-- this is Frege version
item :: Parser Char
item  = maybeToList . uncons


parse :: Parser a -> String -> [(a, String)]
parse p inp = p inp

-- sequencing
(>>=) :: Parser a -> (a -> Parser b) -> Parser b
p >>= f = \inp -> case (parse p inp) of
  [] -> []
  [(v,out)] -> parse (f v) out

p :: Parser (Char, Char)
p = do 
    x <- item
    item
    y <- item
    return (x,y)

main = println (p "Frege is cool")

It prints:

[(('F', 'r'), "ege is cool")]

The main difference to your version is a more efficient item function, but, as I said before, this is not the reason for the stack trace. And there was this small indentation problem with the do in your code.

So yes, you can use the do notation here, though some would call it "abuse".

Ingo
  • 36,037
  • 5
  • 53
  • 100
  • It works in Frege. It seemed to me like silly indentation problem at first, but when trying to compile it with `ghc -XRebindableSyntax` and after adding necessary imports I got `Ambiguous occurrence ‘return’ It could refer to either ‘P.return’, defined at src/Parser.hs:19:1 or ‘Prelude.return’, imported from ‘Prelude’ at src/Parser.hs:1:8-17 (and originally defined in ‘GHC.Base’)`. Anyway, I keep reading with hope that one day I'll get what @badcook was kindly trying to explain to me. – libnull-dev Mar 15 '16 at 23:21
  • @libnull-dev haskell is more picky about redefined identifiers like return. So you just write P.return or import Prelude hiding (return) – Ingo Mar 16 '16 at 15:36