diff options
Diffstat (limited to 'parsing')
-rw-r--r-- | parsing/asttypes.mli | 4 | ||||
-rw-r--r-- | parsing/label.ml | 2 | ||||
-rw-r--r-- | parsing/label.mli | 2 | ||||
-rw-r--r-- | parsing/lexer.mli | 4 | ||||
-rw-r--r-- | parsing/lexer.mll | 53 | ||||
-rw-r--r-- | parsing/location.ml | 4 | ||||
-rw-r--r-- | parsing/location.mli | 4 | ||||
-rw-r--r-- | parsing/longident.ml | 4 | ||||
-rw-r--r-- | parsing/longident.mli | 4 | ||||
-rw-r--r-- | parsing/parse.ml | 4 | ||||
-rw-r--r-- | parsing/parse.mli | 4 | ||||
-rw-r--r-- | parsing/parser.mly | 31 | ||||
-rw-r--r-- | parsing/parsetree.mli | 4 | ||||
-rw-r--r-- | parsing/pstream.ml | 4 | ||||
-rw-r--r-- | parsing/pstream.mli | 6 |
15 files changed, 72 insertions, 62 deletions
diff --git a/parsing/asttypes.mli b/parsing/asttypes.mli index ce0f30648..4431233d5 100644 --- a/parsing/asttypes.mli +++ b/parsing/asttypes.mli @@ -1,10 +1,10 @@ (***********************************************************************) (* *) -(* Caml Special Light *) +(* Objective Caml *) (* *) (* Xavier Leroy, projet Cristal, INRIA Rocquencourt *) (* *) -(* Copyright 1995 Institut National de Recherche en Informatique et *) +(* Copyright 1996 Institut National de Recherche en Informatique et *) (* Automatique. Distributed only by permission. *) (* *) (***********************************************************************) diff --git a/parsing/label.ml b/parsing/label.ml index dd9fd309c..54d1cdc2c 100644 --- a/parsing/label.ml +++ b/parsing/label.ml @@ -1,6 +1,6 @@ (***********************************************************************) (* *) -(* Caml Special Light *) +(* Objective Caml *) (* *) (* Jerome Vouillon, projet Cristal, INRIA Rocquencourt *) (* *) diff --git a/parsing/label.mli b/parsing/label.mli index 88b191288..9f37415cc 100644 --- a/parsing/label.mli +++ b/parsing/label.mli @@ -1,6 +1,6 @@ (***********************************************************************) (* *) -(* Caml Special Light *) +(* Objective Caml *) (* *) (* Jerome Vouillon, projet Cristal, INRIA Rocquencourt *) (* *) diff --git a/parsing/lexer.mli b/parsing/lexer.mli index 5d3af4086..330d565e2 100644 --- a/parsing/lexer.mli +++ b/parsing/lexer.mli @@ -1,10 +1,10 @@ (***********************************************************************) (* *) -(* Caml Special Light *) +(* Objective Caml *) (* *) (* Xavier Leroy, projet Cristal, INRIA Rocquencourt *) (* *) -(* Copyright 1995 Institut National de Recherche en Informatique et *) +(* Copyright 1996 Institut National de Recherche en Informatique et *) (* Automatique. Distributed only by permission. *) (* *) (***********************************************************************) diff --git a/parsing/lexer.mll b/parsing/lexer.mll index 21e987a44..4929e14d5 100644 --- a/parsing/lexer.mll +++ b/parsing/lexer.mll @@ -1,10 +1,10 @@ (***********************************************************************) (* *) -(* Caml Special Light *) +(* Objective Caml *) (* *) (* Xavier Leroy, projet Cristal, INRIA Rocquencourt *) (* *) -(* Copyright 1995 Institut National de Recherche en Informatique et *) +(* Copyright 1996 Institut National de Recherche en Informatique et *) (* Automatique. Distributed only by permission. *) (* *) (***********************************************************************) @@ -186,48 +186,53 @@ rule token = parse start_pos := Lexing.lexeme_start lexbuf; comment lexbuf; token lexbuf } - | "#" { SHARP } - | "&" { AMPERSAND } + | "#" { SHARP } + | "&" { AMPERSAND } | "&&" { AMPERAMPER } - | "'" { QUOTE } - | "(" { LPAREN } - | ")" { RPAREN } - | "*" { STAR } - | "," { COMMA } - | "?" { QUESTION } + | "'" { QUOTE } + | "(" { LPAREN } + | ")" { RPAREN } + | "*" { STAR } + | "," { COMMA } + | "?" { QUESTION } | "->" { MINUSGREATER } - | "." { DOT } + | "." { DOT } | ".." { DOTDOT } - | ":" { COLON } + | ":" { COLON } | "::" { COLONCOLON } | ":=" { COLONEQUAL } | ":>" { COLONGREATER } - | ";" { SEMI } + | ";" { SEMI } | ";;" { SEMISEMI } + | "<" { LESS } | "<-" { LESSMINUS } - | "=" { EQUAL } - | "[" { LBRACKET } + | "=" { EQUAL } + | "[" { LBRACKET } | "[|" { LBRACKETBAR } | "[<" { LBRACKETLESS } - | "]" { RBRACKET } - | "_" { UNDERSCORE } - | "{" { LBRACE } + | "]" { RBRACKET } + | "_" { UNDERSCORE } + | "{" { LBRACE } | "{<" { LBRACELESS } - | "|" { BAR } + | "|" { BAR } | "||" { BARBAR } | "|]" { BARRBRACKET } + | ">" { GREATER } | ">]" { GREATERRBRACKET } - | "}" { RBRACE } + | "}" { RBRACE } | ">}" { GREATERRBRACE } - | "!=" { INFIXOP1 "!=" } - | "-" { SUBTRACTIVE "-" } - | "-." { SUBTRACTIVE "-." } + | "!=" { INFIXOP0 "!=" } + | "-" { SUBTRACTIVE "-" } + | "-." { SUBTRACTIVE "-." } | ['!' '?' '~'] ['!' '$' '%' '&' '*' '+' '-' '.' '/' ':' '<' '=' '>' '?' '@' '^' '|' '~'] * { PREFIXOP(Lexing.lexeme lexbuf) } - | ['=' '<' '>' '@' '^' '|' '&' '$'] + | ['=' '<' '>' '|' '&' '$'] + ['!' '$' '%' '&' '*' '+' '-' '.' '/' ':' '<' '=' '>' '?' '@' '^' '|' '~'] * + { INFIXOP0(Lexing.lexeme lexbuf) } + | ['@' '^'] ['!' '$' '%' '&' '*' '+' '-' '.' '/' ':' '<' '=' '>' '?' '@' '^' '|' '~'] * { INFIXOP1(Lexing.lexeme lexbuf) } | ['+' '-'] diff --git a/parsing/location.ml b/parsing/location.ml index 7de0845bf..82d6a2a61 100644 --- a/parsing/location.ml +++ b/parsing/location.ml @@ -1,10 +1,10 @@ (***********************************************************************) (* *) -(* Caml Special Light *) +(* Objective Caml *) (* *) (* Xavier Leroy, projet Cristal, INRIA Rocquencourt *) (* *) -(* Copyright 1995 Institut National de Recherche en Informatique et *) +(* Copyright 1996 Institut National de Recherche en Informatique et *) (* Automatique. Distributed only by permission. *) (* *) (***********************************************************************) diff --git a/parsing/location.mli b/parsing/location.mli index 1509620e7..01afb75d9 100644 --- a/parsing/location.mli +++ b/parsing/location.mli @@ -1,10 +1,10 @@ (***********************************************************************) (* *) -(* Caml Special Light *) +(* Objective Caml *) (* *) (* Xavier Leroy, projet Cristal, INRIA Rocquencourt *) (* *) -(* Copyright 1995 Institut National de Recherche en Informatique et *) +(* Copyright 1996 Institut National de Recherche en Informatique et *) (* Automatique. Distributed only by permission. *) (* *) (***********************************************************************) diff --git a/parsing/longident.ml b/parsing/longident.ml index 243cb3d0d..82e499027 100644 --- a/parsing/longident.ml +++ b/parsing/longident.ml @@ -1,10 +1,10 @@ (***********************************************************************) (* *) -(* Caml Special Light *) +(* Objective Caml *) (* *) (* Xavier Leroy, projet Cristal, INRIA Rocquencourt *) (* *) -(* Copyright 1995 Institut National de Recherche en Informatique et *) +(* Copyright 1996 Institut National de Recherche en Informatique et *) (* Automatique. Distributed only by permission. *) (* *) (***********************************************************************) diff --git a/parsing/longident.mli b/parsing/longident.mli index bbe7ef2e0..9835c3380 100644 --- a/parsing/longident.mli +++ b/parsing/longident.mli @@ -1,10 +1,10 @@ (***********************************************************************) (* *) -(* Caml Special Light *) +(* Objective Caml *) (* *) (* Xavier Leroy, projet Cristal, INRIA Rocquencourt *) (* *) -(* Copyright 1995 Institut National de Recherche en Informatique et *) +(* Copyright 1996 Institut National de Recherche en Informatique et *) (* Automatique. Distributed only by permission. *) (* *) (***********************************************************************) diff --git a/parsing/parse.ml b/parsing/parse.ml index fdb3ec6d9..7cf8caff2 100644 --- a/parsing/parse.ml +++ b/parsing/parse.ml @@ -1,10 +1,10 @@ (***********************************************************************) (* *) -(* Caml Special Light *) +(* Objective Caml *) (* *) (* Xavier Leroy, projet Cristal, INRIA Rocquencourt *) (* *) -(* Copyright 1995 Institut National de Recherche en Informatique et *) +(* Copyright 1996 Institut National de Recherche en Informatique et *) (* Automatique. Distributed only by permission. *) (* *) (***********************************************************************) diff --git a/parsing/parse.mli b/parsing/parse.mli index f1eaf3464..ddd58daa1 100644 --- a/parsing/parse.mli +++ b/parsing/parse.mli @@ -1,10 +1,10 @@ (***********************************************************************) (* *) -(* Caml Special Light *) +(* Objective Caml *) (* *) (* Xavier Leroy, projet Cristal, INRIA Rocquencourt *) (* *) -(* Copyright 1995 Institut National de Recherche en Informatique et *) +(* Copyright 1996 Institut National de Recherche en Informatique et *) (* Automatique. Distributed only by permission. *) (* *) (***********************************************************************) diff --git a/parsing/parser.mly b/parsing/parser.mly index 1535626f9..ac80d29f1 100644 --- a/parsing/parser.mly +++ b/parsing/parser.mly @@ -1,10 +1,10 @@ /***********************************************************************/ /* */ -/* Caml Special Light */ +/* Objective Caml */ /* */ /* Xavier Leroy, projet Cristal, INRIA Rocquencourt */ /* */ -/* Copyright 1995 Institut National de Recherche en Informatique et */ +/* Copyright 1996 Institut National de Recherche en Informatique et */ /* Automatique. Distributed only by permission. */ /* */ /***********************************************************************/ @@ -116,11 +116,13 @@ let rec mkrangepat c1 c2 = %token FUN %token FUNCTION %token FUNCTOR +%token GREATER %token GREATERRBRACE %token GREATERRBRACKET %token IF %token IN %token INCLUDE +%token <string> INFIXOP0 %token <string> INFIXOP1 %token <string> INFIXOP2 %token <string> INFIXOP3 @@ -132,6 +134,7 @@ let rec mkrangepat c1 c2 = %token LBRACKET %token LBRACKETBAR %token LBRACKETLESS +%token LESS %token LESSMINUS %token LET %token <string> LIDENT @@ -190,7 +193,8 @@ let rec mkrangepat c1 c2 = %right prec_type_arrow /* -> in type expressions */ %right OR BARBAR /* or */ %right AMPERSAND AMPERAMPER /* & */ -%left INFIXOP1 EQUAL /* = < > etc */ +%left INFIXOP0 EQUAL LESS GREATER /* = < > etc */ +%right INFIXOP1 /* @ ^ etc */ %right COLONCOLON /* :: */ %left INFIXOP2 SUBTRACTIVE /* + - */ %left INFIXOP3 STAR /* * / */ @@ -387,6 +391,8 @@ expr: { mkexp(Pexp_for($2, $4, $6, $5, $8)) } | expr COLONCOLON expr { mkexp(Pexp_construct(Lident "::", Some(mkexp(Pexp_tuple[$1;$3])))) } + | expr INFIXOP0 expr + { mkinfix $1 $2 $3 } | expr INFIXOP1 expr { mkinfix $1 $2 $3 } | expr INFIXOP2 expr @@ -401,6 +407,10 @@ expr: { mkinfix $1 "*" $3 } | expr EQUAL expr { mkinfix $1 "=" $3 } + | expr LESS expr + { mkinfix $1 "<" $3 } + | expr GREATER expr + { mkinfix $1 ">" $3 } | expr OR expr { mkinfix $1 "or" $3 } | expr BARBAR expr @@ -867,9 +877,9 @@ simple_core_type: { mktyp(Ptyp_constr($4, List.rev $2, $5)) } | LPAREN core_type RPAREN { $2 } - | less meth_list more alias + | LESS meth_list GREATER alias { mktyp(Ptyp_object($2, $4)) } - | less more alias + | LESS GREATER alias { mktyp(Ptyp_object([], $3)) } | SHARP class_longident alias { mktyp(Ptyp_class($2, [], $3)) } @@ -885,14 +895,6 @@ alias: | /* empty */ {None} ; -less: - INFIXOP1 - { if $1 <> "<" then raise Parse_error } -; -more: - INFIXOP1 - { if $1 <> ">" then raise Parse_error } -; core_type_tuple: simple_core_type STAR simple_core_type { [$3; $1] } @@ -949,6 +951,7 @@ val_ident: ; operator: PREFIXOP { $1 } + | INFIXOP0 { $1 } | INFIXOP1 { $1 } | INFIXOP2 { $1 } | INFIXOP3 { $1 } @@ -956,6 +959,8 @@ operator: | SUBTRACTIVE { $1 } | STAR { "*" } | EQUAL { "=" } + | LESS { "<" } + | GREATER { ">" } | OR { "or" } | BARBAR { "||" } | AMPERSAND { "&" } diff --git a/parsing/parsetree.mli b/parsing/parsetree.mli index ea8356a7e..be7db29fa 100644 --- a/parsing/parsetree.mli +++ b/parsing/parsetree.mli @@ -1,10 +1,10 @@ (***********************************************************************) (* *) -(* Caml Special Light *) +(* Objective Caml *) (* *) (* Xavier Leroy, projet Cristal, INRIA Rocquencourt *) (* *) -(* Copyright 1995 Institut National de Recherche en Informatique et *) +(* Copyright 1996 Institut National de Recherche en Informatique et *) (* Automatique. Distributed only by permission. *) (* *) (***********************************************************************) diff --git a/parsing/pstream.ml b/parsing/pstream.ml index c94d244b8..4e7d00123 100644 --- a/parsing/pstream.ml +++ b/parsing/pstream.ml @@ -1,10 +1,10 @@ (***********************************************************************) (* *) -(* Caml Special Light *) +(* Objective Caml *) (* *) (* Daniel de Rauglaudre, projet Cristal, INRIA Rocquencourt *) (* *) -(* Copyright 1995 Institut National de Recherche en Informatique et *) +(* Copyright 1996 Institut National de Recherche en Informatique et *) (* Automatique. Distributed only by permission. *) (* *) (***********************************************************************) diff --git a/parsing/pstream.mli b/parsing/pstream.mli index fb4f6c68c..6d478abee 100644 --- a/parsing/pstream.mli +++ b/parsing/pstream.mli @@ -1,17 +1,17 @@ (***********************************************************************) (* *) -(* Caml Special Light *) +(* Objective Caml *) (* *) (* Daniel de Rauglaudre, projet Cristal, INRIA Rocquencourt *) (* *) -(* Copyright 1995 Institut National de Recherche en Informatique et *) +(* Copyright 1996 Institut National de Recherche en Informatique et *) (* Automatique. Distributed only by permission. *) (* *) (***********************************************************************) (* $Id$ *) -(* Conversion of streams and parsers into Caml-Special-Light syntax *) +(* Conversion of streams and parsers into Objective Caml syntax *) open Parsetree |