Commit Graph

137 Commits (ee8f71101b80496b2ec2c996d29ac33bbaf7cf00)

Author SHA1 Message Date
Damien Doligez ee8f71101b clean up whitespace and cut long lines 2016-02-17 13:36:27 +01:00
pierreweis 7fe468b820 Integer conversion 0x 0d 0u 0o 0b get a devoted sum data type definition. This is safer, cleaner and avoid assertion failures. Digit scanning functions renamed to *_plus or *_star to reflect their semantics with usual notations. The general digit scanner with digitp predicate is exposed as scan_digit_star out of its embedding _plus procedure for more regular coding scheme and to use it in other scanning function. Careful code review/rewriting. Code documentation. 2015-12-24 14:06:52 +01:00
pierreweis 989ba66803 Revert to old version of memo function for fscanf buffer allocation. Comments revisited and minor modifications. 2015-12-15 01:50:46 +01:00
Benoit Vaugon 484950d84b support for hexadecimal float notation in (scanf '%F') 2015-11-28 17:32:31 +01:00
Xavier Leroy 0c5e862a3e GPR#268: Hexadecimal notation for floating-point numbers
Merge of branch 'hex-float'.

- Add support in byterun/floats.c for conversions between floats and strings in hex notation. We cannot rely on the C standard library here because Microsoft consistently fails at supporting hex notation as standardized in C99. Instead, the conversions are implemented from scratch.
- Add support in the lexer so that hex float literals are recognized in OCaml sources.
- Add support in formats. The ISO C99 format letters for hex floats are %a and %A, but %a is already taken. I chose %h and %H, which are rejected today as bad formats (hence no backward incompatibility) and don't mean anything in C either (h is a modifier, not a format letter).
- Add support in printf. All the trimmings are there in the implementation of %h and %H, including sign modifier and fixed precision.
- Benoit Vaugon contributed support in scanf.

Resolved conflicts:
	boot/ocamlc
	boot/ocamldep
	boot/ocamllex
	parsing/lexer.mll
2015-11-19 10:37:20 +01:00
alainfrisch a127e661b2 Code cleanup: replace let-binding of type unit with sequence. 2015-10-27 11:28:36 +01:00
Damien Doligez 3397e7ff16 GPR#243: Faster test suite
(Xavier Leroy)


git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@16466 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2015-10-09 15:45:37 +00:00
Pierre Weis 36ab801e6f A second attempt to memoize Scanning.from_in_channel using weak pointers.
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@16443 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2015-09-24 18:31:11 +00:00
Pierre Weis 5485362404 Scanning.from_channel now uses a weak hash table to record in_channel -> scanbuf associations. This should prevent memory leaks in program that intensively call Scanf.fscanf.
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@16430 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2015-09-21 17:17:04 +00:00
Pierre Weis 1cd50636fa Bug in function check_char corrected: instead of only accepting \r\n as a new
line, it accepted any amount of \r followed by \n.
Float scanning code revisited, commenting the code and avoiding side effect
in function application.
Type file_name now used to define in_channel_name, hence its definition goes
before in_channel_name.
open/close_in --> Pervasives.open/close_in when necessary.
Indentation revisited.


git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@16421 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2015-09-13 18:02:03 +00:00
Damien Doligez b860d63145 whitespace cleanup, cut long lines, add some missing headers
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@16415 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2015-09-11 11:58:31 +00:00
Pierre Weis 31a85a87b4 Typos in comments.
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@16399 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2015-08-28 00:12:11 +00:00
Xavier Leroy 86d29bf2a6 scanf support for %h and %H (hex floats).
(Contributed by Benoit Vaugon.)


git-svn-id: http://caml.inria.fr/svn/ocaml/branches/hex-float@16295 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2015-07-29 11:56:14 +00:00
Xavier Leroy bb86f5b545 Preliminary support for hexadecimal notation for FP numbers.
- Primitives:
     caml_float_of_string  extended to recognize "0x" hexa notation
     caml_hexstring_of_float  new primitive
  We do not assume hex floats are supported by the C standard library.
  Instead, conversions hex string <-> float are implemented manually.
