From 174eb485d08a1a48bb83f35d8afd410e341a5db4 Mon Sep 17 00:00:00 2001
From: Adrien Nader <adrien@notk.org>
Date: Wed, 23 Nov 2011 22:02:42 +0100
Subject: [PATCH] Apply -for-pack patch and make tests work.

---
 .gitignore                                    |    6 ++
 examples/packedlib/LICENSE                    |   20 +++++++
 examples/packedlib/_oasis                     |   16 ++++++
 examples/packedlib/src/bar.ml                 |   25 +++++++++
 examples/packedlib/src/bar.mli                |   24 ++++++++
 examples/packedlib/src/foo.ml                 |   25 +++++++++
 examples/packedlib/src/foo.mli                |   24 ++++++++
 src/oasis/OASISLibrary.ml                     |   73 ++++++++++++++-----------
 src/oasis/OASISLibrary_intern.ml              |   10 ++++
 src/oasis/OASISTypes.ml                       |    1 +
 src/oasis/OASISTypes.mli                      |    2 +
 src/plugins/internal/InternalInstallPlugin.ml |   60 +++++++++++----------
 src/plugins/ocamlbuild/MyOCamlbuildBase.ml    |    2 +-
 src/plugins/ocamlbuild/OCamlbuildPlugin.ml    |   39 +++++++++++++-
 test/TestFull.ml                              |   23 ++++++++
 test/TestQuickstart.ml                        |    2 +
 16 files changed, 289 insertions(+), 63 deletions(-)
 create mode 100644 .gitignore
 create mode 100644 examples/packedlib/LICENSE
 create mode 100644 examples/packedlib/_oasis
 create mode 100644 examples/packedlib/src/bar.ml
 create mode 100644 examples/packedlib/src/bar.mli
 create mode 100644 examples/packedlib/src/foo.ml
 create mode 100644 examples/packedlib/src/foo.mli

