(***********************************************************************) (* *) (* Objective Caml *) (* *) (* Xavier Leroy, projet Cristal, INRIA Rocquencourt *) (* *) (* Copyright 1996 Institut National de Recherche en Informatique et *) (* en Automatique. All rights reserved. This file is distributed *) (* under the terms of the GNU Library General Public License, with *) (* the special exception on linking described in file ../LICENSE. *) (* *) (***********************************************************************) (* $Id$ *) external format_int: string -> int -> string = "format_int" external format_int32: string -> int32 -> string = "int32_format" external format_nativeint: string -> nativeint -> string = "nativeint_format" external format_int64: string -> int64 -> string = "int64_format" external format_float: string -> float -> string = "format_float" let bad_format fmt pos = invalid_arg ("printf: bad format " ^ String.sub fmt pos (String.length fmt - pos)) (* Parses a format to return the specified length and the padding direction. *) let parse_format format = let rec parse neg i = if i >= String.length format then (0, neg) else match String.unsafe_get format i with | '1'..'9' -> (int_of_string (String.sub format i (String.length format - i - 1)), neg) | '-' -> parse true (succ i) | _ -> parse neg (succ i) in try parse false 1 with Failure _ -> bad_format format 0 (* Pad a (sub) string into a blank string of length [p], on the right if [neg] is true, on the left otherwise. *) let pad_string pad_char p neg s i len = if p = len && i = 0 then s else if p <= len then String.sub s i p else let res = String.make p pad_char in if neg then String.blit s i res 0 len else String.blit s i res (p - len) len; res (* Format a string given a %s format, e.g. %40s or %-20s. To do: ignore other flags (#, +, etc)? *) let format_string format s = let (p, neg) = parse_format format in pad_string ' ' p neg s 0 (String.length s) (* Format a string given a %s format, e.g. %40s or %-20s. To do: ignore other flags (#, +, etc)? *) let format_string format s = let rec parse_format neg i = if i >= String.length format then (0, neg) else match String.unsafe_get format i with | '1'..'9' -> (int_of_string (String.sub format i (String.length format - i - 1)), neg) | '-' -> parse_format true (succ i) | _ -> parse_format neg (succ i) in let (p, neg) = try parse_format false 1 with Failure _ -> bad_format format 0 in if String.length s < p then begin let res = String.make p ' ' in if neg then String.blit s 0 res 0 (String.length s) else String.blit s 0 res (p - String.length s) (String.length s); res end else s (* Format a [%b] format: write a binary representation of an integer. *) let format_binary_int format n = let sharp = String.contains format '#' in let add_sharp_len l = if sharp then l + 2 else l in (* Max length of a Caml int + 1 for a minus sign. *) let maxlen = Sys.word_size - 1 + 1 in let len = add_sharp_len maxlen in let b = String.make len ' ' in let rec format_bin i n = if n = 0 then i else let c = char_of_int (int_of_char '0' + n land 1) in String.unsafe_set b i c; format_bin (i - 1) (n lsr 1) in let rec find_pad_char i len = if i >= len then ' ' else match String.unsafe_get format i with | '0' -> '0' | '1' .. '9' -> ' ' | _ -> find_pad_char (i + 1) len in let add_sharp s i = String.unsafe_set s i '0'; String.unsafe_set s (i + 1) 'b' in let add_bin pad_char s i = match pad_char with | ' ' -> add_sharp s i; s | _ -> add_sharp s 0; s in let i = match n with | 0 -> String.unsafe_set b (len - 1) '0'; len - 2 | n -> format_bin (len - 1) n in let p, neg = parse_format format in let blen = len - 1 - i in let pad_char = find_pad_char 0 (String.length format) in let p = add_sharp_len (max p blen) in let s = pad_string pad_char p neg b (i + 1) blen in if sharp then add_bin pad_char s (i - 1) else s;; (* Extract a %format from [fmt] between [start] and [stop] inclusive. '*' in the format are replaced by integers taken from the [widths] list. The function is somewhat optimized for the "no *" case. *) let extract_format fmt start stop widths = match widths with | [] -> String.sub fmt start (stop - start + 1) | _ -> let b = Buffer.create (stop - start + 10) in let rec fill_format i w = if i > stop then Buffer.contents b else match (String.unsafe_get fmt i, w) with ('*', h::t) -> Buffer.add_string b (string_of_int h); fill_format (succ i) t | ('*', []) -> bad_format fmt start (* should not happen *) | (c, _) -> Buffer.add_char b c; fill_format (succ i) w in fill_format start (List.rev widths) (* Decode a %format and act on it. [fmt] is the printf format style, and [pos] points to a [%] character. After consuming the appropriate number of arguments and formatting them, one of the three continuations is called: [cont_s] for outputting a string (args: string, next pos) [cont_a] for performing a %a action (args: fn, arg, next pos) [cont_t] for performing a %t action (args: fn, next pos) "next pos" is the position in [fmt] of the first character following the %format in [fmt]. *) (* Note: here, rather than test explicitly against [String.length fmt] to detect the end of the format, we use [String.unsafe_get] and rely on the fact that we'll get a "nul" character if we access one past the end of the string. These "nul" characters are then caught by the [_ -> bad_format] clauses below. Don't do this at home, kids. *) let scan_format fmt pos cont_s cont_a cont_t = let rec scan_flags widths i = match String.unsafe_get fmt i with | '*' -> Obj.magic(fun w -> scan_flags (w :: widths) (succ i)) | '0'..'9' | '.' | '#' | '-' | ' ' | '+' -> scan_flags widths (succ i) | _ -> scan_conv widths i and scan_conv widths i = match String.unsafe_get fmt i with | '%' -> cont_s "%" (succ i) | 's' | 'S' as conv -> Obj.magic (fun (s: string) -> let s = if conv = 's' then s else "\"" ^ String.escaped s ^ "\"" in if i = succ pos (* optimize for common case %s *) then cont_s s (succ i) else cont_s (format_string (extract_format fmt pos i widths) s) (succ i)) | 'c' | 'C' as conv -> Obj.magic (fun (c: char) -> if conv = 'c' then cont_s (String.make 1 c) (succ i) else cont_s ("'" ^ Char.escaped c ^ "'") (succ i)) | 'b' -> Obj.magic(fun (n: int) -> cont_s (format_binary_int (extract_format fmt pos i widths) n) (succ i)) | 'd' | 'i' | 'o' | 'x' | 'X' | 'u' as conv -> Obj.magic(fun (n: int) -> cont_s (format_int (extract_format fmt pos i widths) n) (succ i)) | 'f' | 'e' | 'E' | 'g' | 'G' | 'F' as conv -> Obj.magic(fun (f: float) -> let s = if conv = 'F' then string_of_float f else format_float (extract_format fmt pos i widths) f in cont_s s (succ i)) | 'B' -> Obj.magic(fun (b: bool) -> cont_s (string_of_bool b) (succ i)) | 'a' -> Obj.magic (fun printer arg -> cont_a printer arg (succ i)) | 't' -> Obj.magic (fun printer -> cont_t printer (succ i)) | 'l' -> begin match String.unsafe_get fmt (succ i) with | 'd' | 'i' | 'o' | 'x' | 'X' | 'u' -> Obj.magic(fun (n: int32) -> cont_s (format_int32 (extract_format fmt pos (succ i) widths) n) (i + 2)) | _ -> bad_format fmt pos end | 'n' -> begin match String.unsafe_get fmt (succ i) with | 'd' | 'i' | 'o' | 'x' | 'X' | 'u' -> Obj.magic(fun (n: nativeint) -> cont_s (format_nativeint (extract_format fmt pos (succ i) widths) n) (i + 2)) | _ -> bad_format fmt pos end | 'L' -> begin match String.unsafe_get fmt (succ i) with | 'd' | 'i' | 'o' | 'x' | 'X' | 'u' -> Obj.magic(fun (n: int64) -> cont_s (format_int64 (extract_format fmt pos (succ i) widths) n) (i + 2)) | _ -> bad_format fmt pos end | _ -> bad_format fmt pos in scan_flags [] (pos + 1) (* Application to [fprintf], etc. See also [Format.*printf]. *) let fprintf chan fmt = let fmt = (Obj.magic fmt : string) in let len = String.length fmt in let rec doprn i = if i >= len then Obj.magic () else match String.unsafe_get fmt i with | '%' -> scan_format fmt i cont_s cont_a cont_t | c -> output_char chan c; doprn (succ i) and cont_s s i = output_string chan s; doprn i and cont_a printer arg i = printer chan arg; doprn i and cont_t printer i = printer chan; doprn i in doprn 0 let printf fmt = fprintf stdout fmt let eprintf fmt = fprintf stderr fmt let kprintf kont fmt = let fmt = (Obj.magic fmt : string) in let len = String.length fmt in let dest = Buffer.create (len + 16) in let rec doprn i = if i >= len then begin let res = Buffer.contents dest in Buffer.clear dest; (* just in case kprintf is partially applied *) Obj.magic (kont res) end else match String.unsafe_get fmt i with | '%' -> scan_format fmt i cont_s cont_a cont_t | c -> Buffer.add_char dest c; doprn (succ i) and cont_s s i = Buffer.add_string dest s; doprn i and cont_a printer arg i = Buffer.add_string dest (printer () arg); doprn i and cont_t printer i = Buffer.add_string dest (printer ()); doprn i in doprn 0 let sprintf fmt = kprintf (fun x -> x) fmt;; let bprintf dest fmt = let fmt = (Obj.magic fmt : string) in let len = String.length fmt in let rec doprn i = if i >= len then Obj.magic () else match String.unsafe_get fmt i with | '%' -> scan_format fmt i cont_s cont_a cont_t | c -> Buffer.add_char dest c; doprn (succ i) and cont_s s i = Buffer.add_string dest s; doprn i and cont_a printer arg i = printer dest arg; doprn i and cont_t printer i = printer dest; doprn i in doprn 0