- Printf: hex FP output supported with formats %h / %H
- Scanf: remains to be updated (see TODO in stdlib/scanf.ml)


git-svn-id: http://caml.inria.fr/svn/ocaml/branches/hex-float@16257 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2015-07-26 09:29:33 +00:00
Xavier Leroy a1bafbbb67 PR#6316: Scanf.scanf failure on %u formats when reading big integers.
The approach implemented is the second one suggested by Benoît Vaugon in the PR:
- The int_of_string functions accept a "0u" prefix meaning "decimal unsigned".
- The '%u' format of the scanf functions adds this "0u" prefix before conversion.
This is consistent with the current handling of unsigned hexa, octal, and binary numbers.


git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@16241 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2015-07-24 09:36:03 +00:00
Gabriel Scherer 3ad7f526a2 PR#6452, GPR#140: add internal support for custom printing formats
(Jérémie Dimino)

git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@15884 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2015-03-08 09:36:10 +00:00
Gabriel Scherer efa9d3bd9e PR#6791: "%s@[", "%s@{" regression in Scanf
(Benoît Vaugon)

git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@15881 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2015-03-07 10:55:13 +00:00
Damien Doligez 031cffd155 merge branch 4.02 from release 4.02.0 to release 4.02.1
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@15558 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2014-10-15 13:34:58 +00:00
Damien Doligez cbfe627f92 merge changes from branch 4.02 from branching (rev 14852) to 4.02.0+rc1 (rev 15121)
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@15125 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2014-08-22 13:45:02 +00:00
Gabriel Scherer 49d3f7b9f8 PR#6418: support "@[<hov %d>" in the new format implementation (Benoît Vaugon)
The bootstrap procedure, as for commit trunk@14973 (see there for
detailed build instructions), requires to first commit a temporary
patch:

> diff -Naur old/typing/typecore.ml new/typing/typecore.ml
> --- old/typing/typecore.ml        2014-06-11 18:16:24.851647309 +0200
> +++ new/typing/typecore.ml        2014-06-11 18:15:50.075646418 +0200
> @@ -2758,16 +2758,9 @@
>        let mk_int n = mk_cst (Const_int n)
>        and mk_string str = mk_cst (Const_string (str, None))
>        and mk_char chr = mk_cst (Const_char chr) in
> -      let mk_block_type bty = match bty with
> -        | Pp_hbox   -> mk_constr "Pp_hbox"   []
> -        | Pp_vbox   -> mk_constr "Pp_vbox"   []
> -        | Pp_hvbox  -> mk_constr "Pp_hvbox"  []
> -        | Pp_hovbox -> mk_constr "Pp_hovbox" []
> -        | Pp_box    -> mk_constr "Pp_box"    []
> -        | Pp_fits   -> mk_constr "Pp_fits"   [] in
>        let rec mk_formatting_lit fmting = match fmting with
> -        | Open_box (org, bty, idt) ->
> -          mk_constr "Open_box" [ mk_string org; mk_block_type bty; mk_int idt ]
> +        | Open_box _ ->
> +          assert false
>          | Close_box ->
>            mk_constr "Close_box" []
>          | Close_tag ->
> @@ -2950,6 +2943,19 @@
>            mk_constr "Alpha" [ mk_fmt rest ]
>          | Theta rest ->
>            mk_constr "Theta" [ mk_fmt rest ]
> +        | Formatting_lit (Open_box (org, _bty, _idt), rest) ->
> +          mk_constr "Formatting_gen" [
> +            mk_constr "Open_box" [
> +              mk_constr "Format" [
> +                mk_constr "String_literal" [
> +                  mk_string "<>";
> +                  mk_constr "End_of_format" [];
> +                ];
> +                mk_string "@[<>";
> +              ]
> +            ];
> +            mk_fmt rest;
> +          ]
>          | Formatting_lit (fmting, rest) ->
>            mk_constr "Formatting_lit" [ mk_formatting_lit fmting; mk_fmt rest ]
>          | Formatting_gen (fmting, rest) ->

