Skip to content

Commit

Permalink
GlobalState: externalise inferred from system description string
Browse files Browse the repository at this point in the history
  • Loading branch information
rjbou committed Mar 27, 2019
1 parent 4fff3d1 commit 551de1a
Show file tree
Hide file tree
Showing 2 changed files with 8 additions and 1 deletion.
6 changes: 5 additions & 1 deletion src/state/opamGlobalState.ml
Original file line number Diff line number Diff line change
Expand Up @@ -34,6 +34,8 @@ let load_config global_lock root =
OpamFormatUpgrade.as_necessary global_lock root config;
config

let inferred_from_system = "Inferred from system"

let load lock_kind =
let root = OpamStateConfig.(!r.root_dir) in
log "LOAD-GLOBAL-STATE @ %a" (slog OpamFilename.Dir.to_string) root;
Expand Down Expand Up @@ -64,7 +66,9 @@ let load lock_kind =
List.fold_left (fun acc (v,value) ->
OpamVariable.Map.add v
(lazy (Some (OpamStd.Option.default (S "unknown") (Lazy.force value))),
"Inferred from system")
(* Careful on changing it, it is used to determine user defined
variables on `config report`. See [OpamConfigCommand.help]. *)
inferred_from_system)
acc)
OpamVariable.Map.empty
(OpamSysPoll.variables)
Expand Down
3 changes: 3 additions & 0 deletions src/state/opamGlobalState.mli
Original file line number Diff line number Diff line change
Expand Up @@ -60,3 +60,6 @@ val write: rw global_state -> unit
registered if it is set and exists, and removing any non-existing switches.
Writes back to disk if possible (ie lock is available) *)
val fix_switch_list: 'a global_state -> 'a global_state

(** Description used for system inferred variables *)
val inferred_from_system: string

0 comments on commit 551de1a

Please sign in to comment.