1995-08-09 08:06:35 -07:00
|
|
|
(***********************************************************************)
|
|
|
|
(* *)
|
1996-04-30 07:53:58 -07:00
|
|
|
(* Objective Caml *)
|
1995-08-09 08:06:35 -07:00
|
|
|
(* *)
|
|
|
|
(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
|
|
|
|
(* *)
|
1996-04-30 07:53:58 -07:00
|
|
|
(* Copyright 1996 Institut National de Recherche en Informatique et *)
|
1999-11-17 10:59:06 -08:00
|
|
|
(* en Automatique. All rights reserved. This file is distributed *)
|
|
|
|
(* under the terms of the Q Public License version 1.0. *)
|
1995-08-09 08:06:35 -07:00
|
|
|
(* *)
|
|
|
|
(***********************************************************************)
|
|
|
|
|
|
|
|
(* $Id$ *)
|
|
|
|
|
1995-05-04 03:15:53 -07:00
|
|
|
(* Predefined type constructors (with special typing rules in typecore) *)
|
|
|
|
|
2003-07-02 02:14:35 -07:00
|
|
|
open Asttypes
|
1995-05-04 03:15:53 -07:00
|
|
|
open Path
|
1996-09-23 04:33:27 -07:00
|
|
|
open Types
|
1997-03-24 12:11:22 -08:00
|
|
|
open Btype
|
1996-04-22 04:15:41 -07:00
|
|
|
|
|
|
|
let ident_int = Ident.create "int"
|
|
|
|
and ident_char = Ident.create "char"
|
|
|
|
and ident_string = Ident.create "string"
|
|
|
|
and ident_float = Ident.create "float"
|
|
|
|
and ident_bool = Ident.create "bool"
|
|
|
|
and ident_unit = Ident.create "unit"
|
|
|
|
and ident_exn = Ident.create "exn"
|
|
|
|
and ident_array = Ident.create "array"
|
|
|
|
and ident_list = Ident.create "list"
|
2003-07-05 04:13:24 -07:00
|
|
|
and ident_format4 = Ident.create "format4"
|
1999-11-30 08:07:38 -08:00
|
|
|
and ident_option = Ident.create "option"
|
2000-02-21 10:14:56 -08:00
|
|
|
and ident_nativeint = Ident.create "nativeint"
|
|
|
|
and ident_int32 = Ident.create "int32"
|
|
|
|
and ident_int64 = Ident.create "int64"
|
2002-01-20 09:39:10 -08:00
|
|
|
and ident_lazy_t = Ident.create "lazy_t"
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
let path_int = Pident ident_int
|
|
|
|
and path_char = Pident ident_char
|
|
|
|
and path_string = Pident ident_string
|
|
|
|
and path_float = Pident ident_float
|
|
|
|
and path_bool = Pident ident_bool
|
|
|
|
and path_unit = Pident ident_unit
|
|
|
|
and path_exn = Pident ident_exn
|
|
|
|
and path_array = Pident ident_array
|
|
|
|
and path_list = Pident ident_list
|
2003-07-05 04:13:24 -07:00
|
|
|
and path_format4 = Pident ident_format4
|
1999-11-30 08:07:38 -08:00
|
|
|
and path_option = Pident ident_option
|
2000-02-21 10:14:56 -08:00
|
|
|
and path_nativeint = Pident ident_nativeint
|
|
|
|
and path_int32 = Pident ident_int32
|
|
|
|
and path_int64 = Pident ident_int64
|
2002-01-20 09:39:10 -08:00
|
|
|
and path_lazy_t = Pident ident_lazy_t
|
1995-05-04 03:15:53 -07:00
|
|
|
|
1997-01-21 09:43:53 -08:00
|
|
|
let type_int = newgenty (Tconstr(path_int, [], ref Mnil))
|
|
|
|
and type_char = newgenty (Tconstr(path_char, [], ref Mnil))
|
|
|
|
and type_string = newgenty (Tconstr(path_string, [], ref Mnil))
|
|
|
|
and type_float = newgenty (Tconstr(path_float, [], ref Mnil))
|
|
|
|
and type_bool = newgenty (Tconstr(path_bool, [], ref Mnil))
|
|
|
|
and type_unit = newgenty (Tconstr(path_unit, [], ref Mnil))
|
|
|
|
and type_exn = newgenty (Tconstr(path_exn, [], ref Mnil))
|
|
|
|
and type_array t = newgenty (Tconstr(path_array, [t], ref Mnil))
|
|
|
|
and type_list t = newgenty (Tconstr(path_list, [t], ref Mnil))
|
1999-11-30 08:07:38 -08:00
|
|
|
and type_option t = newgenty (Tconstr(path_option, [t], ref Mnil))
|
2000-02-21 10:14:56 -08:00
|
|
|
and type_nativeint = newgenty (Tconstr(path_nativeint, [], ref Mnil))
|
|
|
|
and type_int32 = newgenty (Tconstr(path_int32, [], ref Mnil))
|
|
|
|
and type_int64 = newgenty (Tconstr(path_int64, [], ref Mnil))
|
2002-01-20 09:39:10 -08:00
|
|
|
and type_lazy_t t = newgenty (Tconstr(path_lazy_t, [t], ref Mnil))
|
1995-05-04 03:15:53 -07:00
|
|
|
|
2004-01-04 06:32:34 -08:00
|
|
|
let ident_match_failure = Ident.create_predef_exn "Match_failure"
|
|
|
|
and ident_out_of_memory = Ident.create_predef_exn "Out_of_memory"
|
|
|
|
and ident_invalid_argument = Ident.create_predef_exn "Invalid_argument"
|
|
|
|
and ident_failure = Ident.create_predef_exn "Failure"
|
|
|
|
and ident_not_found = Ident.create_predef_exn "Not_found"
|
|
|
|
and ident_sys_error = Ident.create_predef_exn "Sys_error"
|
|
|
|
and ident_end_of_file = Ident.create_predef_exn "End_of_file"
|
|
|
|
and ident_division_by_zero = Ident.create_predef_exn "Division_by_zero"
|
|
|
|
and ident_stack_overflow = Ident.create_predef_exn "Stack_overflow"
|
|
|
|
and ident_sys_blocked_io = Ident.create_predef_exn "Sys_blocked_io"
|
|
|
|
and ident_assert_failure = Ident.create_predef_exn "Assert_failure"
|
|
|
|
and ident_undefined_recursive_module =
|
|
|
|
Ident.create_predef_exn "Undefined_recursive_module"
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
let path_match_failure = Pident ident_match_failure
|
2000-12-04 07:37:05 -08:00
|
|
|
and path_assert_failure = Pident ident_assert_failure
|
2003-06-19 08:53:53 -07:00
|
|
|
and path_undefined_recursive_module = Pident ident_undefined_recursive_module
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
let build_initial_env add_type add_exception empty_env =
|
|
|
|
let decl_abstr =
|
1995-07-25 04:40:07 -07:00
|
|
|
{type_params = [];
|
|
|
|
type_arity = 0;
|
1995-09-26 13:23:29 -07:00
|
|
|
type_kind = Type_abstract;
|
2000-09-06 03:21:07 -07:00
|
|
|
type_manifest = None;
|
|
|
|
type_variance = []}
|
1995-05-04 03:15:53 -07:00
|
|
|
and decl_bool =
|
1995-07-25 04:40:07 -07:00
|
|
|
{type_params = [];
|
|
|
|
type_arity = 0;
|
2003-07-02 02:14:35 -07:00
|
|
|
type_kind = Type_variant(["false",[]; "true",[]], Public);
|
2000-09-06 03:21:07 -07:00
|
|
|
type_manifest = None;
|
|
|
|
type_variance = []}
|
1995-05-04 03:15:53 -07:00
|
|
|
and decl_unit =
|
1995-07-25 04:40:07 -07:00
|
|
|
{type_params = [];
|
|
|
|
type_arity = 0;
|
2003-07-02 02:14:35 -07:00
|
|
|
type_kind = Type_variant(["()",[]], Public);
|
2000-09-06 03:21:07 -07:00
|
|
|
type_manifest = None;
|
|
|
|
type_variance = []}
|
1995-05-04 03:15:53 -07:00
|
|
|
and decl_exn =
|
1995-07-25 04:40:07 -07:00
|
|
|
{type_params = [];
|
|
|
|
type_arity = 0;
|
2003-07-02 02:14:35 -07:00
|
|
|
type_kind = Type_variant([], Public);
|
2000-09-06 03:21:07 -07:00
|
|
|
type_manifest = None;
|
|
|
|
type_variance = []}
|
1995-05-04 03:15:53 -07:00
|
|
|
and decl_array =
|
1997-03-24 12:11:22 -08:00
|
|
|
let tvar = newgenvar() in
|
1995-07-25 04:40:07 -07:00
|
|
|
{type_params = [tvar];
|
|
|
|
type_arity = 1;
|
1995-09-26 13:23:29 -07:00
|
|
|
type_kind = Type_abstract;
|
2000-09-06 03:21:07 -07:00
|
|
|
type_manifest = None;
|
2003-05-21 02:04:54 -07:00
|
|
|
type_variance = [true, true, true]}
|
1995-05-04 03:15:53 -07:00
|
|
|
and decl_list =
|
1997-03-24 12:11:22 -08:00
|
|
|
let tvar = newgenvar() in
|
1995-07-25 04:40:07 -07:00
|
|
|
{type_params = [tvar];
|
|
|
|
type_arity = 1;
|
2003-07-02 02:14:35 -07:00
|
|
|
type_kind =
|
|
|
|
Type_variant(["[]", []; "::", [tvar; type_list tvar]], Public);
|
2000-09-06 03:21:07 -07:00
|
|
|
type_manifest = None;
|
2003-05-21 02:04:54 -07:00
|
|
|
type_variance = [true, false, false]}
|
2003-07-05 04:13:24 -07:00
|
|
|
and decl_format4 =
|
2002-10-31 01:56:11 -08:00
|
|
|
{type_params = [newgenvar(); newgenvar(); newgenvar(); newgenvar()];
|
|
|
|
type_arity = 4;
|
1995-09-26 13:23:29 -07:00
|
|
|
type_kind = Type_abstract;
|
2000-09-06 03:21:07 -07:00
|
|
|
type_manifest = None;
|
2003-05-21 02:04:54 -07:00
|
|
|
type_variance = [true, true, true; true, true, true;
|
|
|
|
true, true, true; true, true, true]}
|
1999-11-30 08:07:38 -08:00
|
|
|
and decl_option =
|
|
|
|
let tvar = newgenvar() in
|
|
|
|
{type_params = [tvar];
|
|
|
|
type_arity = 1;
|
2003-07-02 02:14:35 -07:00
|
|
|
type_kind = Type_variant(["None", []; "Some", [tvar]], Public);
|
2000-09-06 03:21:07 -07:00
|
|
|
type_manifest = None;
|
2003-05-21 02:04:54 -07:00
|
|
|
type_variance = [true, false, false]}
|
2002-01-20 09:39:10 -08:00
|
|
|
and decl_lazy_t =
|
|
|
|
let tvar = newgenvar() in
|
|
|
|
{type_params = [tvar];
|
|
|
|
type_arity = 1;
|
|
|
|
type_kind = Type_abstract;
|
|
|
|
type_manifest = None;
|
2003-05-21 02:04:54 -07:00
|
|
|
type_variance = [true, false, false]}
|
1999-11-30 08:07:38 -08:00
|
|
|
in
|
1995-07-25 04:40:07 -07:00
|
|
|
|
1997-05-13 11:28:15 -07:00
|
|
|
add_exception ident_match_failure
|
|
|
|
[newgenty (Ttuple[type_string; type_int; type_int])] (
|
1995-05-04 03:15:53 -07:00
|
|
|
add_exception ident_out_of_memory [] (
|
1997-05-15 06:30:02 -07:00
|
|
|
add_exception ident_stack_overflow [] (
|
1995-05-04 03:15:53 -07:00
|
|
|
add_exception ident_invalid_argument [type_string] (
|
|
|
|
add_exception ident_failure [type_string] (
|
|
|
|
add_exception ident_not_found [] (
|
1998-11-20 07:38:09 -08:00
|
|
|
add_exception ident_sys_blocked_io [] (
|
1995-05-04 03:15:53 -07:00
|
|
|
add_exception ident_sys_error [type_string] (
|
|
|
|
add_exception ident_end_of_file [] (
|
|
|
|
add_exception ident_division_by_zero [] (
|
2000-12-04 07:37:05 -08:00
|
|
|
add_exception ident_assert_failure
|
|
|
|
[newgenty (Ttuple[type_string; type_int; type_int])] (
|
2003-06-19 08:53:53 -07:00
|
|
|
add_exception ident_undefined_recursive_module
|
|
|
|
[newgenty (Ttuple[type_string; type_int; type_int])] (
|
2000-02-21 10:14:56 -08:00
|
|
|
add_type ident_int64 decl_abstr (
|
|
|
|
add_type ident_int32 decl_abstr (
|
|
|
|
add_type ident_nativeint decl_abstr (
|
2002-01-20 09:39:10 -08:00
|
|
|
add_type ident_lazy_t decl_lazy_t (
|
1999-11-30 08:07:38 -08:00
|
|
|
add_type ident_option decl_option (
|
2003-07-05 04:13:24 -07:00
|
|
|
add_type ident_format4 decl_format4 (
|
1995-05-04 03:15:53 -07:00
|
|
|
add_type ident_list decl_list (
|
|
|
|
add_type ident_array decl_array (
|
|
|
|
add_type ident_exn decl_exn (
|
|
|
|
add_type ident_unit decl_unit (
|
|
|
|
add_type ident_bool decl_bool (
|
|
|
|
add_type ident_float decl_abstr (
|
|
|
|
add_type ident_string decl_abstr (
|
|
|
|
add_type ident_char decl_abstr (
|
|
|
|
add_type ident_int decl_abstr (
|
2003-06-19 08:53:53 -07:00
|
|
|
empty_env)))))))))))))))))))))))))))
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
let builtin_values =
|
|
|
|
List.map (fun id -> Ident.make_global id; (Ident.name id, id))
|
1997-05-15 06:30:02 -07:00
|
|
|
[ident_match_failure; ident_out_of_memory; ident_stack_overflow;
|
1997-05-13 11:28:15 -07:00
|
|
|
ident_invalid_argument;
|
1995-05-04 03:15:53 -07:00
|
|
|
ident_failure; ident_not_found; ident_sys_error; ident_end_of_file;
|
2000-12-04 07:37:05 -08:00
|
|
|
ident_division_by_zero; ident_sys_blocked_io;
|
2003-06-19 08:53:53 -07:00
|
|
|
ident_assert_failure; ident_undefined_recursive_module ]
|