git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@14984 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2014-06-14 21:08:50 +00:00
Gabriel Scherer 7cb9d0d84e PR#6418: fix format regression on "@{<..%d..%s..>" (Benoît Vaugon)
To be able to compile this patch, you should temporarily apply the
following patch to bootstrap the format type change:

> diff -Naur old/typing/typecore.ml new/typing/typecore.ml
> --- old/typing/typecore.ml	2014-06-06 03:37:03.240926150 +0200
> +++ new/typing/typecore.ml	2014-06-06 03:37:24.696926699 +0200
> @@ -2956,7 +2956,7 @@
>          | Theta rest ->
>            mk_constr "Theta" [ mk_fmt rest ]
>          | Formatting (fmting, rest) ->
> -          mk_constr "Formatting" [ mk_formatting fmting; mk_fmt rest ]
> +          mk_constr "Formatting_lit" [ mk_formatting fmting; mk_fmt rest ]
>          | Reader rest ->
>            mk_constr "Reader" [ mk_fmt rest ]
>          | Scan_char_set (width_opt, char_set, rest) ->

Bootstrap process:

  make core
  apply the patch above
  make core
  make promote-cross
  make partialclean
  revert the patch above, apply the commit
  make partialclean
  make core
  make coreboot

git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@14973 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2014-06-09 13:53:47 +00:00
Gabriel Scherer e0b000527b format+gadts: make format types "relational" to fix %(...%) typing
See the long comment in pervasives.ml for an explanation of the
change. The short summary is that we need to prove more elaborate
properties between the format types involved in the typing of %(...%),
and that proving things by writing GADT functions in OCaml reveals
that Coq's Ltac is a miracle of usability.

Proofs on OCaml GADTs are runtime functions that do have a runtime
semantics: it is legitimate to hope that those proof computations are
as simple as possible, but the current implementation was optimized
for feasability, not simplicity. François Bobot has some interesting
suggestions to simplify the reasoning part (with more equality
reasoning where I used transitivity and symmetry of the
relation profusely), which may make the code simpler in the future
(and possibly more efficient: the hope is that only %(...%) users will
pay a proof-related cost).

git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@14897 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2014-05-21 13:23:13 +00:00
Gabriel Scherer 3ffa399b37 Use a nominal datatype for CamlinternalFormat.format6
This should make the type-checking of formats simpler and more robust:
instead of trying to find a pair as previously, we can now use the
path of the format6 type directly.

A nice side-effect of the change is that the internal definition of
formats (as a pair) is not printed in error messages anymore.
Because format6 is in fact defined in the CamlinternalFormatBasics
submodule of Pervasives, and has an alias at the toplevel of
Pervasives, error messages still expand the definition:

> Error: This expression has type
>          ('a, 'b, 'c, 'd, 'd, 'a) format6 =
>            ('a, 'b, 'c, 'd, 'd, 'a) CamlinternalFormatBasics.format6
>        but an expression was expected of type ...

Passing the option `-short-paths` does avoid this expansion and
returns exactly the same error message as 4.01:

> Error: This expression has type ('a, 'b, 'c, 'd, 'd, 'a) format6
>        but an expression was expected of type ...

(To get this error message without -short-paths, one would need to
define format6 directly in Pervasives; but this type is mutually
recursive with several GADT types that we don't want to add in the
Pervasives namespace unqualified. This is why I'll keep the alias
for now.)

git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@14868 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2014-05-14 15:07:13 +00:00
Gabriel Scherer bf6e3185c0 Add support for ignored scan_get_counter formats (%_[nlNL])
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@14820 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2014-05-12 15:37:56 +00:00
Gabriel Scherer 72669307e8 second part of Benoît Vaugon's format+gadts patch
To finish the bootstrap cycle, run:

  make library-cross
  make promote
  make partialclean
  make core

  make library-cross
  make promote-cross
  make partialclean
  make ocamlc ocamllex ocamltools

  make library-cross
  make promote
  make partialclean
  make core
  make compare

