Skip to content

Commit

Permalink
remove the unused parts of OpamFile.Descr
Browse files Browse the repository at this point in the history
  • Loading branch information
kit-ty-kate committed Oct 21, 2024
1 parent adb134e commit 9805cd4
Show file tree
Hide file tree
Showing 4 changed files with 13 additions and 37 deletions.
4 changes: 3 additions & 1 deletion src/client/opamAdminRepoUpgrade.ml
Original file line number Diff line number Diff line change
Expand Up @@ -217,7 +217,9 @@ let do_upgrade repo_root =
let descr_file =
OpamFilename.(opt_file (add_extension (chop_extension comp_file) "descr"))
in
let descr = descr_file >>| fun f -> OpamFile.Descr.read (OpamFile.make f) in
let descr =
descr_file >>| fun f -> OpamFile.Descr.create (OpamFilename.read f)
in
let nv, ocaml_version, variant =
match OpamStd.String.cut_at c '+' with
| None ->
Expand Down
33 changes: 2 additions & 31 deletions src/format/opamFile.ml
Original file line number Diff line number Diff line change
Expand Up @@ -186,10 +186,7 @@ end
content. Formerly, (<repo>/packages/.../descr,
<repo>/compilers/.../<v>.descr) *)

module DescrIO = struct

let internal = "descr"
let format_version = OpamVersion.of_string "0"
module Descr = struct

type t = string * string

Expand All @@ -203,39 +200,13 @@ module DescrIO = struct
| "" -> x ^ "\n"
| y -> String.concat "" [x; "\n\n"; y; "\n"]

let of_channel _ ic =
let x =
try OpamStd.String.strip (input_line ic)
with End_of_file | Sys_error _ -> "" in
let y =
try OpamStd.String.strip (OpamSystem.string_of_channel ic)
with End_of_file | Sys_error _ -> ""
in
x, y

let to_channel _ oc (x,y) =
output_string oc x;
output_char oc '\n';
if y <> "" then
(output_char oc '\n';
output_string oc y;
output_char oc '\n')

let create str =
let head, tail =
match OpamStd.String.cut_at str '\n' with
| None -> str, ""
| Some (h,t) -> h, t in
OpamStd.String.strip head, OpamStd.String.strip tail

let of_string _ = create

let to_string _ = full

end
module Descr = struct
include DescrIO
include MakeIO(DescrIO)
end

(* module Comp_descr = Descr *)
Expand Down Expand Up @@ -3182,7 +3153,7 @@ module OPAMSyntax = struct
Pp.V.os_constraint;
"descr", no_cleanup Pp.ppacc_opt with_descr OpamStd.Option.none
(Pp.V.string_tr -|
Pp.of_pair "descr" Descr.(of_string (), to_string ()));
Pp.of_pair "descr" Descr.(create, full));
"extra-sources", no_cleanup Pp.ppacc_opt
with_extra_sources OpamStd.Option.none
(Pp.V.map_list ~depth:2 @@
Expand Down
7 changes: 3 additions & 4 deletions src/format/opamFile.mli
Original file line number Diff line number Diff line change
Expand Up @@ -298,12 +298,11 @@ end
(** Package descriptions: [$opam/descr/] *)
module Descr: sig

include IO_FILE
type t

val create: string -> t
val empty : t

(** Create an abstract description file from a string *)
val of_string: t typed_file -> string -> t
val create: string -> t

(** Return the first line *)
val synopsis: t -> string
Expand Down
6 changes: 5 additions & 1 deletion src/state/opamFormatUpgrade.ml
Original file line number Diff line number Diff line change
Expand Up @@ -563,7 +563,11 @@ let from_1_3_dev2_to_1_3_dev5 ~on_the_fly:_ root conf =
OpamStd.Option.default
(OpamFile.Descr.create
"Switch relying on a system-wide installation of OCaml")
(OpamFile.Descr.read_opt descr_f)
(if OpamFile.exists descr_f then
Some (OpamFile.Descr.create
(OpamSystem.read (OpamFile.to_string descr_f)))
else
None)
in
let comp_opam =
OpamFile.Comp.to_package comp (Some descr)
Expand Down

0 comments on commit 9805cd4

Please sign in to comment.