Skip to content

Commit

Permalink
OpamPath: remove url & descr
Browse files Browse the repository at this point in the history
  • Loading branch information
hannesm committed Oct 21, 2024
1 parent 612ff8c commit b43c23e
Show file tree
Hide file tree
Showing 5 changed files with 1 addition and 58 deletions.
6 changes: 0 additions & 6 deletions src/client/opamPinCommand.ml
Original file line number Diff line number Diff line change
Expand Up @@ -259,12 +259,6 @@ let edit st ?version name =
| Some o when OpamFile.OPAM.equal opam o ->
(OpamConsole.msg "Package metadata unchanged.\n"; st)
| _ ->
(* Remove obsolete auxiliary files, in case *)
OpamFilename.remove
(OpamFile.filename (path OpamPath.Switch.Overlay.url));
OpamFilename.remove
(OpamFile.filename (path OpamPath.Switch.Overlay.descr));

let opam_extra =
OpamStd.Option.default [] @@ OpamFile.OPAM.extra_files opam
in
Expand Down
4 changes: 0 additions & 4 deletions src/format/opamPath.ml
Original file line number Diff line number Diff line change
Expand Up @@ -270,10 +270,6 @@ module Switch = struct

let tmp_opam t a n = package t a n /- "opam_"

let url t a n = package t a n /- "url"

let descr t a n = package t a n /- "descr"

let files t a n = package t a n / "files"

end
Expand Down
7 changes: 0 additions & 7 deletions src/format/opamPath.mli
Original file line number Diff line number Diff line change
Expand Up @@ -362,13 +362,6 @@ module Switch: sig
$meta/overlay/$name.$version/opam_} *)
val tmp_opam: t -> switch -> name -> OpamFile.OPAM.t OpamFile.t

(** URL overlay: {i
$meta/overlay/$name.$version/url} *)
val url: t -> switch -> name -> OpamFile.URL.t OpamFile.t

(** Descr orverlay *)
val descr: t -> switch -> name -> OpamFile.Descr.t OpamFile.t

(** Files overlay *)
val files: t -> switch -> name -> dirname
end
Expand Down
35 changes: 0 additions & 35 deletions src/state/opamFileTools.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1297,44 +1297,9 @@ let add_aux_files ?dir ?(files_subdir_hashes=false) opam =
match dir with
| None -> opam
| Some dir ->
let (url_file: OpamFile.URL.t OpamFile.t) =
OpamFile.make (dir // "url")
in
let (descr_file: OpamFile.Descr.t OpamFile.t) =
OpamFile.make (dir // "descr")
in
let files_dir =
OpamFilename.Op.(dir / "files")
in
let opam =
match OpamFile.OPAM.url opam, try_read OpamFile.URL.read_opt url_file with
| None, (Some url, None) -> OpamFile.OPAM.with_url url opam
| Some opam_url, (Some url, errs) ->
if url = opam_url && errs = None then
log "Duplicate definition of url in '%s' and opam file"
(OpamFile.to_string url_file)
else
OpamConsole.warning
"File '%s' ignored (conflicting url already specified in the \
'opam' file)"
(OpamFile.to_string url_file);
opam
| _, (_, Some err) ->
OpamFile.OPAM.with_format_errors (err :: opam.format_errors) opam
| _, (None, None) -> opam
in
let opam =
match OpamFile.OPAM.descr opam,
try_read OpamFile.Descr.read_opt descr_file with
| None, (Some descr, None) -> OpamFile.OPAM.with_descr descr opam
| Some _, (Some _, _) ->
log "Duplicate descr in '%s' and opam file"
(OpamFile.to_string descr_file);
opam
| _, (_, Some err) ->
OpamFile.OPAM.with_format_errors (err :: opam.format_errors) opam
| _, (None, None) -> opam
in
let opam =
let extra_files =
OpamFilename.opt_dir files_dir >>| fun dir ->
Expand Down
7 changes: 1 addition & 6 deletions src/state/opamUpdate.ml
Original file line number Diff line number Diff line change
Expand Up @@ -331,12 +331,7 @@ let pinned_package st ?version ?(autolock=false) ?(working_dir=false) name =
let save_overlay opam =
OpamFilename.mkdir overlay_dir;
let opam_file = OpamPath.Switch.Overlay.opam root st.switch name in
List.iter OpamFilename.remove
OpamPath.Switch.Overlay.([
OpamFile.filename opam_file;
OpamFile.filename (url root st.switch name);
OpamFile.filename (descr root st.switch name);
]);
OpamFilename.remove (OpamFile.filename opam_file);
let files_dir = OpamPath.Switch.Overlay.files root st.switch name in
OpamFilename.rmdir files_dir;
let opam =
Expand Down

0 comments on commit b43c23e

Please sign in to comment.