diff --git a/.gitignore b/.gitignore
new file mode 100644
index 0000000..29a0e0d
--- /dev/null
+++ b/.gitignore
@@ -0,0 +1,6 @@
+*~
+*.mllib
+*.odocl
+*.data
+*.log
+.*.sw[po]
diff --git a/examples/packedlib/LICENSE b/examples/packedlib/LICENSE
new file mode 100644
index 0000000..30739df
--- /dev/null
+++ b/examples/packedlib/LICENSE
@@ -0,0 +1,20 @@
+********************************************************************************
+*  OASIS: architecture for building OCaml libraries and applications           *
+*                                                                              *
+*  Copyright (C) 2008-2010, OCamlCore SARL                                     *
+*                                                                              *
+*  This library is free software; you can redistribute it and/or modify it     *
+*  under the terms of the GNU Lesser General Public License as published by    *
+*  the Free Software Foundation; either version 2.1 of the License, or (at     *
+*  your option) any later version, with the OCaml static compilation           *
+*  exception.                                                                  *
+*                                                                              *
+*  This library is distributed in the hope that it will be useful, but         *
+*  WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY  *
+*  or FITNESS FOR A PARTICULAR PURPOSE. See the file COPYING for more          *
+*  details.                                                                    *
+*                                                                              *
+*  You should have received a copy of the GNU Lesser General Public License    *
+*  along with this library; if not, write to the Free Software Foundation,     *
+*  Inc., 51 Franklin St, Fifth Floor, Boston, MA  02110-1301 USA               *
+********************************************************************************
diff --git a/examples/packedlib/_oasis b/examples/packedlib/_oasis
new file mode 100644
index 0000000..f051710
--- /dev/null
+++ b/examples/packedlib/_oasis
@@ -0,0 +1,16 @@
+Name: packedlib
+Version: 0.1
+OASISFormat: 0.1
+Authors: Till Varoquaux <till@janestreet.com>
+Maintainers: Till Varoquaux <till@janestreet.com>
+Copyrights: (C) 2011 Till Varoquaux
+License: LGPL with OCaml linking exception
+BuildTools: ocamlbuild
+
+Synopsis: Testing packed libraries work fine in oasis
+
+
+Library packedlib
+  Pack: true
+  Path: src
+  Modules: Foo, Bar
diff --git a/examples/packedlib/src/bar.ml b/examples/packedlib/src/bar.ml
new file mode 100644
index 0000000..97f146a
--- /dev/null
+++ b/examples/packedlib/src/bar.ml
@@ -0,0 +1,25 @@
+(********************************************************************************)
+(*  OASIS: architecture for building OCaml libraries and applications           *)
+(*                                                                              *)
+(*  Copyright (C) 2008-2010, OCamlCore SARL                                     *)
+(*                                                                              *)
+(*  This library is free software; you can redistribute it and/or modify it     *)
+(*  under the terms of the GNU Lesser General Public License as published by    *)
+(*  the Free Software Foundation; either version 2.1 of the License, or (at     *)
+(*  your option) any later version, with the OCaml static compilation           *)
+(*  exception.                                                                  *)
+(*                                                                              *)
+(*  This library is distributed in the hope that it will be useful, but         *)
+(*  WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY  *)
+(*  or FITNESS FOR A PARTICULAR PURPOSE. See the file COPYING for more          *)
+(*  details.                                                                    *)
+(*                                                                              *)
+(*  You should have received a copy of the GNU Lesser General Public License    *)
+(*  along with this library; if not, write to the Free Software Foundation,     *)
+(*  Inc., 51 Franklin St, Fifth Floor, Boston, MA  02110-1301 USA               *)
+(********************************************************************************)
+
+type t = string
+
+let create s = s
+let value s = s
diff --git a/examples/packedlib/src/bar.mli b/examples/packedlib/src/bar.mli
new file mode 100644
index 0000000..664e096
--- /dev/null
+++ b/examples/packedlib/src/bar.mli
@@ -0,0 +1,24 @@
+(********************************************************************************)
+(*  OASIS: architecture for building OCaml libraries and applications           *)
+(*                                                                              *)
+(*  Copyright (C) 2008-2010, OCamlCore SARL                                     *)
+(*                                                                              *)
+(*  This library is free software; you can redistribute it and/or modify it     *)
+(*  under the terms of the GNU Lesser General Public License as published by    *)
+(*  the Free Software Foundation; either version 2.1 of the License, or (at     *)
+(*  your option) any later version, with the OCaml static compilation           *)
+(*  exception.                                                                  *)
+(*                                                                              *)
+(*  This library is distributed in the hope that it will be useful, but         *)
+(*  WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY  *)
+(*  or FITNESS FOR A PARTICULAR PURPOSE. See the file COPYING for more          *)
+(*  details.                                                                    *)
+(*                                                                              *)
+(*  You should have received a copy of the GNU Lesser General Public License    *)
+(*  along with this library; if not, write to the Free Software Foundation,     *)
+(*  Inc., 51 Franklin St, Fifth Floor, Boston, MA  02110-1301 USA               *)
+(********************************************************************************)
+
+type t
+val create : string -> t
+val value : t -> string
diff --git a/examples/packedlib/src/foo.ml b/examples/packedlib/src/foo.ml
new file mode 100644
index 0000000..de6c94d
--- /dev/null
+++ b/examples/packedlib/src/foo.ml
@@ -0,0 +1,25 @@
+(********************************************************************************)
+(*  OASIS: architecture for building OCaml libraries and applications           *)
+(*                                                                              *)
+(*  Copyright (C) 2008-2010, OCamlCore SARL                                     *)
+(*                                                                              *)
+(*  This library is free software; you can redistribute it and/or modify it     *)
+(*  under the terms of the GNU Lesser General Public License as published by    *)
+(*  the Free Software Foundation; either version 2.1 of the License, or (at     *)
+(*  your option) any later version, with the OCaml static compilation           *)
+(*  exception.                                                                  *)
+(*                                                                              *)
+(*  This library is distributed in the hope that it will be useful, but         *)
+(*  WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY  *)
+(*  or FITNESS FOR A PARTICULAR PURPOSE. See the file COPYING for more          *)
+(*  details.                                                                    *)
+(*                                                                              *)
+(*  You should have received a copy of the GNU Lesser General Public License    *)
+(*  along with this library; if not, write to the Free Software Foundation,     *)
+(*  Inc., 51 Franklin St, Fifth Floor, Boston, MA  02110-1301 USA               *)
+(********************************************************************************)
+
+type t = int
+
+let create n = n
+let value n = n
diff --git a/examples/packedlib/src/foo.mli b/examples/packedlib/src/foo.mli
new file mode 100644
index 0000000..751ebf3
--- /dev/null
+++ b/examples/packedlib/src/foo.mli
@@ -0,0 +1,24 @@
+(********************************************************************************)
+(*  OASIS: architecture for building OCaml libraries and applications           *)
+(*                                                                              *)
+(*  Copyright (C) 2008-2010, OCamlCore SARL                                     *)
+(*                                                                              *)
+(*  This library is free software; you can redistribute it and/or modify it     *)
+(*  under the terms of the GNU Lesser General Public License as published by    *)
+(*  the Free Software Foundation; either version 2.1 of the License, or (at     *)
+(*  your option) any later version, with the OCaml static compilation           *)
+(*  exception.                                                                  *)
+(*                                                                              *)
+(*  This library is distributed in the hope that it will be useful, but         *)
+(*  WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY  *)
+(*  or FITNESS FOR A PARTICULAR PURPOSE. See the file COPYING for more          *)
+(*  details.                                                                    *)
+(*                                                                              *)
+(*  You should have received a copy of the GNU Lesser General Public License    *)
+(*  along with this library; if not, write to the Free Software Foundation,     *)
+(*  Inc., 51 Franklin St, Fifth Floor, Boston, MA  02110-1301 USA               *)
+(********************************************************************************)
+
+type t
+val create : int -> t
+val value : t -> int
diff --git a/src/oasis/OASISLibrary.ml b/src/oasis/OASISLibrary.ml
index 816eca4..b07534d 100644
--- a/src/oasis/OASISLibrary.ml
+++ b/src/oasis/OASISLibrary.ml
@@ -29,36 +29,40 @@ let generated_unix_files ~ctxt (cs, bs, lib)
       source_file_exists is_native ext_lib ext_dll =
   (* The headers that should be compiled along *)
   let headers =
