Skip to content

Commit

Permalink
OpamFile: Make all writes atomic
Browse files Browse the repository at this point in the history
Partial revert of 64a569f
  • Loading branch information
kit-ty-kate committed Aug 13, 2024
1 parent 2ee2c1b commit 9ba1154
Show file tree
Hide file tree
Showing 8 changed files with 16 additions and 48 deletions.
1 change: 1 addition & 0 deletions master_changes.md
Original file line number Diff line number Diff line change
Expand Up @@ -75,6 +75,7 @@ users)
## Env

## Opamfile
* Make all writes atomic [#5489 @kit-ty-kate]

## External dependencies
* Always pass --no-version-check and --no-write-registry to Cygwin setup [#6046 @dra27]
Expand Down
2 changes: 1 addition & 1 deletion src/core/opamFilename.ml
Original file line number Diff line number Diff line change
Expand Up @@ -232,7 +232,7 @@ let with_open_out_bin_aux open_out_bin filename f =
OpamStd.Exn.finalise e @@ fun () ->
close_out oc; remove filename

let with_open_out_bin =
let with_open_out_bin [@deprecated] =
with_open_out_bin_aux (fun f -> (), open_out_bin f)

let with_open_out_bin_atomic filename f =
Expand Down
6 changes: 4 additions & 2 deletions src/core/opamFilename.mli
Original file line number Diff line number Diff line change
Expand Up @@ -147,9 +147,11 @@ val open_out_bin: t -> out_channel
If [f] raises an exception, then [filename] is deleted and then exception is
propagated. The out_channel does not have to be closed by [f]. *)
val with_open_out_bin: t -> (out_channel -> unit) -> unit
[@@deprecated "use with_open_out_bin_atomic instead"]

(** As {!with_open_out_bin} except that the file is written atomically. If [f]
raises an exception, then [filename] will be unaltered. *)
(** [with_open_out_bin_atomic filename f] opens [f] and passes the out_channel to [f].
If [f] raises an exception, then [filename] will be unaltered and then exception is
propagated. The out_channel does not have to be closed by [f]. *)
val with_open_out_bin_atomic: t -> (out_channel -> unit) -> unit

(** Removes everything in [filename] if existed. *)
Expand Down
37 changes: 2 additions & 35 deletions src/format/opamFile.ml
Original file line number Diff line number Diff line change
Expand Up @@ -76,7 +76,6 @@ end

module type IO_Arg = sig
val internal : string
val atomic : bool
type t
val empty : t
val of_channel : 'a typed_file -> in_channel -> t
Expand Down Expand Up @@ -110,15 +109,10 @@ module MakeIO (F : IO_Arg) = struct
let write f v =
let filename = OpamFilename.to_string f in
let chrono = OpamConsole.timer () in
let write =
if F.atomic then
OpamFilename.with_open_out_bin_atomic
else
OpamFilename.with_open_out_bin
in
let write = OpamFilename.with_open_out_bin_atomic in
write f (fun oc -> F.to_channel f oc v);
Stats.write_files := filename :: !Stats.write_files;
log "Wrote %s%s in %.3fs" filename (if F.atomic then " atomically" else "") (chrono ())
log "Wrote %s atomically in %.3fs" filename (chrono ())

let read_opt f =
let filename = OpamFilename.prettify f in
Expand Down Expand Up @@ -195,7 +189,6 @@ end
module DescrIO = struct

let internal = "descr"
let atomic = false
let format_version = OpamVersion.of_string "0"

type t = string * string
Expand Down Expand Up @@ -288,8 +281,6 @@ module LinesBase = struct

let internal = "lines"

let atomic = false

let find_escapes s len =
let rec aux acc i =
if i < 0 then acc else
Expand Down Expand Up @@ -379,7 +370,6 @@ end

module type LineFileArg = sig
val internal: string
val atomic: bool
type t
val empty: t
val pp: (string list list, t) Pp.t
Expand Down Expand Up @@ -416,7 +406,6 @@ end
module Aliases = LineFile(struct

let internal = "aliases"
let atomic = false

type t = string switch_map

Expand All @@ -435,7 +424,6 @@ module Aliases = LineFile(struct
module Repo_index (A : OpamStd.ABSTRACT) = LineFile(struct

let internal = "repo-index"
let atomic = false

type t = (repository_name * string option) A.Map.t

Expand All @@ -457,7 +445,6 @@ module Package_index = Repo_index(OpamPackage)
module PkgList = LineFile (struct

let internal = "package-version-list"
let atomic = false

type t = package_set

Expand Down Expand Up @@ -528,7 +515,6 @@ module Pinned_legacy = struct
include LineFile(struct

let internal = "pinned"
let atomic = false

type t = pin_option OpamPackage.Name.Map.t

Expand All @@ -553,7 +539,6 @@ external open_env_updates:
module Environment = struct include LineFile(struct

let internal = "environment"
let atomic = true

type t = (spf_resolved, euok_writeable) env_update list

Expand Down Expand Up @@ -729,7 +714,6 @@ end
module File_attributes = LineFile(struct

let internal = "file_attributes"
let atomic = false

type t = file_attribute_set

Expand All @@ -756,7 +740,6 @@ module File_attributes = LineFile(struct
module StateTable = struct

let internal = "export"
let atomic = false

module M = OpamPackage.Name.Map

Expand Down Expand Up @@ -1174,7 +1157,6 @@ end

module type SyntaxFileArg = sig
val internal: string
val atomic: bool
val format_version: OpamVersion.t
type t
val empty: t
Expand Down Expand Up @@ -1215,7 +1197,6 @@ module SyntaxFile(X: SyntaxFileArg) : IO_FILE with type t := X.t = struct
include MakeIO(struct
include X
include IO
let atomic = false
end)

end
Expand Down Expand Up @@ -1392,7 +1373,6 @@ end
module ConfigSyntax = struct

let internal = "config"
let atomic = false
let format_version = OpamVersion.of_string "2.1"
let file_format_version = OpamVersion.of_string "2.0"
let root_version = OpamVersion.of_string "2.2"
Expand Down Expand Up @@ -1711,7 +1691,6 @@ end

module InitConfigSyntax = struct
let internal = "init-config"
let atomic = false
let format_version = OpamVersion.of_string "2.0"

type t = {
Expand Down Expand Up @@ -1972,7 +1951,6 @@ end
module Repos_configSyntax = struct

let internal = "repos-config"
let atomic = false
let format_version = OpamVersion.of_string "2.0"
let file_format_version = OpamVersion.of_string "2.0"

Expand Down Expand Up @@ -2017,7 +1995,6 @@ end
module Switch_configSyntax = struct

let internal = "switch-config"
let atomic = false
let format_version = OpamVersion.of_string "2.1"
let file_format_version = OpamVersion.of_string "2.0"
let oldest_compatible_format_version = OpamVersion.of_string "2.0"
Expand Down Expand Up @@ -2134,7 +2111,6 @@ end
module SwitchSelectionsSyntax = struct

let internal = "switch-state"
let atomic = false
let format_version = OpamVersion.of_string "2.0"
let file_format_version = OpamVersion.of_string "2.0"

Expand Down Expand Up @@ -2205,7 +2181,6 @@ end
module Repo_config_legacySyntax = struct

let internal = "repo-file"
let atomic = false
let format_version = OpamVersion.of_string "1.2"

type t = {
Expand Down Expand Up @@ -2270,7 +2245,6 @@ end
module Dot_configSyntax = struct

let internal = ".config"
let atomic = false
let format_version = OpamVersion.of_string "2.0"

type t = {
Expand Down Expand Up @@ -2363,7 +2337,6 @@ end
module RepoSyntax = struct

let internal = "repo"
let atomic = false
let format_version = OpamVersion.of_string "2.0"

type t = {
Expand Down Expand Up @@ -2453,7 +2426,6 @@ end
module URLSyntax = struct

let internal = "url-file"
let atomic = false
let format_version = OpamVersion.of_string "1.2"

type t = {
Expand Down Expand Up @@ -2567,7 +2539,6 @@ end
module OPAMSyntax = struct

let internal = "opam"
let atomic = false
let format_version = OpamVersion.of_string "2.0"

type t = {
Expand Down Expand Up @@ -3709,7 +3680,6 @@ end
module Dot_installSyntax = struct

let internal = ".install"
let atomic = false
let format_version = OpamVersion.of_string "2.0"

type t = {
Expand Down Expand Up @@ -3877,7 +3847,6 @@ end

module ChangesSyntax = struct
let internal = "changes"
let atomic = false
let format_version = OpamVersion.of_string "2.0"

open OpamDirTrack
Expand Down Expand Up @@ -3943,7 +3912,6 @@ end
module SwitchExportSyntax = struct

let internal = "switch-export"
let atomic = false
let format_version = OpamVersion.of_string "2.1"

type t = {
Expand Down Expand Up @@ -4021,7 +3989,6 @@ end
module CompSyntax = struct

let internal = "comp"
let atomic = false
let format_version = OpamVersion.of_string "1.2"

type compiler = string
Expand Down
2 changes: 0 additions & 2 deletions src/format/opamFile.mli
Original file line number Diff line number Diff line change
Expand Up @@ -1162,7 +1162,6 @@ end

module type SyntaxFileArg = sig
val internal: string
val atomic: bool
val format_version: OpamVersion.t
type t
val empty: t
Expand All @@ -1173,7 +1172,6 @@ module SyntaxFile(X: SyntaxFileArg) : IO_FILE with type t := X.t

module type LineFileArg = sig
val internal: string
val atomic: bool
type t
val empty: t
val pp: (string list list, t) OpamPp.t
Expand Down
2 changes: 1 addition & 1 deletion tests/reftests/dot-install.test
Original file line number Diff line number Diff line change
Expand Up @@ -211,7 +211,7 @@ Not found: ${BASEDIR}/OPAM/inst/.opam-switch/install/dot.changes
- install lot-of-files ~dev
SYSTEM mkdir ${BASEDIR}/OPAM/inst/.opam-switch/build/lot-of-files.~dev
SYSTEM copy ${BASEDIR}/OPAM/repo/default/packages/lot-of-files/lot-of-files.~dev/files/lot-of-files.install.in -> ${BASEDIR}/OPAM/inst/.opam-switch/build/lot-of-files.~dev/lot-of-files.install.in
FILE(.config) Wrote ${BASEDIR}/OPAM/inst/.opam-switch/config/lot-of-files.config in 0.000s
FILE(.config) Wrote ${BASEDIR}/OPAM/inst/.opam-switch/config/lot-of-files.config atomically in 0.000s
SYSTEM install ${BASEDIR}/OPAM/inst/.opam-switch/build/lot-of-files.~dev/fichier -> ${BASEDIR}/OPAM/inst/bin/fichier (755)
SYSTEM mkdir ${BASEDIR}/OPAM/inst/lib/lot-of-files
SYSTEM install ${BASEDIR}/OPAM/inst/.opam-switch/build/lot-of-files.~dev/a-file -> ${BASEDIR}/OPAM/inst/lib/lot-of-files/a-file (644)
Expand Down
8 changes: 4 additions & 4 deletions tests/reftests/opamroot-versions.test
Original file line number Diff line number Diff line change
Expand Up @@ -1244,7 +1244,7 @@ Update done, please now retry your command.
# Return code 10 #
### # ro global state, ro repo state, rw switch state
### opam install i-am-package
FILE(switch-config) Wrote ${BASEDIR}/_opam/.opam-switch/switch-config in 0.000s
FILE(switch-config) Wrote ${BASEDIR}/_opam/.opam-switch/switch-config atomically in 0.000s
GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM
RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM
RSTATE Cache found
Expand Down Expand Up @@ -1297,7 +1297,7 @@ roots: ["i-am-package.2" "i-am-sys-compiler.2"]
### ocaml generate.ml $OPAMROOTVERSION orphaned 2.1~alpha
### # ro global state, ro repo state, ro switch state
### opam list
FILE(switch-config) Wrote ${BASEDIR}/_opam/.opam-switch/switch-config in 0.000s
FILE(switch-config) Wrote ${BASEDIR}/_opam/.opam-switch/switch-config atomically in 0.000s
GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM
RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM
RSTATE No cache found
Expand Down Expand Up @@ -1616,7 +1616,7 @@ Update done, please now retry your command.
# Return code 10 #
### # ro global state, ro repo state, rw switch state
### opam install i-am-package
FILE(switch-config) Wrote ${BASEDIR}/_opam/.opam-switch/switch-config in 0.000s
FILE(switch-config) Wrote ${BASEDIR}/_opam/.opam-switch/switch-config atomically in 0.000s
GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM
RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM
RSTATE Cache found
Expand Down Expand Up @@ -1669,7 +1669,7 @@ roots: ["i-am-package.2" "i-am-sys-compiler.2"]
### ocaml generate.ml $OPAMROOTVERSION orphaned 2.1~alpha2
### # ro global state, ro repo state, ro switch state
### opam list
FILE(switch-config) Wrote ${BASEDIR}/_opam/.opam-switch/switch-config in 0.000s
FILE(switch-config) Wrote ${BASEDIR}/_opam/.opam-switch/switch-config atomically in 0.000s
GSTATE LOAD-GLOBAL-STATE @ ${BASEDIR}/OPAM
RSTATE LOAD-REPOSITORY-STATE @ ${BASEDIR}/OPAM
RSTATE No cache found
Expand Down
6 changes: 3 additions & 3 deletions tests/reftests/repository.test
Original file line number Diff line number Diff line change
Expand Up @@ -122,7 +122,7 @@ FILE(opam) Read ${BASEDIR}/OPAM/repo/tarred/packages/foo/fo
FILE(opam) Read ${BASEDIR}/OPAM/repo/tarred/packages/foo/foo.2/opam in 0.000s
FILE(opam) Read ${BASEDIR}/OPAM/repo/tarred/packages/foo/foo.1/opam in 0.000s
FILE(opam) Read ${BASEDIR}/OPAM/repo/tarred/packages/foo/foo.5/opam in 0.000s
FILE(repos-config) Wrote ${BASEDIR}/OPAM/repo/repos-config in 0.000s
FILE(repos-config) Wrote ${BASEDIR}/OPAM/repo/repos-config atomically in 0.000s
CACHE(repository) Writing the repository cache to ${BASEDIR}/OPAM/repo/state-hash.cache ...
CACHE(repository) ${BASEDIR}/OPAM/repo/state-hash.cache written in 0.000s
Now run 'opam upgrade' to apply any package updates.
Expand Down Expand Up @@ -203,7 +203,7 @@ FILE(repo) Read ${BASEDIR}/OPAM/repo/repo2/repo in 0.000s
FILE(opam) Read ${BASEDIR}/OPAM/repo/repo2/packages/bar/bar.2/opam in 0.000s
FILE(opam) Read ${BASEDIR}/OPAM/repo/repo2/packages/bar/bar.1/opam in 0.000s
[tarred] no changes from file://${BASEDIR}/REPO
FILE(repos-config) Wrote ${BASEDIR}/OPAM/repo/repos-config in 0.000s
FILE(repos-config) Wrote ${BASEDIR}/OPAM/repo/repos-config atomically in 0.000s
CACHE(repository) Writing the repository cache to ${BASEDIR}/OPAM/repo/state-hash.cache ...
CACHE(repository) ${BASEDIR}/OPAM/repo/state-hash.cache written in 0.000s
Now run 'opam upgrade' to apply any package updates.
Expand Down Expand Up @@ -247,7 +247,7 @@ FILE(opam) Read ${BASEDIR}/OPAM/repo/tarred/packages/foo/fo
FILE(opam) Read ${BASEDIR}/OPAM/repo/tarred/packages/foo/foo.2/opam in 0.000s
FILE(opam) Read ${BASEDIR}/OPAM/repo/tarred/packages/foo/foo.1/opam in 0.000s
FILE(opam) Read ${BASEDIR}/OPAM/repo/tarred/packages/foo/foo.5/opam in 0.000s
FILE(repos-config) Wrote ${BASEDIR}/OPAM/repo/repos-config in 0.000s
FILE(repos-config) Wrote ${BASEDIR}/OPAM/repo/repos-config atomically in 0.000s
CACHE(repository) Writing the repository cache to ${BASEDIR}/OPAM/repo/state-hash.cache ...
CACHE(repository) ${BASEDIR}/OPAM/repo/state-hash.cache written in 0.000s
Now run 'opam upgrade' to apply any package updates.
Expand Down

0 comments on commit 9ba1154

Please sign in to comment.