diff options
author | Alain Frisch <alain@frisch.fr> | 2013-04-10 12:37:56 +0000 |
---|---|---|
committer | Alain Frisch <alain@frisch.fr> | 2013-04-10 12:37:56 +0000 |
commit | 91a1d4104722ab8a201fe3dbe66183f9f518b087 (patch) | |
tree | 21f62c4ea666acfd7e97262ebad4d51016402cd0 | |
parent | e2036c5a22d9e7c01e194dc44df9d10d76a89087 (diff) |
Cosmetic.
git-svn-id: http://caml.inria.fr/svn/ocaml/branches/extension_points@13498 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
-rw-r--r-- | parsing/ast_helper.ml | 24 | ||||
-rw-r--r-- | parsing/ast_helper.mli | 32 |
2 files changed, 32 insertions, 24 deletions
diff --git a/parsing/ast_helper.ml b/parsing/ast_helper.ml index a03868d3d..d87353e13 100644 --- a/parsing/ast_helper.ml +++ b/parsing/ast_helper.ml @@ -16,7 +16,7 @@ open Asttypes open Parsetree module Typ = struct - let mk ?(attrs = []) ?(loc = Location.none) d = {ptyp_desc = d; ptyp_loc = loc; ptyp_attributes = attrs} + let mk ?(loc = Location.none) ?(attrs = []) d = {ptyp_desc = d; ptyp_loc = loc; ptyp_attributes = attrs} let attr d a = {d with ptyp_attributes = d.ptyp_attributes @ [a]} let any ?loc ?attrs () = mk ?loc ?attrs Ptyp_any @@ -39,7 +39,7 @@ module Typ = struct end module Pat = struct - let mk ?(attrs = []) ?(loc = Location.none) d = {ppat_desc = d; ppat_loc = loc; ppat_attributes = attrs} + let mk ?(loc = Location.none) ?(attrs = []) d = {ppat_desc = d; ppat_loc = loc; ppat_attributes = attrs} let attr d a = {d with ppat_attributes = d.ppat_attributes @ [a]} let any ?loc ?attrs () = mk ?loc ?attrs Ppat_any @@ -60,7 +60,7 @@ module Pat = struct end module Exp = struct - let mk ?(attrs = []) ?(loc = Location.none) d = {pexp_desc = d; pexp_loc = loc; pexp_attributes = attrs} + let mk ?(loc = Location.none) ?(attrs = []) d = {pexp_desc = d; pexp_loc = loc; pexp_attributes = attrs} let attr d a = {d with pexp_attributes = d.pexp_attributes @ [a]} let ident ?loc ?attrs a = mk ?loc ?attrs (Pexp_ident a) @@ -100,7 +100,7 @@ module Exp = struct end module Mty = struct - let mk ?(attrs = []) ?(loc = Location.none) d = {pmty_desc = d; pmty_loc = loc; pmty_attributes = attrs} + let mk ?(loc = Location.none) ?(attrs = []) d = {pmty_desc = d; pmty_loc = loc; pmty_attributes = attrs} let attr d a = {d with pmty_attributes = d.pmty_attributes @ [a]} let ident ?loc ?attrs a = mk ?loc ?attrs (Pmty_ident a) @@ -112,7 +112,7 @@ module Mty = struct end module Mod = struct -let mk ?(attrs = []) ?(loc = Location.none) d = {pmod_desc = d; pmod_loc = loc; pmod_attributes = attrs} +let mk ?(loc = Location.none) ?(attrs = []) d = {pmod_desc = d; pmod_loc = loc; pmod_attributes = attrs} let attr d a = {d with pmod_attributes = d.pmod_attributes @ [a]} let ident ?loc ?attrs x = mk ?loc ?attrs (Pmod_ident x) @@ -181,7 +181,7 @@ module Cty = struct end module Ctf = struct - let mk ?(attrs = []) ?(loc = Location.none) d = + let mk ?(loc = Location.none) ?(attrs = []) d = { pctf_desc = d; pctf_loc = loc; @@ -196,7 +196,7 @@ module Ctf = struct end module Cf = struct - let mk ?(attrs = []) ?(loc = Location.none) d = + let mk ?(loc = Location.none) ?(attrs = []) d = { pcf_desc = d; pcf_loc = loc; @@ -215,7 +215,7 @@ module Cf = struct end module Val = struct - let mk ?(attrs = []) ?(loc = Location.none) ?(prim = []) name typ = + let mk ?(loc = Location.none) ?(attrs = []) ?(prim = []) name typ = { pval_name = name; pval_type = typ; @@ -262,7 +262,7 @@ module Mb = struct end module Ci = struct - let mk ?(attrs = []) ?(loc = Location.none) ?(virt = Concrete) ?(params = [], Location.none) name expr = + let mk ?(loc = Location.none) ?(attrs = []) ?(virt = Concrete) ?(params = [], Location.none) name expr = { pci_virt = virt; pci_params = params; @@ -274,7 +274,7 @@ module Ci = struct end module Type = struct - let mk ?(attrs = []) ?(loc = Location.none) + let mk ?(loc = Location.none) ?(attrs = []) ?(params = []) ?(cstrs = []) ?(kind = Ptype_abstract) @@ -295,7 +295,7 @@ end module Cd = struct - let mk ?(attrs = []) ?(loc = Location.none) ?(args = []) ?res name = + let mk ?(loc = Location.none) ?(attrs = []) ?(args = []) ?res name = { pcd_name = name; pcd_args = args; @@ -307,7 +307,7 @@ end module Ld = struct - let mk ?(attrs = []) ?(loc = Location.none) ?(mut = Immutable) name typ = + let mk ?(loc = Location.none) ?(attrs = []) ?(mut = Immutable) name typ = { pld_name = name; pld_mutable = mut; diff --git a/parsing/ast_helper.mli b/parsing/ast_helper.mli index 8b30397be..4e134982b 100644 --- a/parsing/ast_helper.mli +++ b/parsing/ast_helper.mli @@ -17,7 +17,7 @@ open Asttypes module Typ : sig - val mk: ?attrs:attribute list -> ?loc:Location.t -> core_type_desc -> core_type + val mk: ?loc:Location.t -> ?attrs:attribute list -> core_type_desc -> core_type val attr: core_type -> attribute -> core_type val any: ?loc:Location.t -> ?attrs:attribute list -> unit -> core_type @@ -37,8 +37,9 @@ module Typ : end module Pat: sig - val mk: ?attrs:attribute list -> ?loc:Location.t -> pattern_desc -> pattern + val mk: ?loc:Location.t -> ?attrs:attribute list -> pattern_desc -> pattern val attr:pattern -> attribute -> pattern + val any: ?loc:Location.t -> ?attrs:attribute list -> unit -> pattern val var: ?loc:Location.t -> ?attrs:attribute list -> string loc -> pattern val alias: ?loc:Location.t -> ?attrs:attribute list -> pattern -> string loc -> pattern @@ -57,8 +58,9 @@ module Pat: end module Exp: sig - val mk: ?attrs:attribute list -> ?loc:Location.t -> expression_desc -> expression + val mk: ?loc:Location.t -> ?attrs:attribute list -> expression_desc -> expression val attr: expression -> attribute -> expression + val ident: ?loc:Location.t -> ?attrs:attribute list -> Longident.t loc -> expression val constant: ?loc:Location.t -> ?attrs:attribute list -> constant -> expression val let_: ?loc:Location.t -> ?attrs:attribute list -> rec_flag -> (pattern * expression) list -> expression -> expression @@ -96,8 +98,9 @@ module Exp: end module Mty: sig - val mk: ?attrs:attribute list -> ?loc:Location.t -> module_type_desc -> module_type + val mk: ?loc:Location.t -> ?attrs:attribute list -> module_type_desc -> module_type val attr: module_type -> attribute -> module_type + val ident: ?loc:Location.t -> ?attrs:attribute list -> Longident.t loc -> module_type val signature: ?loc:Location.t -> ?attrs:attribute list -> signature -> module_type val functor_: ?loc:Location.t -> ?attrs:attribute list -> string loc -> module_type -> module_type -> module_type @@ -107,8 +110,9 @@ module Mty: end module Mod: sig - val mk: ?attrs:attribute list -> ?loc:Location.t -> module_expr_desc -> module_expr + val mk: ?loc:Location.t -> ?attrs:attribute list -> module_expr_desc -> module_expr val attr: module_expr -> attribute -> module_expr + val ident: ?loc:Location.t -> ?attrs:attribute list -> Longident.t loc -> module_expr val structure: ?loc:Location.t -> ?attrs:attribute list -> structure -> module_expr val functor_: ?loc:Location.t -> ?attrs:attribute list -> string loc -> module_type -> module_expr -> module_expr @@ -120,6 +124,7 @@ module Mod: module Sig: sig val mk: ?loc:Location.t -> signature_item_desc -> signature_item + val value: ?loc:Location.t -> value_description -> signature_item val type_: ?loc:Location.t -> type_declaration list -> signature_item val exception_: ?loc:Location.t -> constructor_declaration -> signature_item @@ -136,6 +141,7 @@ module Sig: module Str: sig val mk: ?loc:Location.t -> structure_item_desc -> structure_item + val eval: ?loc:Location.t -> expression -> structure_item val value: ?loc:Location.t -> rec_flag -> (pattern * expression) list -> structure_item val primitive: ?loc:Location.t -> value_description -> structure_item @@ -155,6 +161,7 @@ module Str: module Cl: sig val mk: ?loc:Location.t -> class_expr_desc -> class_expr + val constr: ?loc:Location.t -> Longident.t loc -> core_type list -> class_expr val structure: ?loc:Location.t -> class_structure -> class_expr val fun_: ?loc:Location.t -> label -> expression option -> pattern -> class_expr -> class_expr @@ -165,13 +172,14 @@ module Cl: module Cty: sig val mk: ?loc:Location.t -> class_type_desc -> class_type + val constr: ?loc:Location.t -> Longident.t loc -> core_type list -> class_type val signature: ?loc:Location.t -> class_signature -> class_type val fun_: ?loc:Location.t -> label -> core_type -> class_type -> class_type end module Ctf: sig - val mk: ?attrs:attribute list -> ?loc:Location.t -> class_type_field_desc -> class_type_field + val mk: ?loc:Location.t -> ?attrs:attribute list -> class_type_field_desc -> class_type_field val attr: class_type_field -> attribute -> class_type_field val inherit_: ?loc:Location.t -> ?attrs:attribute list -> class_type -> class_type_field @@ -181,7 +189,7 @@ module Ctf: end module Cf: sig - val mk: ?attrs:attribute list -> ?loc:Location.t -> class_field_desc -> class_field + val mk: ?loc:Location.t -> ?attrs:attribute list -> class_field_desc -> class_field val attr: class_field -> attribute -> class_field val inherit_: ?loc:Location.t -> ?attrs:attribute list -> override_flag -> class_expr -> string option -> class_field @@ -195,7 +203,7 @@ module Cf: end module Val: sig - val mk: ?attrs:attribute list -> ?loc:Location.t -> ?prim:string list -> string loc -> core_type -> value_description + val mk: ?loc:Location.t -> ?attrs:attribute list -> ?prim:string list -> string loc -> core_type -> value_description end module Mtb: sig @@ -215,19 +223,19 @@ module Mb: end module Ci: sig - val mk: ?attrs:attribute list -> ?loc:Location.t -> ?virt:virtual_flag -> ?params:(string loc * variance) list * Location.t -> string loc -> 'a -> 'a class_infos + val mk: ?loc:Location.t -> ?attrs:attribute list -> ?virt:virtual_flag -> ?params:(string loc * variance) list * Location.t -> string loc -> 'a -> 'a class_infos end module Type: sig - val mk: ?attrs:attribute list -> ?loc:Location.t -> ?params:(string loc option * variance) list -> ?cstrs:(core_type * core_type * Location.t) list -> ?kind:type_kind -> ?priv:private_flag -> ?manifest:core_type -> string loc -> type_declaration + val mk: ?loc:Location.t -> ?attrs:attribute list -> ?params:(string loc option * variance) list -> ?cstrs:(core_type * core_type * Location.t) list -> ?kind:type_kind -> ?priv:private_flag -> ?manifest:core_type -> string loc -> type_declaration end module Cd: sig - val mk: ?attrs:attribute list -> ?loc:Location.t -> ?args:core_type list -> ?res:core_type -> string loc -> constructor_declaration + val mk: ?loc:Location.t -> ?attrs:attribute list -> ?args:core_type list -> ?res:core_type -> string loc -> constructor_declaration end module Ld: sig - val mk: ?attrs:attribute list -> ?loc:Location.t -> ?mut:mutable_flag -> string loc -> core_type -> label_declaration + val mk: ?loc:Location.t -> ?attrs:attribute list -> ?mut:mutable_flag -> string loc -> core_type -> label_declaration end module Csig: sig |