Revert "Add a special syntax for index operators"
This reverts commit 16bc43219c
.
(Conflict resolution: bytecomp/translcore.ml:prim_makearray was
dead code and has since been removed)
master
parent
1b8909d332
commit
1552d30d16
BIN
boot/ocamlc
BIN
boot/ocamlc
Binary file not shown.
BIN
boot/ocamldep
BIN
boot/ocamldep
Binary file not shown.
|
@ -299,30 +299,6 @@ let primitives_table = create_hashtable 57 [
|
|||
"%int_as_pointer", Pint_as_pointer;
|
||||
]
|
||||
|
||||
let index_primitives_table =
|
||||
let make_ba_ref n =
|
||||
"%caml_ba_opt_ref_"^(string_of_int n),
|
||||
fun () -> Pbigarrayref(!Clflags.fast, n, Pbigarray_unknown,
|
||||
Pbigarray_unknown_layout)
|
||||
and make_ba_set n =
|
||||
"%caml_ba_opt_set_"^(string_of_int n),
|
||||
fun () -> Pbigarrayset(!Clflags.fast, n, Pbigarray_unknown,
|
||||
Pbigarray_unknown_layout)
|
||||
in
|
||||
create_hashtable 10 [
|
||||
"%array_opt_get", ( fun () -> if !Clflags.fast then Parrayrefu Pgenarray
|
||||
else Parrayrefs Pgenarray );
|
||||
"%array_opt_set", ( fun () -> if !Clflags.fast then Parraysetu Pgenarray
|
||||
else Parraysets Pgenarray );
|
||||
"%string_opt_get", ( fun () -> if !Clflags.fast then Pstringrefu
|
||||
else Pstringrefs );
|
||||
"%string_opt_set", ( fun () -> if !Clflags.fast then Pstringsetu
|
||||
else Pstringsets );
|
||||
make_ba_ref 1; make_ba_set 1;
|
||||
make_ba_ref 2; make_ba_set 2;
|
||||
make_ba_ref 3; make_ba_set 3;
|
||||
]
|
||||
|
||||
let prim_obj_dup =
|
||||
Primitive.simple ~name:"caml_obj_dup" ~arity:1 ~alloc:true
|
||||
|
||||
|
@ -335,9 +311,7 @@ let find_primitive loc prim_name =
|
|||
| "%loc_LINE" -> Ploc Loc_LINE
|
||||
| "%loc_POS" -> Ploc Loc_POS
|
||||
| "%loc_MODULE" -> Ploc Loc_MODULE
|
||||
| name ->
|
||||
try Hashtbl.find index_primitives_table name @@ () with
|
||||
| Not_found -> Hashtbl.find primitives_table name
|
||||
| name -> Hashtbl.find primitives_table name
|
||||
|
||||
let specialize_comparison table env ty =
|
||||
let (gencomp, intcomp, floatcomp, stringcomp,
|
||||
|
|
|
@ -2215,25 +2215,7 @@ operator:
|
|||
| COLONEQUAL { ":=" }
|
||||
| PLUSEQ { "+=" }
|
||||
| PERCENT { "%" }
|
||||
| index_operator { $1 }
|
||||
;
|
||||
index_operator:
|
||||
DOT index_operator_core opt_assign_arrow { $2^$3 }
|
||||
;
|
||||
index_operator_core:
|
||||
| LPAREN RPAREN { ".()" }
|
||||
| LBRACKET RBRACKET { ".[]" }
|
||||
| LBRACE RBRACE { ".{}" }
|
||||
| LBRACE COMMA RBRACE { ".{,}" }
|
||||
| LBRACE COMMA COMMA RBRACE { ".{,,}" }
|
||||
| LBRACE COMMA DOTDOT COMMA RBRACE { ".{,..,}"}
|
||||
;
|
||||
|
||||
opt_assign_arrow:
|
||||
{ "" }
|
||||
| LESSMINUS { "<-" }
|
||||
;
|
||||
|
||||
constr_ident:
|
||||
UIDENT { $1 }
|
||||
/* | LBRACKET RBRACKET { "[]" } */
|
||||
|
|
Loading…
Reference in New Issue