diff options
author | Pierre Weis <Pierre.Weis@inria.fr> | 2000-12-28 13:07:42 +0000 |
---|---|---|
committer | Pierre Weis <Pierre.Weis@inria.fr> | 2000-12-28 13:07:42 +0000 |
commit | 2116da4220acde3fdf11ac0ef0100e0166729bcd (patch) | |
tree | 3d09bdc4675c58823863bfe12c05e6cdd490d6f0 /stdlib/format.ml | |
parent | 447c79eadec7db87abc782735c5b06ed4fd020e4 (diff) |
Getting rid of obsolete boolean operators & and or
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@3359 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'stdlib/format.ml')
-rw-r--r-- | stdlib/format.ml | 33 |
1 files changed, 16 insertions, 17 deletions
diff --git a/stdlib/format.ml b/stdlib/format.ml index a512b1db1..0d3563f4f 100644 --- a/stdlib/format.ml +++ b/stdlib/format.ml @@ -780,14 +780,13 @@ let fprintf_out str out ppf format = invalid_arg ("fprintf: bad %s format, " ^ format) in if p > 0 && String.length s < p then begin pp_print_as_string ppf - (String.make (p - String.length s) ' '); - pp_print_as_string ppf s - end else if p < 0 && String.length s < -p then begin + (String.make (p - String.length s) ' '); + pp_print_as_string ppf s end else + if p < 0 && String.length s < -p then begin pp_print_as_string ppf s; pp_print_as_string ppf - (String.make (-p - String.length s) ' ') - end else - pp_print_as_string ppf s + (String.make (-p - String.length s) ' ') end + else pp_print_as_string ppf s end; doprn (succ j)) | 'c' -> @@ -807,25 +806,25 @@ let fprintf_out str out ppf format = | 'b' -> Obj.magic(fun b -> pp_print_as_string ppf (string_of_bool b); - doprn(succ j)) + doprn (succ j)) | 'a' -> if str then Obj.magic(fun printer arg -> pp_print_as_string ppf (printer () arg); - doprn(succ j)) + doprn (succ j)) else Obj.magic(fun printer arg -> printer ppf arg; - doprn(succ j)) + doprn (succ j)) | 't' -> if str then Obj.magic(fun printer -> pp_print_as_string ppf (printer ()); - doprn(succ j)) + doprn (succ j)) else Obj.magic(fun printer -> printer ppf; - doprn(succ j)) + doprn (succ j)) | c -> format_invalid_arg "fprintf: unknown format " c end @@ -859,13 +858,13 @@ let fprintf_out str out ppf format = let j = succ j in if j >= limit then Pp_hbox, j else begin match format.[j] with - | 'o' -> + | 'o' -> let j = succ j in if j >= limit then invalid_arg ("fprintf: bad box format " ^ format) else begin match format.[j] with | 'v' -> Pp_hovbox, succ j - | c -> format_invalid_arg "fprintf: bad name " c end + | c -> format_invalid_arg "fprintf: bad box name " c end | 'v' -> Pp_hvbox, succ j | c -> Pp_hbox, j end @@ -885,17 +884,17 @@ let fprintf_out str out ppf format = then invalid_arg "fprintf: bad break format" format else pp_print_break ppf nspaces offset; j - | c -> pp_print_space ppf (); i + | c -> pp_print_space ppf (); i and do_pp_open ppf i = if i >= limit then begin pp_open_box_gen ppf 0 Pp_box; i end else match format.[i] with | '<' -> - let k, j = get_box_kind (succ i) in + let kind, j = get_box_kind (succ i) in let size, j = get_int "fprintf: bad box format " format j in - pp_open_box_gen ppf size k; + pp_open_box_gen ppf size kind; j - | c -> pp_open_box_gen ppf 0 Pp_box; i + | c -> pp_open_box_gen ppf 0 Pp_box; i in doprn 0;; |