Revert "Continuation of GPR#1580 (022051e7bd): bootstrap to remove Lambda.Const_pointer"

This reverts commit b4fa820b78.
master
Damien Doligez 2018-04-06 15:22:24 +02:00
parent 4d5852d3f9
commit d42422a0cf
8 changed files with 7 additions and 0 deletions

View File

@ -831,6 +831,7 @@ let rec close fenv cenv = function
let rec transl = function
| Const_base(Const_int n) -> Uconst_int n
| Const_base(Const_char c) -> Uconst_int (Char.code c)
| Const_pointer _ -> assert false
| Const_block (tag, fields) ->
str (Uconst_block (tag, List.map transl fields))
| Const_float_array sl ->

Binary file not shown.

View File

@ -192,6 +192,7 @@ and raise_kind =
type structured_constant =
Const_base of constant
| Const_pointer of int
| Const_block of int * structured_constant list
| Const_float_array of string list
| Const_immstring of string

View File

@ -200,6 +200,7 @@ and raise_kind =
type structured_constant =
Const_base of constant
| Const_pointer of int
| Const_block of int * structured_constant list
| Const_float_array of string list
| Const_immstring of string

View File

@ -29,6 +29,7 @@ let rec struct_const ppf = function
| Const_base(Const_int32 n) -> fprintf ppf "%lil" n
| Const_base(Const_int64 n) -> fprintf ppf "%LiL" n
| Const_base(Const_nativeint n) -> fprintf ppf "%nin" n
| Const_pointer n -> fprintf ppf "%ia" n
| Const_block(tag, []) ->
fprintf ppf "[%i]" tag
| Const_block(tag, sc1::scl) ->

View File

@ -210,6 +210,7 @@ let rec transl_const = function
| Const_base(Const_int32 i) -> Obj.repr i
| Const_base(Const_int64 i) -> Obj.repr i
| Const_base(Const_nativeint i) -> Obj.repr i
| Const_pointer i -> Obj.repr i
| Const_immstring s -> Obj.repr s
| Const_block(tag, fields) ->
let block = Obj.new_block tag (List.length fields) in

View File

@ -134,6 +134,7 @@ let rec declare_const t (const : Lambda.structured_constant)
register_const t (Allocated_const (Int64 c)) "int64"
| Const_base (Const_nativeint c) ->
register_const t (Allocated_const (Nativeint c)) "nativeint"
| Const_pointer _ -> assert false
| Const_immstring c ->
register_const t (Allocated_const (Immutable_string c)) "immstring"
| Const_float_array c ->

View File

@ -92,6 +92,7 @@ let rec print_struct_const = function
| Const_base(Const_int32 i) -> printf "%ldl" i
| Const_base(Const_nativeint i) -> printf "%ndn" i
| Const_base(Const_int64 i) -> printf "%LdL" i
| Const_pointer n -> printf "%da" n
| Const_block(tag, args) ->
printf "<%d>" tag;
begin match args with