-    List.fold_left
-      (fun hdrs modul ->
-         try
-           let base_fn =
-             List.find
-               (fun fn ->
-                  source_file_exists (fn^".ml") ||
-                  source_file_exists (fn^".mli") ||
-                  source_file_exists (fn^".mll") ||
-                  source_file_exists (fn^".mly"))
-               (List.map
-                  (OASISUnixPath.concat bs.bs_path)
-                  [modul;
-                   OASISUnixPath.uncapitalize_file modul;
-                   OASISUnixPath.capitalize_file modul])
-           in
-             [base_fn^".cmi"] :: hdrs
-         with Not_found ->
-           OASISMessage.warning
-             ~ctxt
-             (f_ "Cannot find source file matching \
-                  module '%s' in library %s")
-             modul cs.cs_name;
-             (List.map (OASISUnixPath.concat bs.bs_path)
-                [modul^".cmi";
-                 OASISUnixPath.uncapitalize_file modul ^ ".cmi";
-                 OASISUnixPath.capitalize_file modul ^ ".cmi"])
-             :: hdrs)
+    if lib.lib_pack then
       []
-      lib.lib_modules
+    else
+      List.fold_left
+        (fun hdrs modul ->
+           try 
+             let base_fn = 
+               List.find
+                 (fun fn -> 
+                    source_file_exists (fn^".ml") ||
+                    source_file_exists (fn^".mli") ||
+                    source_file_exists (fn^".mll") ||
+                    source_file_exists (fn^".mly")) 
+                 (List.map
+                    (OASISUnixPath.concat bs.bs_path)
+                    [modul;
+                     String.uncapitalize modul;
+                     String.capitalize modul])
+             in
+               [base_fn^".cmi"] :: hdrs
+           with Not_found ->
+             OASISMessage.warning
+               ~ctxt
+               (f_ "Cannot find source file matching \
+                    module '%s' in library %s")
+               modul cs.cs_name;
+               (List.map (OASISUnixPath.concat bs.bs_path)
+                  [modul^".cmi";
+                   String.uncapitalize modul ^ ".cmi";
+                   String.capitalize modul ^ ".cmi"])
+               :: hdrs)
+        []
+        lib.lib_modules
+
   in
 
   let acc_nopath =
@@ -67,11 +71,18 @@ let generated_unix_files ~ctxt (cs, bs, lib)
 
   (* Compute what libraries should be built *)
   let acc_nopath =
+    (* Add the packed header file if required *)
+    let add_pack_header acc =
+      if lib.lib_pack then
+        [cs.cs_name^".cmi"] :: acc
+      else
+        acc
+    in
     let byte acc =
-      [cs.cs_name^".cma"] :: acc
+      add_pack_header ([cs.cs_name^".cma"] :: acc)
     in
     let native acc =
-      [cs.cs_name^".cmxa"] :: [cs.cs_name^(ext_lib ())] :: acc
+      add_pack_header ([cs.cs_name^".cmxa"] :: [cs.cs_name^(ext_lib ())] :: acc)
     in
       match bs.bs_compiled_object with
         | Native ->
diff --git a/src/oasis/OASISLibrary_intern.ml b/src/oasis/OASISLibrary_intern.ml
index 7e7f002..2e99285 100644
--- a/src/oasis/OASISLibrary_intern.ml
+++ b/src/oasis/OASISLibrary_intern.ml
@@ -64,6 +64,15 @@ let schema, generator =
          s_ "List of modules to compile which are not exported.")
       (fun (_, _, lib) -> lib.lib_internal_modules)
   in
