Skip to content

Commit

Permalink
Merge pull request #1219 from OCamlPro/opamlfind
Browse files Browse the repository at this point in the history
This is an experiment to use ocamlfind calls to track installations
  • Loading branch information
AltGr committed Mar 5, 2014
2 parents 6348dfd + 40a5b01 commit 0c739b0
Show file tree
Hide file tree
Showing 3 changed files with 92 additions and 0 deletions.
2 changes: 2 additions & 0 deletions opam.install
@@ -1,4 +1,6 @@
bin: [
"_obuild/opam/opam.asm" { "opam" }
"_obuild/opam-admin/opam-admin.asm" { "opam-admin" }
"_obuild/opam-installer/opam-installer.asm" { "opam-installer" }
"_obuild/opamlfind/opamlfind.asm" { "opamlfind" }
]
83 changes: 83 additions & 0 deletions src/scripts/opamlfind.ml
@@ -0,0 +1,83 @@
(**************************************************************************)
(* *)
(* Copyright 2014 OCamlPro *)
(* *)
(* All rights reserved.This file is distributed under the terms of the *)
(* GNU Lesser General Public License version 3.0 with linking *)
(* exception. *)
(* *)
(* OPAM 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 GNU General Public *)
(* License for more details. *)
(* *)
(**************************************************************************)

let ocamlfind_command =
if Filename.basename Sys.executable_name = "ocamlfind"
then "ocamlfind.real"
else "ocamlfind"

let pass_on argv =
prerr_endline " [go on]";
Unix.execvp ocamlfind_command
(Array.concat [ [|ocamlfind_command|]; argv ])

let handle_install args =
match args with
| [] -> pass_on [||]
| package :: args ->
let dot_install = package ^ ".install" in
if Sys.file_exists dot_install then
(Printf.eprintf " %s exists, skipping" dot_install;
pass_on (Array.of_list (package::args)))
else
let isoption s = try s.[0] = '-' with Invalid_argument _ -> false in
let rec parse_params forcedll optional dlls files options = function
| ("-destdir" | "-metadir" | "-ldconf"
| "-patch-version" | "-patch-rmpkg") as arg :: param :: l ->
parse_params forcedll optional dlls files ((arg,param)::options) l
| "-optional" :: l -> parse_params forcedll true dlls files options l
| "-dll" :: l -> parse_params (Some true) optional dlls files options l
| "-nodll" :: l -> parse_params (Some false) optional dlls files options l
| option :: l when isoption option ->
parse_params forcedll optional dlls files ((option,"")::options) l
| file :: l ->
let isdll = match forcedll with
| Some d -> d
| None -> Filename.check_suffix file "dll" ||
Filename.check_suffix file "so"
in
let dlls, files =
if isdll then (file,optional)::dlls, files
else dlls, (file,optional)::files
in
parse_params forcedll optional dlls files options l
| [] -> List.rev dlls, List.rev files, List.rev options
in
let dlls, files, _options = parse_params None false [] [] [] args in
(* if try List.assoc "-destdir" rev_options <> opam-lib-dir
with Not_found -> false
then... *)
let oc = open_out dot_install in
let printl oc =
List.iter (fun (src,opt) ->
Printf.fprintf oc " %S\n" (if opt then "?" ^src else src))
in
if files <> [] then
Printf.fprintf oc "lib: [\n%a]\n" printl files;
if dlls <> [] then
Printf.fprintf oc "stublibs: [\n%a]\n" printl dlls;
close_out oc;
Printf.eprintf " %s%s%s generated"
(Sys.getcwd ()) Filename.dir_sep dot_install;
Printf.eprintf " [skip]\n"

let () =
prerr_string "[OPAM ocamlfind wrapper]";
if Array.length Sys.argv = 0 then pass_on Sys.argv else
match Sys.argv.(0) with
| "install" ->
let args = List.tl (Array.to_list Sys.argv) in
handle_install args
| _ -> pass_on Sys.argv
7 changes: 7 additions & 0 deletions src/scripts/scripts.ocp
Expand Up @@ -20,3 +20,10 @@ begin program "opam-installer"
]
requires = [ "opam-client" ]
end

begin program "opamlfind"
files = [
"opamlfind.ml"
]
requires = [ "unix" ]
end

0 comments on commit 0c739b0

Please sign in to comment.