Skip to content

Commit 731b2a0

Browse files
committed
Too long lines.
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@11254 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
1 parent 67e74db commit 731b2a0

File tree

2 files changed

+12
-8
lines changed

2 files changed

+12
-8
lines changed

parsing/parsetree.mli

+9-7
Original file line numberDiff line numberDiff line change
@@ -189,12 +189,14 @@ and class_structure = pattern * class_field list
189189
and class_field =
190190
Pcf_inher of override_flag * class_expr * string option
191191
| Pcf_valvirt of (string * mutable_flag * core_type * Location.t)
192-
| Pcf_val of (string * mutable_flag * override_flag * expression * Location.t)
193-
| Pcf_virt of (string * private_flag * core_type * Location.t)
194-
| Pcf_meth of (string * private_flag *override_flag * expression * Location.t)
195-
| Pcf_cstr of (core_type * core_type * Location.t)
196-
| Pcf_let of rec_flag * (pattern * expression) list * Location.t
197-
| Pcf_init of expression
192+
| Pcf_val of
193+
(string * mutable_flag * override_flag * expression * Location.t)
194+
| Pcf_virt of (string * private_flag * core_type * Location.t)
195+
| Pcf_meth of
196+
(string * private_flag * override_flag * expression * Location.t)
197+
| Pcf_cstr of (core_type * core_type * Location.t)
198+
| Pcf_let of rec_flag * (pattern * expression) list * Location.t
199+
| Pcf_init of expression
198200

199201
and class_declaration = class_expr class_infos
200202

@@ -239,7 +241,7 @@ and with_constraint =
239241
| Pwith_typesubst of type_declaration
240242
| Pwith_modsubst of Longident.t
241243

242-
(* value expressions for the module language *)
244+
(* Value expressions for the module language *)
243245

244246
and module_expr =
245247
{ pmod_desc: module_expr_desc;

parsing/syntaxerr.ml

+3-1
Original file line numberDiff line numberDiff line change
@@ -37,7 +37,9 @@ let report_error ppf = function
3737
Location.print_error opening_loc opening
3838
end
3939
| Applicative_path loc ->
40-
fprintf ppf "%aSyntax error: applicative paths of the form F(X).t are not supported when the option -no-app-func is set."
40+
fprintf ppf
41+
"%aSyntax error: applicative paths of the form F(X).t \
42+
are not supported when the option -no-app-func is set."
4143
Location.print_error loc
4244
| Other loc ->
4345
fprintf ppf "%aSyntax error" Location.print_error loc

0 commit comments

Comments
 (0)