summaryrefslogtreecommitdiffstats
path: root/typing
AgeCommit message (Collapse)Author
2014-09-30Cleanup.Alain Frisch
git-svn-id: http://caml.inria.fr/svn/ocaml/branches/constructors_with_record4@15373 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2014-09-30Towards sugar-less encoding of constructor types.Alain Frisch
git-svn-id: http://caml.inria.fr/svn/ocaml/branches/constructors_with_record4@15372 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2014-09-29Towards getting rid of the internal syntactic sugar.Alain Frisch
git-svn-id: http://caml.inria.fr/svn/ocaml/branches/constructors_with_record4@15371 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2014-09-29Cleanup.Alain Frisch
git-svn-id: http://caml.inria.fr/svn/ocaml/branches/constructors_with_record3@15368 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2014-09-26Get rid of type-qualifed constructor paths for extensible types.Alain Frisch
git-svn-id: http://caml.inria.fr/svn/ocaml/branches/constructors_with_record3@15355 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2014-09-26Disallow multiple declaration of extension constructors with the same name ↵Alain Frisch
in the same module. git-svn-id: http://caml.inria.fr/svn/ocaml/branches/constructors_with_record3@15353 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2014-09-26Cleanup.Alain Frisch
git-svn-id: http://caml.inria.fr/svn/ocaml/branches/constructors_with_record3@15348 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2014-09-26Merge with trunk.Alain Frisch
git-svn-id: http://caml.inria.fr/svn/ocaml/branches/constructors_with_record3@15347 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2014-09-26Fix merge problem.Alain Frisch
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@15346 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2014-09-25Make it clear that type-qualified constructors are only allowed in bang types.Alain Frisch
git-svn-id: http://caml.inria.fr/svn/ocaml/branches/constructors_with_record3@15333 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2014-09-25Allow qualified reference to constructors (at least in bang-types). A ↵Alain Frisch
regular variant type supports qualified constructors of the form: M.t.X. An extensible variant type supports qualified constructors of the form: M.t.N.X. git-svn-id: http://caml.inria.fr/svn/ocaml/branches/constructors_with_record3@15332 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2014-09-23Refer to the inlined record type as !M.Foo for a constructor M.Foo.Alain Frisch
git-svn-id: http://caml.inria.fr/svn/ocaml/branches/constructors_with_record3@15315 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2014-09-05#5528: factorize the generation of names for inlined records.Alain Frisch
git-svn-id: http://caml.inria.fr/svn/ocaml/branches/constructors_with_record3@15194 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2014-09-04Sync with trunk.Alain Frisch
git-svn-id: http://caml.inria.fr/svn/ocaml/branches/constructors_with_record3@15190 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2014-09-01#6529: the checked flag is now part of pers_struct.Alain Frisch
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@15174 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2014-09-01#6529: further optimize consistency check.Alain Frisch
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@15171 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2014-08-29merge changes of version/4.02 from r15121 to r15155Damien Doligez
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@15168 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2014-08-28fix minor error-reporting bugGabriel Scherer
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@15141 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2014-08-22merge changes from branch 4.02 from branching (rev 14852) to 4.02.0+rc1 (rev ↵Damien Doligez
15121) git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@15125 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2014-08-12#5528: type extensions can create local type names t.A without an explicit ↵Alain Frisch
local type t (if the extended type is non-local). We must thus check explicitly uniqueness of synthesized type names t.A instead of relying on uniqueness of declared types as before (well, we already had the problem if someone redefined a local exn type). git-svn-id: http://caml.inria.fr/svn/ocaml/branches/constructors_with_record3@15083 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2014-08-12#5528: improve error reporting.Alain Frisch
git-svn-id: http://caml.inria.fr/svn/ocaml/branches/constructors_with_record3@15081 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2014-08-12#5528: improve error reporting.Alain Frisch
git-svn-id: http://caml.inria.fr/svn/ocaml/branches/constructors_with_record3@15080 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2014-08-12#5528: support rebinding inlined extension constructors with free variables.Alain Frisch
git-svn-id: http://caml.inria.fr/svn/ocaml/branches/constructors_with_record3@15079 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2014-08-08Cherry pick 15071 from 4.02 (Fix #6510: Removal of shadowed constructors of ↵Alain Frisch
extensible types can break the structure of definitions). git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@15072 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2014-08-07Sync with trunk. Rebinding of inlined extension constructors with free ↵Alain Frisch
variables is not yet supported. git-svn-id: http://caml.inria.fr/svn/ocaml/branches/constructors_with_record3@15069 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2014-08-06PR#6474: fix the "weak dependencies" support (patch by Leo White)Gabriel Scherer
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@15045 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2014-06-14PR#6418: support "@[<hov %d>" in the new format implementation (Benoît Vaugon)Gabriel Scherer
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-09PR#6418: fix format regression on "@{<..%d..%s..>" (Benoît Vaugon)Gabriel Scherer
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-09Fix PR#6417: sprintf broken when local module named Pervasives is in scopeGabriel Scherer
(Backport from Jacques' commit 4.02@14921) git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@14972 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2014-05-21format+gadts: make format types "relational" to fix %(...%) typingGabriel Scherer
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-14replay trunk@14523: warn on non-principal format6 coercionsGabriel Scherer
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@14869 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2014-05-14Use a nominal datatype for CamlinternalFormat.format6Gabriel Scherer
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-14apply patch for PR#6420: Bad error message for non-exhaustive matching on ↵Jacques Garrigue
extensible types git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@14859 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2014-05-12typecore.ml: fix format's expected-type mistakeGabriel Scherer
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@14826 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2014-05-12add typer support for the new formatsGabriel Scherer
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@14822 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2014-05-12update Benoît's patch wrt. Parsetree changesGabriel Scherer
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@14808 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2014-05-12convert Benoît's first patch to bytes/stringGabriel Scherer
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@14807 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2014-05-12first part of Benoît Vaugon's format-gadts patchGabriel Scherer
After applying this patch, you should run: make library-cross make promote-cross make partialclean make ocamlc ocamllex ocamltools and then immediately apply the following patches until the "second part of Benoît Vaugon's format+gadts patch"; the bootstrap cycle is not finished yet. git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@14806 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2014-05-12avoid warning just before an error happens using -no-alias-depsJacques Garrigue
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@14797 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2014-05-12* split Typetexp.lookup_module and Typetexp.find_moduleJacques Garrigue
* fix semantics of -open by using Typemod.type_open_ git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@14795 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2014-05-11Fix PR#6410: Error message for an attempt to use a functor as a module is ↵Jacques Garrigue
confusing git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@14790 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2014-05-11comment out Ctype.local_non_recursive_abbrevJacques Garrigue
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@14789 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2014-05-09indentationJacques Garrigue
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@14775 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2014-05-09disable Clflags.transparent_modules when narrowing unbound identifier errorJacques Garrigue
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@14774 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2014-05-09Fix PR#6405: unsound interaction of -rectypes and GADTsJacques Garrigue
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@14769 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2014-05-07Protocol to allow ppx processors to report warnings to the compiler ↵Alain Frisch
(reported as warning 22). git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@14762 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2014-05-07Expose a Typemod.type_interface (currently an alias of ↵Alain Frisch
Typemod.transl_signature) by symmetry with type_implementation. git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@14759 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2014-05-07Minor tweak to raw dump of parsetree/typedtree.Alain Frisch
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@14758 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2014-05-07Fix PR#6394: Assertion failed in Typecore.expand_pathJacques Garrigue
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@14757 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
2014-05-07#6399: protocol (based on a built-in ocaml.error extension node) to let ppx ↵Alain Frisch
tools send located errors to be reported by the compiler (patch by Peter Zotov). git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@14756 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02