git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@14810 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2014-05-12 15:37:37 +00:00
Damien Doligez 5b8df637d2 merge branch "safe-string"
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@14705 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2014-04-29 11:56:17 +00:00
Hongbo Zhang e97c59d045 fix scanf.ml build
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@13728 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2013-06-02 14:42:33 +00:00
Pierre Weis e833f3c9d5 Better error messages for binary/octal/hexa integer scanning.
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@13725 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2013-06-01 09:01:59 +00:00
Pierre Weis 626c696aee Wrong quoting chase.
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@13717 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2013-05-29 18:03:55 +00:00
Pierre Weis 559521f125 Documentation.
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@13412 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2013-03-19 08:02:15 +00:00
Damien Doligez c63f9e0957 fix a few problems with whitespace and over-long lines
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@13393 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2013-03-09 22:38:52 +00:00
Pierre Weis 4a6a0c199d Normalization.
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@13292 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2013-02-12 08:14:49 +00:00
Damien Doligez def31744f9 remove all $Id keywords
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@13013 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2012-10-15 17:50:56 +00:00
Alain Frisch 4dcc69b52c Detect (and fix some) useless recursive flags.
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@12501 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2012-05-29 12:31:28 +00:00
Damien Doligez 1b782a0122 PR#5585: typo explicitely -> explicitly
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@12353 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2012-04-13 12:44:29 +00:00
Damien Doligez 6c24f4f90b merge version 3.12 from 3.12.1 to r12205
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@12210 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2012-03-08 19:52:03 +00:00
Damien Doligez b4ccb873a6 PR#5380: copy fix from 3.12 branch
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@12014 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2012-01-11 15:22:51 +00:00
Fabrice Le Fessant d02419cef7 Fix bug #3888 (String.map and Scanf.unescaped)
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@12004 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2012-01-08 15:38:38 +00:00
Damien Doligez cca0035fbb continuing to change the name to OCaml
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@11922 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2011-12-21 15:37:54 +00:00
Pierre Weis 99451ca83e Implementing the precision feature for Scanf.
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@11255 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2011-10-28 21:35:32 +00:00
Pierre Weis 2a2fcade52 Bug #4380.
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@11243 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2011-10-25 13:13:54 +00:00
Damien Doligez 3b507dd1aa renaming of Objective Caml to OCaml and cleanup of copyright headers
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@11156 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2011-07-27 14:17:02 +00:00
Pierre Weis c5289420e9 Module Printf, Format, and Scanf are printed in -w A warning mode. This found an old and subtle bug in Format; for other modules, the code is clearer and cleaner!
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@11100 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2011-06-20 21:46:20 +00:00
Pierre Weis 0d2a1430d0 Defining type file_name.
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@10963 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2011-02-23 18:39:15 +00:00
Pierre Weis 2855154d6c Typo in module Scanf prevented tests to succeeded properly.
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@10377 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2010-05-05 17:49:19 +00:00
Pierre Weis 1b5c521bb7 Forgotten export added. Remove spurious warninggs from Oug[1].
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@10374 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2010-05-05 12:58:01 +00:00
Pierre Weis 8fdedc9035 PR#4983. Test suite succesfully passed.
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@10344 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2010-05-02 18:38:35 +00:00
Pierre Weis c73e191b80 Documentation + some rewriting in check_next_char.
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@10318 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2010-04-27 10:35:18 +00:00
Pierre Weis 5a23453ce6 Bug in function scan: the size of the string format argument must be calculated inside the scan function body, not before. Otherwise, recursive independant calls to scan assume a wrong length for the format string. More explicit error messages.
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@10305 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2010-04-25 14:56:59 +00:00
Pierre Weis 818c9a0742 Adding a close-in function to module Scanf, to be able to close a Scanf scan buffer (hence its underlying Pervasives.in_channel, if any).
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@9501 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2009-12-29 19:04:35 +00:00