diff options
author | Alain Frisch <alain@frisch.fr> | 2013-04-16 09:21:05 +0000 |
---|---|---|
committer | Alain Frisch <alain@frisch.fr> | 2013-04-16 09:21:05 +0000 |
commit | c8743ab55fc822b710c38f27071ef37c3a1ceb20 (patch) | |
tree | 808154222d3993968e6bc8fa7ebe5b1aef7fad07 | |
parent | 986fb105c164cb4a46e091de9d8ae7b143541edb (diff) |
Remove pcsig_loc field + doc.
git-svn-id: http://caml.inria.fr/svn/ocaml/branches/extension_points@13538 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
-rw-r--r-- | camlp4/Camlp4/Struct/Camlp4Ast2OCamlAst.ml | 1 | ||||
-rw-r--r-- | camlp4/boot/Camlp4.ml | 1 | ||||
-rw-r--r-- | parsing/ast_helper.ml | 11 | ||||
-rw-r--r-- | parsing/ast_helper.mli | 6 | ||||
-rw-r--r-- | parsing/ast_mapper.ml | 3 | ||||
-rw-r--r-- | parsing/parser.mly | 5 | ||||
-rw-r--r-- | parsing/parsetree.mli | 11 | ||||
-rw-r--r-- | parsing/printast.ml | 2 | ||||
-rw-r--r-- | tools/untypeast.ml | 1 | ||||
-rw-r--r-- | typing/typeclass.ml | 6 | ||||
-rw-r--r-- | typing/typedtree.ml | 1 | ||||
-rw-r--r-- | typing/typedtree.mli | 1 |
12 files changed, 27 insertions, 22 deletions
diff --git a/camlp4/Camlp4/Struct/Camlp4Ast2OCamlAst.ml b/camlp4/Camlp4/Struct/Camlp4Ast2OCamlAst.ml index 75bd975c0..2961a6ea0 100644 --- a/camlp4/Camlp4/Struct/Camlp4Ast2OCamlAst.ml +++ b/camlp4/Camlp4/Struct/Camlp4Ast2OCamlAst.ml @@ -1110,7 +1110,6 @@ value varify_constructors var_names = mkcty loc (Pcty_signature { pcsig_self = ctyp t; pcsig_fields = cil; - pcsig_loc = mkloc loc; }) | CtCon loc _ _ _ -> error loc "invalid virtual class inside a class type" diff --git a/camlp4/boot/Camlp4.ml b/camlp4/boot/Camlp4.ml index db49cff1d..3d5a26c8e 100644 --- a/camlp4/boot/Camlp4.ml +++ b/camlp4/boot/Camlp4.ml @@ -15501,7 +15501,6 @@ module Struct = { pcsig_self = ctyp t; pcsig_fields = cil; - pcsig_loc = mkloc loc; }) | CtCon (loc, _, _, _) -> error loc "invalid virtual class inside a class type" diff --git a/parsing/ast_helper.ml b/parsing/ast_helper.ml index bdd8330f0..c87fdb2bc 100644 --- a/parsing/ast_helper.ml +++ b/parsing/ast_helper.ml @@ -353,11 +353,18 @@ module Ld = struct end module Csig = struct - let mk ?(loc = !default_loc) self fields = + let mk self fields = { pcsig_self = self; pcsig_fields = fields; - pcsig_loc = loc; + } +end + +module Cstr = struct + let mk self fields = + { + pcstr_self = self; + pcstr_fields = fields; } end diff --git a/parsing/ast_helper.mli b/parsing/ast_helper.mli index c0539ed3a..17ac67e32 100644 --- a/parsing/ast_helper.mli +++ b/parsing/ast_helper.mli @@ -257,7 +257,11 @@ module Ld: end module Csig: sig - val mk: ?loc:loc -> core_type -> class_type_field list -> class_signature + val mk: core_type -> class_type_field list -> class_signature + end +module Cstr: + sig + val mk: pattern -> class_field list -> class_structure end diff --git a/parsing/ast_mapper.ml b/parsing/ast_mapper.ml index abbc5939d..c3f520572 100644 --- a/parsing/ast_mapper.ml +++ b/parsing/ast_mapper.ml @@ -98,11 +98,10 @@ module CT = struct | Pctf_constraint (t1, t2) -> constraint_ ~loc ~attrs (sub # typ t1) (sub # typ t2) | Pctf_extension x -> extension ~loc ~attrs (sub # extension x) - let map_signature sub {pcsig_self; pcsig_fields; pcsig_loc} = + let map_signature sub {pcsig_self; pcsig_fields} = Csig.mk (sub # typ pcsig_self) (List.map (sub # class_type_field) pcsig_fields) - ~loc:(sub # location pcsig_loc) end module MT = struct diff --git a/parsing/parser.mly b/parsing/parser.mly index ddb281087..a427776fe 100644 --- a/parsing/parser.mly +++ b/parsing/parser.mly @@ -807,7 +807,7 @@ class_simple_expr: ; class_structure: class_self_pattern class_fields - { { pcstr_self = $1; pcstr_fields = List.rev $2 } } + { Cstr.mk $1 (List.rev $2) } ; class_self_pattern: LPAREN pattern RPAREN @@ -908,8 +908,7 @@ class_signature: ; class_sig_body: class_self_type class_sig_fields - { { pcsig_self = $1; pcsig_fields = List.rev $2; - pcsig_loc = symbol_rloc(); } } + { Csig.mk $1 (List.rev $2) } ; class_self_type: LPAREN core_type RPAREN diff --git a/parsing/parsetree.mli b/parsing/parsetree.mli index 4c9ff8cd4..f4cc8c46b 100644 --- a/parsing/parsetree.mli +++ b/parsing/parsetree.mli @@ -420,9 +420,10 @@ and class_signature = { pcsig_self: core_type; pcsig_fields: class_type_field list; - pcsig_loc: Location.t; } -(* object('selfpat) ... end *) +(* object('selfpat) ... end + object ... end (self = Ptyp_any) + *) and class_type_field = { @@ -506,13 +507,15 @@ and class_structure = pcstr_self: pattern; pcstr_fields: class_field list; } -(* object(selfpat) ... end *) +(* object(selfpat) ... end + object ... end (self = Ppat_any) + *) and class_field = { pcf_desc: class_field_desc; pcf_loc: Location.t; - pcf_attributes: attributes; + pcf_attributes: attributes; (* ... [@id1 E1] [@id2 E2] *) } and class_field_desc = diff --git a/parsing/printast.ml b/parsing/printast.ml index d6c583824..89c1cbe3d 100644 --- a/parsing/printast.ml +++ b/parsing/printast.ml @@ -416,7 +416,7 @@ and class_type i ppf x = expression i ppf arg and class_signature i ppf cs = - line i ppf "class_signature %a\n" fmt_location cs.pcsig_loc; + line i ppf "class_signature\n"; core_type (i+1) ppf cs.pcsig_self; list (i+1) class_type_field ppf cs.pcsig_fields; diff --git a/tools/untypeast.ml b/tools/untypeast.ml index f0dcdae8f..c22fdcc98 100644 --- a/tools/untypeast.ml +++ b/tools/untypeast.ml @@ -465,7 +465,6 @@ and untype_class_signature cs = { pcsig_self = untype_core_type cs.csig_self; pcsig_fields = List.map untype_class_type_field cs.csig_fields; - pcsig_loc = cs.csig_loc; } and untype_class_type_field ctf = diff --git a/typing/typeclass.ml b/typing/typeclass.ml index c4780f645..848cc32a4 100644 --- a/typing/typeclass.ml +++ b/typing/typeclass.ml @@ -407,7 +407,7 @@ let rec class_type_field env self_type meths | Pctf_extension (s, _arg) -> raise (Error (ctf.pctf_loc, env, Extension s)) -and class_signature env sty sign loc = +and class_signature env {pcsig_self=sty; pcsig_fields=sign} = let meths = ref Meths.empty in let self_cty = transl_simple_type env false sty in let self_cty = { self_cty with @@ -439,7 +439,6 @@ and class_signature env sty sign loc = { csig_self = self_cty; csig_fields = fields; csig_type = cty; - csig_loc = loc; } and class_type env scty = @@ -479,8 +478,7 @@ and class_type env scty = cltyp (Tcty_constr ( path, lid , ctys)) typ | Pcty_signature pcsig -> - let clsig = class_signature env - pcsig.pcsig_self pcsig.pcsig_fields pcsig.pcsig_loc in + let clsig = class_signature env pcsig in let typ = Cty_signature clsig.csig_type in cltyp (Tcty_signature clsig) typ diff --git a/typing/typedtree.ml b/typing/typedtree.ml index 8200f0f7a..87aa9f9a9 100644 --- a/typing/typedtree.ml +++ b/typing/typedtree.ml @@ -404,7 +404,6 @@ and class_signature = { csig_self : core_type; csig_fields : class_type_field list; csig_type : Types.class_signature; - csig_loc : Location.t; } and class_type_field = { diff --git a/typing/typedtree.mli b/typing/typedtree.mli index 924f2a233..d4a03a465 100644 --- a/typing/typedtree.mli +++ b/typing/typedtree.mli @@ -404,7 +404,6 @@ and class_signature = { csig_self : core_type; csig_fields : class_type_field list; csig_type : Types.class_signature; - csig_loc : Location.t; } and class_type_field = { |