Skip to content

Commit 42a0d4c

Browse files
committed
[API] Split the deprecated url and descr files implementations to their own submodules
1 parent 22b3869 commit 42a0d4c

File tree

12 files changed

+174
-125
lines changed

12 files changed

+174
-125
lines changed

src/client/opamAdminRepoUpgrade.ml

Lines changed: 9 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -219,7 +219,7 @@ let do_upgrade repo_root =
219219
let descr_file =
220220
OpamFilename.(opt_file (add_extension (chop_extension comp_file) "descr"))
221221
in
222-
let descr = descr_file >>| fun f -> OpamFile.Descr.read (OpamFile.make f) in
222+
let descr = descr_file >>| fun f -> OpamFile.Descr_legacy.read (OpamFile.make f) in
223223
let nv, ocaml_version, variant =
224224
match OpamStd.String.cut_at c '+' with
225225
| None ->
@@ -319,9 +319,8 @@ let do_upgrade repo_root =
319319
)) |>
320320
O.with_maintainer [ "[email protected]" ] |>
321321
O.with_flags [Pkgflag_Compiler] |>
322-
O.with_descr
323-
(OpamFile.Descr.create
324-
"The OCaml compiler (system version, from outside of opam)") |>
322+
O.with_synopsis
323+
"The OCaml compiler (system version, from outside of opam)" |>
325324
O.with_available
326325
(FOp (FIdent ([],OpamVariable.of_string "sys-ocaml-version",None),
327326
`Eq,
@@ -381,12 +380,12 @@ let do_upgrade repo_root =
381380
(* leave the Compiler flag to the implementations (since the user
382381
needs to select one)
383382
O.with_flags [Pkgflag_Compiler] |> *)
384-
O.with_descr
385-
(OpamFile.Descr.create
386-
"The OCaml compiler (virtual package)\n\
387-
This package requires a matching implementation of OCaml,\n\
388-
and polls it to initialise specific variables like \
389-
`ocaml:native-dynlink`") |>
383+
O.with_synopsis
384+
"The OCaml compiler (virtual package)" |>
385+
O.with_description
386+
"This package requires a matching implementation of OCaml,\n\
387+
and polls it to initialise specific variables like \
388+
`ocaml:native-dynlink`" |>
390389
O.with_depends
391390
(OpamFormula.ors [
392391
Atom (

src/client/opamListCommand.ml

Lines changed: 3 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -564,9 +564,7 @@ let detail_printer ?prettify ?normalise ?(sort=false) st nv =
564564
(OpamPackage.name_to_string nv % (`bold :: root_sty)) ^
565565
("." ^ OpamPackage.version_to_string nv) % root_sty
566566
| Synopsis ->
567-
(get_opam st nv |>
568-
OpamFile.OPAM.descr >>| OpamFile.Descr.synopsis)
569-
+! ""
567+
(get_opam st nv |> OpamFile.OPAM.synopsis) +! ""
570568
| Synopsis_or_target ->
571569
(match OpamPinned.package_opt st nv.name with
572570
| Some nv ->
@@ -584,14 +582,9 @@ let detail_printer ?prettify ?normalise ?(sort=false) st nv =
584582
(fun u -> OpamUrl.to_string u % [`underline])
585583
(OpamFile.OPAM.get_url opam))
586584
| None ->
587-
(get_opam st nv |>
588-
OpamFile.OPAM.descr >>| OpamFile.Descr.synopsis)
589-
+! "")
585+
(get_opam st nv |> OpamFile.OPAM.synopsis) +! "")
590586
| Description ->
591-
(get_opam st nv |>
592-
OpamFile.OPAM.descr >>|
593-
OpamFile.Descr.body)
594-
+! ""
587+
(get_opam st nv |> OpamFile.OPAM.description) +! ""
595588
| Raw_field f | Field f ->
596589
(try
597590
let open OpamStd.Option.Op in

src/format/opamFile.ml

Lines changed: 119 additions & 48 deletions
Original file line numberDiff line numberDiff line change
@@ -170,7 +170,7 @@ end
170170
content. Formerly, (<repo>/packages/.../descr,
171171
<repo>/compilers/.../<v>.descr) *)
172172

173-
module DescrIO = struct
173+
module Descr_legacyIO = struct
174174

175175
let internal = "descr"
176176
let format_version = OpamVersion.of_string "0"
@@ -217,9 +217,9 @@ module DescrIO = struct
217217
let to_string _ = full
218218

219219
end
220-
module Descr = struct
221-
include DescrIO
222-
include MakeIO(DescrIO)
220+
module Descr_legacy = struct
221+
include Descr_legacyIO
222+
include MakeIO(Descr_legacyIO)
223223
end
224224

225225
(* module Comp_descr = Descr *)
@@ -2412,10 +2412,79 @@ end
24122412
(** Package url field in opam file. Formerly, file
24132413
(<repo>/packages/.../url) *)
24142414

2415-
module URLSyntax = struct
2415+
module URL_legacySyntax = struct
24162416

2417-
let internal = "url-file"
2418-
let format_version = OpamVersion.of_string "1.2"
2417+
let internal = "url"
2418+
let format_version = OpamVersion.of_string "0"
2419+
2420+
type t = {
2421+
url : url;
2422+
mirrors : url list;
2423+
checksum: OpamHash.t list;
2424+
errors : (string * Pp.bad_format) list;
2425+
}
2426+
2427+
let empty = {
2428+
url = OpamUrl.empty;
2429+
mirrors = [];
2430+
checksum= [];
2431+
errors = [];
2432+
}
2433+
2434+
let url t = t.url
2435+
let mirrors t = t.mirrors
2436+
let checksum t = t.checksum
2437+
2438+
let with_url url t = { t with url }
2439+
let with_mirrors mirrors t = { t with mirrors }
2440+
let with_checksum checksum t = { t with checksum = checksum }
2441+
2442+
let fields =
2443+
let with_url url t =
2444+
if t.url <> OpamUrl.empty then Pp.bad_format "Too many URLS"
2445+
else with_url url t
2446+
in
2447+
[
2448+
"src", Pp.ppacc with_url url
2449+
Pp.V.url;
2450+
"archive", Pp.ppacc_opt with_url OpamStd.Option.none
2451+
(Pp.V.url_with_backend `http);
2452+
"http", Pp.ppacc_opt with_url OpamStd.Option.none
2453+
(Pp.V.url_with_backend `http);
2454+
"git", Pp.ppacc_opt with_url OpamStd.Option.none
2455+
(Pp.V.url_with_backend `git);
2456+
"darcs", Pp.ppacc_opt with_url OpamStd.Option.none
2457+
(Pp.V.url_with_backend `darcs);
2458+
"hg", Pp.ppacc_opt with_url OpamStd.Option.none
2459+
(Pp.V.url_with_backend `hg);
2460+
"local", Pp.ppacc_opt with_url OpamStd.Option.none
2461+
(Pp.V.url_with_backend `rsync);
2462+
"checksum", Pp.ppacc with_checksum checksum
2463+
(Pp.V.map_list ~depth:1
2464+
(Pp.V.string -| Pp.of_module "checksum" (module OpamHash)));
2465+
"mirrors", Pp.ppacc with_mirrors mirrors
2466+
(Pp.V.map_list ~depth:1 Pp.V.url);
2467+
]
2468+
2469+
let pp_contents =
2470+
let name = internal in
2471+
Pp.I.fields ~name ~empty fields -|
2472+
Pp.I.on_errors ~name (fun t e -> {t with errors = e::t.errors}) -|
2473+
Pp.pp ~name
2474+
(fun ~pos t ->
2475+
if t.url = OpamUrl.empty then OpamPp.bad_format ~pos "missing URL"
2476+
else t)
2477+
(fun x -> x)
2478+
2479+
let pp = Pp.I.map_file pp_contents
2480+
2481+
end
2482+
module URL_legacy = struct
2483+
include URL_legacySyntax
2484+
include SyntaxFile(URL_legacySyntax)
2485+
end
2486+
2487+
module URL = struct
24192488

24202489
type t = {
24212490
url : url;
@@ -2440,6 +2509,9 @@ module URLSyntax = struct
24402509
subpath = None;
24412510
}
24422511

2512+
let of_legacy {URL_legacy.url; mirrors; checksum; errors} =
2513+
{(create ~mirrors ~checksum url) with errors}
2514+
24432515
let url t = t.url
24442516
let mirrors t = t.mirrors
24452517
let checksum t = t.checksum
@@ -2485,7 +2557,7 @@ module URLSyntax = struct
24852557
]
24862558

24872559
let pp_contents =
2488-
let name = internal in
2560+
let name = "url-field" in
24892561
Pp.I.fields ~name ~empty fields -|
24902562
Pp.I.on_errors ~name (fun t e -> {t with errors = e::t.errors}) -|
24912563
Pp.pp ~name
@@ -2513,16 +2585,9 @@ module URLSyntax = struct
25132585
swhid = None;
25142586
mirrors = OpamSWHID.to_url swhid :: t.mirrors })
25152587

2516-
let pp = Pp.I.map_file pp_contents
2517-
2518-
end
2519-
module URL = struct
2520-
include URLSyntax
2521-
include SyntaxFile(URLSyntax)
25222588
end
25232589

25242590

2525-
25262591
(** (3) Opam package format *)
25272592

25282593
module OPAMSyntax = struct
@@ -2582,7 +2647,8 @@ module OPAMSyntax = struct
25822647

25832648
(* Extra sections *)
25842649
url : URL.t option;
2585-
descr : Descr.t option;
2650+
synopsis : string option;
2651+
description: string option;
25862652

25872653
(* Extra data, not actually file fields *)
25882654

@@ -2650,7 +2716,8 @@ module OPAMSyntax = struct
26502716

26512717
extensions = OpamStd.String.Map.empty;
26522718
url = None;
2653-
descr = None;
2719+
synopsis = None;
2720+
description = None;
26542721

26552722
metadata_dir = None;
26562723
extra_files = None;
@@ -2752,11 +2819,8 @@ module OPAMSyntax = struct
27522819
with Not_found -> None
27532820

27542821
let url t = t.url
2755-
let descr t = t.descr
2756-
let synopsis t = Option.map Descr.synopsis t.descr
2757-
let descr_body t = match t.descr with
2758-
| None | Some (_, "") -> None
2759-
| Some (_, text) -> Some text
2822+
let description t = t.description
2823+
let synopsis t = t.synopsis
27602824
let get_url t = match url t with Some u -> Some (URL.url u) | None -> None
27612825

27622826
let format_errors t = t.format_errors
@@ -2846,15 +2910,17 @@ module OPAMSyntax = struct
28462910
in
28472911
{ t with url;
28482912
format_errors = format_errors @ t.format_errors }
2849-
2850-
let with_descr descr t = { t with descr = Some descr }
2851-
let with_descr_opt descr t = { t with descr }
2852-
let with_synopsis synopsis t =
2853-
{ t with descr =
2854-
Some (synopsis, OpamStd.Option.default "" (descr_body t)) }
2855-
let with_descr_body text t =
2856-
{ t with descr =
2857-
Some (OpamStd.Option.default "" (synopsis t), text) }
2913+
let with_url_legacy url t =
2914+
with_url (URL.of_legacy url) t
2915+
2916+
let with_description description t = { t with description = Some description }
2917+
let with_description_opt description t = { t with description }
2918+
let with_synopsis synopsis t = { t with synopsis = Some synopsis }
2919+
let with_descr_legacy (synopsis, description) t =
2920+
let t = { t with synopsis = Some synopsis } in
2921+
if description = ""
2922+
then t
2923+
else { t with description = Some description }
28582924

28592925
let with_metadata_dir metadata_dir t = { t with metadata_dir }
28602926
let with_extra_files extra_files t = { t with extra_files = Some extra_files }
@@ -2974,7 +3040,7 @@ module OPAMSyntax = struct
29743040

29753041
"synopsis", no_cleanup Pp.ppacc_opt with_synopsis synopsis
29763042
Pp.V.string_tr;
2977-
"description", no_cleanup Pp.ppacc_opt with_descr_body descr_body
3043+
"description", no_cleanup Pp.ppacc_opt with_description description
29783044
Pp.V.string_tr;
29793045

29803046
"maintainer", no_cleanup Pp.ppacc with_maintainer maintainer
@@ -3100,9 +3166,9 @@ module OPAMSyntax = struct
31003166
Pp.V.constraints Pp.V.compiler_version);
31013167
"os", no_cleanup Pp.ppacc_opt with_os OpamStd.Option.none
31023168
Pp.V.os_constraint;
3103-
"descr", no_cleanup Pp.ppacc_opt with_descr OpamStd.Option.none
3169+
"descr", no_cleanup Pp.ppacc_opt with_descr_legacy OpamStd.Option.none
31043170
(Pp.V.string_tr -|
3105-
Pp.of_pair "descr" Descr.(of_string (), to_string ()));
3171+
Pp.of_pair "descr" Descr_legacy.(of_string (), to_string ()));
31063172
"extra-sources", no_cleanup Pp.ppacc_opt
31073173
with_extra_sources OpamStd.Option.none
31083174
(Pp.V.map_list ~depth:2 @@
@@ -3534,7 +3600,8 @@ module OPAM = struct
35343600
t.extensions;
35353601

35363602
url = Option.map effective_url t.url;
3537-
descr = empty.descr;
3603+
synopsis = empty.synopsis;
3604+
description = empty.description;
35383605

35393606
metadata_dir = empty.metadata_dir;
35403607
extra_files = OpamStd.Option.Op.(t.extra_files ++ Some []);
@@ -4188,19 +4255,23 @@ module CompSyntax = struct
41884255
comp.patches
41894256
in
41904257
let pkg = OPAM.create package in
4191-
{ pkg with
4192-
OPAM.
4193-
depends;
4194-
build;
4195-
install;
4196-
maintainer = [ "[email protected]" ];
4197-
extra_sources;
4198-
patches;
4199-
env = comp.env;
4200-
flags = [Pkgflag_Compiler];
4201-
url;
4202-
descr = descr_opt;
4203-
}
4258+
let pkg =
4259+
{ pkg with
4260+
OPAM.
4261+
depends;
4262+
build;
4263+
install;
4264+
maintainer = [ "[email protected]" ];
4265+
extra_sources;
4266+
patches;
4267+
env = comp.env;
4268+
flags = [Pkgflag_Compiler];
4269+
url;
4270+
}
4271+
in
4272+
match descr_opt with
4273+
| None -> pkg
4274+
| Some descr -> OPAM.with_descr_legacy descr pkg
42044275

42054276
end
42064277
module Comp = struct

0 commit comments

Comments
 (0)