+  let pack =
+    new_field schm "Pack"
+      ~default:false
+      ~quickstart_level:Expert
+      boolean
+      (fun () ->
+         s_ "Set if we should build a packed library.")
+      (fun (_, _, lib) -> lib.lib_pack)
+  in
   let findlib_parent =
     new_field schm "FindlibParent"
       ~default:None
@@ -102,6 +111,7 @@ let schema, generator =
           {
             lib_modules            = external_modules data;
             lib_internal_modules   = internal_modules data;
+            lib_pack               = pack data;
             lib_findlib_parent     = findlib_parent data;
             lib_findlib_name       = findlib_name data;
             lib_findlib_containers = findlib_containers data;
diff --git a/src/oasis/OASISTypes.ml b/src/oasis/OASISTypes.ml
index 6b79a15..f34ed29 100644
--- a/src/oasis/OASISTypes.ml
+++ b/src/oasis/OASISTypes.ml
@@ -140,6 +140,7 @@ type library =
     {
       lib_modules:            string list;
       lib_internal_modules:   string list;
+      lib_pack:               bool;
       lib_findlib_parent:     findlib_name option;
       lib_findlib_name:       findlib_name option;
       lib_findlib_containers: findlib_name list;
diff --git a/src/oasis/OASISTypes.mli b/src/oasis/OASISTypes.mli
index ecf209f..2e98df4 100644
--- a/src/oasis/OASISTypes.mli
+++ b/src/oasis/OASISTypes.mli
@@ -196,6 +196,8 @@ type library =
       (** List of modules exported by the library. *)
       lib_internal_modules:   string list;
       (** List of modules not-exported by the library, but compiled along. *)
+      lib_pack:               bool;
+      (** Are we building a packed library? *)
       lib_findlib_parent:     findlib_name option;
       (** Name of the findlib parent, if any. *)
       lib_findlib_name:       findlib_name option;
diff --git a/src/plugins/internal/InternalInstallPlugin.ml b/src/plugins/internal/InternalInstallPlugin.ml
index f31afa8..bca3c3f 100644
--- a/src/plugins/internal/InternalInstallPlugin.ml
+++ b/src/plugins/internal/InternalInstallPlugin.ml
@@ -130,38 +130,40 @@ let install pkg argv =
            BaseBuilt.is_built BaseBuilt.BLib cs.cs_name then
           begin
             let acc =
-              (* Start with acc + lib_extra *)
               List.rev_append lib_extra acc
             in
             let acc =
-              (* Add uncompiled header from the source tree *)
-              let path =
-                BaseFilePath.of_unix bs.bs_path
-              in
-                List.fold_left
-                  (fun acc modul ->
-                     try
-                       List.find
-                         Sys.file_exists
-                         (List.map
-                            (Filename.concat path)
-                            [modul^".mli";
-                             modul^".ml";
-                             OASISUnixPath.uncapitalize_file modul^".mli";
-                             OASISUnixPath.capitalize_file   modul^".mli";
-                             OASISUnixPath.uncapitalize_file modul^".ml";
-                             OASISUnixPath.capitalize_file   modul^".ml"])
-                       :: acc
-                     with Not_found ->
-                       begin
-                         warning
-                           (f_ "Cannot find source header for module %s \
-                                in library %s")
-                           modul cs.cs_name;
-                         acc
-                       end)
-                  acc
-                  lib.lib_modules
+              if lib.lib_pack then
+                acc
+              else
+                (* Add uncompiled header from the source tree (for non-packed libraries) *)
+                let path = 
+                  BaseFilePath.of_unix bs.bs_path
+                in
+                  List.fold_left
+                    (fun acc modul ->
+                       try 
+                         List.find
+                           Sys.file_exists 
+                           (List.map
+                              (Filename.concat path)
+                              [modul^".mli";
+                               modul^".ml";
+                               String.uncapitalize modul^".mli";
+                               String.capitalize   modul^".mli";
+                               String.uncapitalize modul^".ml";
+                               String.capitalize   modul^".ml"])
+                         :: acc
+                       with Not_found ->
+                         begin
+                           warning 
+                             (f_ "Cannot find source header for module %s \
+                                  in library %s")
+                             modul cs.cs_name;
+                           acc
+                         end)
+                    acc
+                    lib.lib_modules
             in
 
             let acc =
diff --git a/src/plugins/ocamlbuild/MyOCamlbuildBase.ml b/src/plugins/ocamlbuild/MyOCamlbuildBase.ml
index be46166..2d36de5 100644
--- a/src/plugins/ocamlbuild/MyOCamlbuildBase.ml
+++ b/src/plugins/ocamlbuild/MyOCamlbuildBase.ml
@@ -129,7 +129,7 @@ let dispatch t e =
                  (* When ocaml link something that use the C library, then one
                     need that file to be up to date.
                   *)
-                 dep  ["link"; "ocaml"; "use_lib"^lib] 
+                 dep  ["compile"; "ocaml"; "use_lib"^lib] 
                    [dir/"lib"^lib^"."^(!Options.ext_lib)];
 
                  (* TODO: be more specific about what depends on headers *)
diff --git a/src/plugins/ocamlbuild/OCamlbuildPlugin.ml b/src/plugins/ocamlbuild/OCamlbuildPlugin.ml
index 7c0bbe5..08d4046 100644
--- a/src/plugins/ocamlbuild/OCamlbuildPlugin.ml
+++ b/src/plugins/ocamlbuild/OCamlbuildPlugin.ml
@@ -572,6 +572,35 @@ let add_ocamlbuild_files ctxt pkg =
                      ["include"]
                  in
 
+                 let tag_t =
+                   if lib.lib_pack then
+                     let fnames =
+                       List.fold_left
+                         (fun acc s ->
+                           (FilePath.UnixPath.add_extension s "cmx")
+                           :: (FilePath.UnixPath.add_extension
+                                 (String.uncapitalize s)
+                                 "cmx")
+                           :: acc)
+                         []
+                         lib.lib_modules
+                     in
+                     add_tags
+                       tag_t
+                       (List.fold_left
+                          (fun acc dn ->
+                            List.fold_left
+                              (fun acc fn ->
+                                Filename.concat dn fn :: acc)
+                              acc
+                              fnames)
+                          []
+                          (src_dirs @ src_internal_dirs))
+                       ["for-pack(" ^ String.capitalize cs.cs_name ^ ")"]
+                   else
+                     tag_t
+                 in
+
                  let ctxt, tag_t, myocamlbuild_t =
                    bs_tags
                      pkg sct cs bs
@@ -601,13 +630,19 @@ let add_ocamlbuild_files ctxt pkg =
                  in
 
                  let ctxt =
-                   (* Generate .mllib files *)
+                   (* Generate .mllib or .mlpack files *)
+                   let extension =
+                     if lib.lib_pack then
+                       "mlpack"
+                     else
+                       "mllib"
+                   in
                    let fn_base =
                      prepend_bs_path bs cs.cs_name
                    in
                      add_file
                        (template_make
-                          (FilePath.add_extension fn_base "mllib")
+                          (FilePath.add_extension fn_base extension)
                           comment_ocamlbuild
                           []
                           (lib.lib_modules @ lib.lib_internal_modules)
diff --git a/test/TestFull.ml b/test/TestFull.ml
index b7825b6..a3b9e81 100644
--- a/test/TestFull.ml
+++ b/test/TestFull.ml
@@ -912,6 +912,29 @@ let tests =
             ],
             []);
 
+         (* Packed library *)
+         "../examples/packedlib", 
+         (fun () -> 
+            long_test,
+            oasis_ocamlbuild_files @ 
+              [ "src/packedlib.mlpack" ],
+            [
+              in_ocaml_library "packedlib" 
+                ["packedlib.cma"; 
+                 "foo.cmi"; "foo.mli"; 
+                 "bar.cmi"; "bar.mli"; 
+                 "META"];
+              conditional
+                !has_ocamlopt
+                (in_ocaml_library "packedlib"
+                   ["packedlib.cmxa"; 
+                    if Sys.os_type = "Win32" then
+                      "packedlib.lib"
+                    else
+                      "packedlib.a"]);
+            ],
+            []);
+
 
          (* Complete library with findlib package to check *)
          "../examples/findlib",
diff --git a/test/TestQuickstart.ml b/test/TestQuickstart.ml
index 5a569e9..cee2346 100644
--- a/test/TestQuickstart.ml
+++ b/test/TestQuickstart.ml
@@ -359,6 +359,7 @@ let tests =
            "nativeopt", "";
            "modules", "";
            "internalmodules", "";
+           "pack", "";
            "findlibparent", "";
            "findlibname", "";
            "findlibcontainers", "";
@@ -384,6 +385,7 @@ let tests =
            "nativeopt", "";
            "modules", "";
            "internalmodules", "";
+           "pack", "";
            "findlibparent", "libtest";
            "findlibname", "";
            "findlibcontainers", "";
-- 
1.7.5.1

