[Haskell-cafe] parse error in pattern, and byte code interpreter

TP paratribulations at free.fr
Sun Jan 15 00:18:14 CET 2012


Hi everybody,

I want to test a higher level language than C/C++ (type inference, garbage 
collection), but much faster than Python. So I am naturally led to Haskell or 
OCaml.

I have read and tested tutorials for the two languages. For the time being, my 
preference goes to Haskell, first because it looks more like Python, and also 
because some things appear not so clean in OCaml, at least for a beginner (Put 
a line termination or not? Why have I to put "rec" in the definition of a 
recursive function? Etc.).

I have two questions.

1/ Inspiring from tutorials out there, I have tried to write a small formal 
program which is able to distribute n*(x+y) to n*x+n*y. The OCaml version is 
working (see Post Scriptum). However, I have difficulties to make the Haskell 
version work. This is my code:

{----------------------------------------------------}
data Expr = Plus Expr Expr
          | Minus Expr Expr
          | Times Expr Expr
          | Divide Expr Expr
          | Variable String
        deriving ( Show, Eq )

expr_to_string expr = case expr of
        Times expr1 expr2 -> "(" ++ ( expr_to_string expr1 ) ++ " * "
                            ++ ( expr_to_string expr2 ) ++ ")"
        Plus expr1 expr2 -> "(" ++ ( expr_to_string expr1 ) ++ " + "
                            ++ ( expr_to_string expr2 ) ++ ")"
        Variable var -> var

distribute expr = case expr of
     Variable var -> var
     Times expr1 Plus( expr2 expr3 ) ->
         Plus ( Times ( expr1 expr2 ) Times ( expr1 expr3 ) )

main = do
let x = Times ( Variable "n" )
        ( Plus ( Variable "x" ) ( Variable "y" ) )
print x
print ( expr_to_string x )
{----------------------------------------------------}

When I try to run this code with "runghc", I obtain:

pattern_matching_example.hs:28:24: Parse error in pattern: expr2

Thus it does not like my pattern "Times expr1 Plus( expr2 expr3 )". Why?
How can I obtain the right result, as with the OCaml code below?

2/ It seems there is no possibility to generate bytecode, contrary to OCaml. 
Is it correct? Is there an alternative?
What is interesting with bytecode run with "ocamlrun" is that the process of 
generating the bytecode is very fast, so it is very convenient to test the 
program being written, in an efficient workflow. Only at the end the program is 
compiled to get more execution speed.

Thanks a lot in advance.

TP

PS:
---
To test the OCaml tutorial, type:
$ ocamlc -o pattern_matching_example pattern_matching_example.ml
$ ocamlrun ./pattern_matching_example

(*************************************************************)
(* from OCaml tutorial, section 'data_types_and_matching.html' *)

(* This is a binary tree *)
type expr = Plus of expr * expr
          | Minus of expr * expr
          | Times of expr * expr
          | Divide of expr * expr
          | Value of string
;;

let v = Times ( Value "n", Plus (Value "x", Value "y") )

let rec to_string e =
    match e with
    Plus ( left, right ) -> "(" ^ (to_string left ) ^ " + " ^ (to_string 
right) ^ ")"
  | Minus ( left, right ) -> "(" ^ (to_string left ) ^ " - " ^ (to_string 
right) ^ ")"
  | Times ( left, right ) -> "(" ^ (to_string left ) ^ " * " ^ (to_string 
right) ^ ")"
  | Divide ( left, right ) -> "(" ^ (to_string left ) ^ " / " ^ (to_string 
right) ^ ")"
  | Value value -> value
    ;;

(* by type inference, ocaml knows that e is of type expr just below *)
let print_expr e = print_endline ( to_string e );;

print_expr v;;

let rec distribute e =
    match e with
    Times ( e1, Plus( e2, e3 ) ) ->
        Plus (Times ( distribute e1, distribute e2 )
            , Times ( distribute e1, distribute e3 ) )
  | Times ( Plus( e1, e2 ), e3 ) ->
        Plus (Times ( distribute e1, distribute e3 )
            , Times ( distribute e2, distribute e3 ) )
  | Plus ( left, right ) -> Plus ( distribute left, distribute right )
  | Minus ( left, right ) -> Minus ( distribute left, distribute right )
  | Times ( left, right ) -> Times ( distribute left, distribute right )
  | Divide ( left, right ) -> Divide ( distribute left, distribute right )
  | Value v -> Value v
;;

print_expr ( distribute v );;
(*************************************************************)



More information about the Haskell-Cafe mailing list