Skip to content

Commit

Permalink
Merge pull request #1736 from OCamlPro/admin-scripts
Browse files Browse the repository at this point in the history
Fix and improve admin-scripts
  • Loading branch information
AltGr committed Sep 17, 2014
2 parents c3f7ab1 + 10cd16c commit 3527946
Show file tree
Hide file tree
Showing 4 changed files with 33 additions and 7 deletions.
7 changes: 6 additions & 1 deletion admin-scripts/add-build-deps.ml
Original file line number Diff line number Diff line change
Expand Up @@ -14,9 +14,14 @@ let addbuild (pkg, (flags, cstr) as atom) =
OpamFormula.Atom atom
;;

iter_packages ~opam:(fun _ opam ->
iter_packages ~opam:(fun _ opam0 ->
let open OpamFile.OPAM in
let opam = opam0 in
let opam = with_depends opam @@ OpamFormula.map addbuild @@ depends opam in
let opam = with_depopts opam @@ OpamFormula.map addbuild @@ depopts opam in
let opam = if opam <> opam0
then with_opam_version opam @@ OpamVersion.of_string "1.2"
else opam
in
opam)
()
9 changes: 6 additions & 3 deletions admin-scripts/add-github-dev.ml
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,7 @@ open Opam_admin_top;;
let github_re =
Re.compile (Re_perl.re "https?://([^/]*github.com/.*)/archive/.*");;

iter_packages_gen @@ fun nv ~opam ~descr ~url ~dot_install ->
iter_packages_gen @@ fun nv ~prefix:_ ~opam ~descr:_ ~url ~dot_install:_ ->
let opam =
if OpamFile.OPAM.dev_repo opam <> None then opam else
match url with
Expand All @@ -18,7 +18,10 @@ let opam =
| `http, (addr,None) when Re.execp github_re addr ->
let substrings = Re.exec github_re addr in
let git = Printf.sprintf "git://%s" (Re.get substrings 1) in
OpamFile.OPAM.with_dev_repo opam (Some (OpamTypes.Git (git,None)))
let opam =
OpamFile.OPAM.with_dev_repo opam (Some (OpamTypes.Git (git,None)))
in
OpamFile.OPAM.with_opam_version opam (OpamVersion.of_string "1.2")
| _ -> opam
in
opam, descr, url, dot_install
opam, `Keep, `Keep, `Keep
20 changes: 18 additions & 2 deletions admin-scripts/to_1_1.ml
Original file line number Diff line number Diff line change
Expand Up @@ -7,8 +7,18 @@
* remove the new fields: install, flags and dev-repo
* remove dependency flags ('build', 'test', 'doc')
* set file version
* replace inequality constraints with '> & <'
*)

let rewrite_constraint ~conj = (* Rewrites '!=' *)
OpamFormula.map OpamFormula.(function
| (`Neq,v) ->
prerr_endline "XX";
if conj then And (Atom (`Lt,v), Atom (`Gt,v))
else Or (Atom (`Lt,v), Atom (`Gt,v))
| atom -> Atom atom)
;;

let to_1_1 _ opam =
let module OF = OpamFile.OPAM in
if
Expand All @@ -22,11 +32,17 @@ let to_1_1 _ opam =
let opam = OF.with_dev_repo opam None in
let opam = OF.with_opam_version opam (OpamVersion.of_string "1.1") in
let remove_ext =
OpamFormula.map (fun (n, (_,formula)) ->
OpamFormula.Atom (n, ([], formula)))
OpamFormula.map (fun (n, (_,cstr)) ->
OpamFormula.Atom (n, ([], rewrite_constraint ~conj:false cstr)))
in
let opam = OF.with_depends opam (remove_ext (OF.depends opam)) in
let opam = OF.with_depopts opam (remove_ext (OF.depopts opam)) in
let opam =
OF.with_conflicts opam
(OpamFormula.map (fun (n, cstr) ->
OpamFormula.Atom (n, rewrite_constraint ~conj:true cstr))
(OF.conflicts opam))
in
opam
;;

Expand Down
4 changes: 3 additions & 1 deletion src/core/opamFile.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1298,7 +1298,9 @@ module X = struct
in
assoc_default OpamFormula.Empty s s_depopts @@ fun value ->
let f = OpamFormat.parse_opt_formula value in
if OpamVersion.compare opam_version (OpamVersion.of_string "1.2") >= 0 then
if not !OpamGlobals.skip_version_checks &&
OpamVersion.compare opam_version (OpamVersion.of_string "1.2") >= 0
then
OpamFormula.ors_to_list f
|> cleanup ~pos:(OpamFormat.value_pos value) []
|> List.rev
Expand Down

0 comments on commit 3527946

Please sign in to comment.