From eb4c09670786ed8da4c297c19f3a11744a0a0f4b Mon Sep 17 00:00:00 2001 From: teague hansen Date: Mon, 19 Aug 2024 12:54:07 -0400 Subject: [PATCH 01/17] initial support for authors default from config Signed-off-by: teague hansen --- bin/common.ml | 1 + bin/dune_init.ml | 13 +++++++++---- bin/dune_init.mli | 3 ++- bin/init.ml | 4 ++-- src/dune_config_file/dune_config_file.ml | 21 +++++++++++++++++++++ src/dune_config_file/dune_config_file.mli | 7 +++++++ src/dune_lang/package_info.ml | 4 ++-- src/dune_lang/package_info.mli | 2 +- 8 files changed, 45 insertions(+), 10 deletions(-) diff --git a/bin/common.ml b/bin/common.ml index 49811f2977a..566a20f73e0 100644 --- a/bin/common.ml +++ b/bin/common.ml @@ -488,6 +488,7 @@ let shared_with_config_file = ; cache_storage_mode ; action_stdout_on_success ; action_stderr_on_success + ; default_authors = None ; experimental = None } ;; diff --git a/bin/dune_init.ml b/bin/dune_init.ml index 59e660d140d..fa4f1b3872a 100644 --- a/bin/dune_init.ml +++ b/bin/dune_init.ml @@ -172,10 +172,14 @@ module Init_context = struct type t = { dir : Path.t ; project : Dune_project.t + ; defaults : Dune_config_file.Dune_config.t } - let make path = + let make path config = let open Memo.O in + + let _ = config in + let+ project = (* CR-rgrinberg: why not get the project from the source tree? *) Dune_project.load @@ -196,7 +200,7 @@ module Init_context = struct | Some p -> Path.of_string p in File.create_dir dir; - { dir; project } + { dir; project; defaults=config } ;; end @@ -373,7 +377,7 @@ module Component = struct let test common (() : Options.Test.t) = make "test" common [] (* A list of CSTs for dune-project file content *) - let dune_project ~opam_file_gen dir (common : Options.Common.t) = + let dune_project ~opam_file_gen ~defaults dir (common : Options.Common.t) = let cst = let package = Package.create @@ -400,7 +404,7 @@ module Component = struct ] in let packages = Package.Name.Map.singleton (Package.name package) package in - let info = Package_info.example in + let info = Package_info.example defaults in Dune_project.anonymous ~dir info packages |> Dune_project.set_generate_opam_files opam_file_gen |> Dune_project.encode @@ -476,6 +480,7 @@ module Component = struct let content = Stanza_cst.dune_project ~opam_file_gen + ~defaults:context.defaults.default_authors Path.(as_in_source_tree_exn context.dir) common in diff --git a/bin/dune_init.mli b/bin/dune_init.mli index 3c4dc97cec8..15339bd0ac4 100644 --- a/bin/dune_init.mli +++ b/bin/dune_init.mli @@ -7,9 +7,10 @@ module Init_context : sig type t = { dir : Path.t ; project : Dune_project.t + ; defaults : Dune_config_file.Dune_config.t } - val make : string option -> t Memo.t + val make : string option -> Dune_config_file.Dune_config.t -> t Memo.t end module Public_name : sig diff --git a/bin/init.ml b/bin/init.ml index 0c4493085a9..416eefb3158 100644 --- a/bin/init.ml +++ b/bin/init.ml @@ -74,7 +74,7 @@ let context_cwd : Init_context.t Term.t = and+ path = path in let builder = Common.Builder.set_default_root_is_cwd builder true in let common, config = Common.init builder in - Scheduler.go ~common ~config (fun () -> Memo.run (Init_context.make path)) + Scheduler.go ~common ~config (fun () -> Memo.run (Init_context.make path config)) ;; module Public_name = struct @@ -228,7 +228,7 @@ let project = let builder = Builder.set_root common_builder root in let (_ : Fpath.mkdir_p_result) = Fpath.mkdir_p root in let common, config = Common.init builder in - Scheduler.go ~common ~config (fun () -> Memo.run init_context) + Scheduler.go ~common ~config (fun () -> Memo.run @@ init_context config) in Component.init (Project { context; common; options = { template; inline_tests; pkg } }); diff --git a/src/dune_config_file/dune_config_file.ml b/src/dune_config_file/dune_config_file.ml index 1bf91c61025..3db9c5d608d 100644 --- a/src/dune_config_file/dune_config_file.ml +++ b/src/dune_config_file/dune_config_file.ml @@ -16,6 +16,17 @@ module Dune_config = struct simplicity *) let syntax = Stanza.syntax + module Default_authors = struct + type t = string list + + let to_dyn = function + | [] -> Dyn.Variant ("Not-Provided", []) + | lst -> Dyn.Set (List.map ~f:(fun s -> Dyn.String s) lst) + ;; + + let decode = repeat1 string + end + module Terminal_persistence = struct type t = | Preserve @@ -136,6 +147,7 @@ module Dune_config = struct ; cache_storage_mode : Cache.Storage_mode.t field ; action_stdout_on_success : Action_output_on_success.t field ; action_stderr_on_success : Action_output_on_success.t field + ; default_authors : Default_authors.t field ; experimental : (string * (Loc.t * string)) list field } end @@ -163,6 +175,7 @@ module Dune_config = struct field a.action_stdout_on_success b.action_stdout_on_success ; action_stderr_on_success = field a.action_stderr_on_success b.action_stderr_on_success + ; default_authors = field a.default_authors b.default_authors ; experimental = field a.experimental b.experimental } ;; @@ -186,6 +199,7 @@ module Dune_config = struct ; cache_storage_mode ; action_stdout_on_success ; action_stderr_on_success + ; default_authors ; experimental } = @@ -205,6 +219,8 @@ module Dune_config = struct , field Action_output_on_success.to_dyn action_stdout_on_success ) ; ( "action_stderr_on_success" , field Action_output_on_success.to_dyn action_stderr_on_success ) + ; ( "default_authors" + , field Default_authors.to_dyn default_authors ) ; ( "experimental" , field Dyn.(list (pair string (fun (_, v) -> string v))) experimental ) ] @@ -228,6 +244,7 @@ module Dune_config = struct ; cache_storage_mode = None ; action_stdout_on_success = None ; action_stderr_on_success = None + ; default_authors = None ; experimental = None } ;; @@ -294,6 +311,7 @@ module Dune_config = struct ; cache_storage_mode = None ; action_stdout_on_success = Print ; action_stderr_on_success = Print + ; default_authors = [] ; experimental = [] } ;; @@ -357,6 +375,8 @@ module Dune_config = struct field_o "action_stdout_on_success" (3, 0) Action_output_on_success.decode and+ action_stderr_on_success = field_o "action_stderr_on_success" (3, 0) Action_output_on_success.decode + and+ default_authors = + field_o "default_authors" (3, 0) Default_authors.decode and+ experimental = field_o "experimental" (3, 8) (repeat (pair string (located string))) in @@ -377,6 +397,7 @@ module Dune_config = struct ; cache_storage_mode ; action_stdout_on_success ; action_stderr_on_success + ; default_authors ; experimental } ;; diff --git a/src/dune_config_file/dune_config_file.mli b/src/dune_config_file/dune_config_file.mli index 0f33225084b..714884542e8 100644 --- a/src/dune_config_file/dune_config_file.mli +++ b/src/dune_config_file/dune_config_file.mli @@ -5,6 +5,12 @@ module Dune_config : sig open Dune_config module Display : module type of Display + module Default_authors : sig + type t = string list + + val decode : t Dune_lang.Decoder.t + end + module Concurrency : sig type t = | Fixed of int @@ -56,6 +62,7 @@ module Dune_config : sig ; cache_storage_mode : Cache.Storage_mode.t field ; action_stdout_on_success : Action_output_on_success.t field ; action_stderr_on_success : Action_output_on_success.t field + ; default_authors : Default_authors.t field ; experimental : (string * (Loc.t * string)) list field } end diff --git a/src/dune_lang/package_info.ml b/src/dune_lang/package_info.ml index 177ff173101..d23cbeab1fb 100644 --- a/src/dune_lang/package_info.ml +++ b/src/dune_lang/package_info.ml @@ -41,11 +41,11 @@ let empty = } ;; -let example = +let example defaults = { source = Some (Host (Source_kind.Host.Github { user = "username"; repo = "reponame" })) ; license = Some [ "LICENSE" ] - ; authors = Some [ "Author Name" ] + ; authors = Some defaults ; maintainers = Some [ "Maintainer Name" ] ; documentation = Some "https://url/to/documentation" diff --git a/src/dune_lang/package_info.mli b/src/dune_lang/package_info.mli index 4e9003b410a..3e34905b50b 100644 --- a/src/dune_lang/package_info.mli +++ b/src/dune_lang/package_info.mli @@ -9,7 +9,7 @@ val documentation : t -> string option val maintainers : t -> string list option (** example package info (used for project initialization ) *) -val example : t +val example : string list -> t val empty : t val to_dyn : t Dyn.builder From cab0a11e420eec3163c95af95247b3b7fe1fabcc Mon Sep 17 00:00:00 2001 From: teague hansen Date: Mon, 19 Aug 2024 16:39:02 -0400 Subject: [PATCH 02/17] refactor to make solution more generic Signed-off-by: teague hansen --- bin/common.ml | 1 + bin/dune_init.ml | 13 ++--- bin/dune_init.mli | 6 +- bin/init.ml | 6 +- src/dune_config_file/dune_config_file.ml | 67 +++++++++++++++++------ src/dune_config_file/dune_config_file.mli | 13 +++++ src/dune_lang/package_info.ml | 8 ++- src/dune_lang/package_info.mli | 2 +- 8 files changed, 85 insertions(+), 31 deletions(-) diff --git a/bin/common.ml b/bin/common.ml index 566a20f73e0..f311859696b 100644 --- a/bin/common.ml +++ b/bin/common.ml @@ -488,6 +488,7 @@ let shared_with_config_file = ; cache_storage_mode ; action_stdout_on_success ; action_stderr_on_success + ; project_defaults = None ; default_authors = None ; experimental = None } diff --git a/bin/dune_init.ml b/bin/dune_init.ml index fa4f1b3872a..364bbd522cd 100644 --- a/bin/dune_init.ml +++ b/bin/dune_init.ml @@ -169,17 +169,16 @@ end (** The context in which the initialization is executed *) module Init_context = struct + open Dune_config_file + type t = { dir : Path.t ; project : Dune_project.t - ; defaults : Dune_config_file.Dune_config.t + ; defaults : Dune_config.Project_defaults.t } - let make path config = + let make path defaults = let open Memo.O in - - let _ = config in - let+ project = (* CR-rgrinberg: why not get the project from the source tree? *) Dune_project.load @@ -200,7 +199,7 @@ module Init_context = struct | Some p -> Path.of_string p in File.create_dir dir; - { dir; project; defaults=config } + { dir; project; defaults } ;; end @@ -480,7 +479,7 @@ module Component = struct let content = Stanza_cst.dune_project ~opam_file_gen - ~defaults:context.defaults.default_authors + ~defaults:context.defaults Path.(as_in_source_tree_exn context.dir) common in diff --git a/bin/dune_init.mli b/bin/dune_init.mli index 15339bd0ac4..4e9a4127773 100644 --- a/bin/dune_init.mli +++ b/bin/dune_init.mli @@ -4,13 +4,15 @@ open Import (** The context in which the initialization is executed *) module Init_context : sig + open Dune_config_file + type t = { dir : Path.t ; project : Dune_project.t - ; defaults : Dune_config_file.Dune_config.t + ; defaults : Dune_config.Project_defaults.t } - val make : string option -> Dune_config_file.Dune_config.t -> t Memo.t + val make : string option -> Dune_config.Project_defaults.t -> t Memo.t end module Public_name : sig diff --git a/bin/init.ml b/bin/init.ml index 416eefb3158..64d1052fd38 100644 --- a/bin/init.ml +++ b/bin/init.ml @@ -74,7 +74,8 @@ let context_cwd : Init_context.t Term.t = and+ path = path in let builder = Common.Builder.set_default_root_is_cwd builder true in let common, config = Common.init builder in - Scheduler.go ~common ~config (fun () -> Memo.run (Init_context.make path config)) + let project_defaults = config.project_defaults in + Scheduler.go ~common ~config (fun () -> Memo.run (Init_context.make path project_defaults)) ;; module Public_name = struct @@ -228,7 +229,8 @@ let project = let builder = Builder.set_root common_builder root in let (_ : Fpath.mkdir_p_result) = Fpath.mkdir_p root in let common, config = Common.init builder in - Scheduler.go ~common ~config (fun () -> Memo.run @@ init_context config) + let project_defaults = config.project_defaults in + Scheduler.go ~common ~config (fun () -> Memo.run @@ init_context project_defaults) in Component.init (Project { context; common; options = { template; inline_tests; pkg } }); diff --git a/src/dune_config_file/dune_config_file.ml b/src/dune_config_file/dune_config_file.ml index 3db9c5d608d..3485296275a 100644 --- a/src/dune_config_file/dune_config_file.ml +++ b/src/dune_config_file/dune_config_file.ml @@ -16,15 +16,50 @@ module Dune_config = struct simplicity *) let syntax = Stanza.syntax - module Default_authors = struct - type t = string list + module Project_defaults = struct + type t = (string * string list option) list - let to_dyn = function - | [] -> Dyn.Variant ("Not-Provided", []) - | lst -> Dyn.Set (List.map ~f:(fun s -> Dyn.String s) lst) + let decode = + fields + (let+ authors = field_o "authors" (repeat1 string) + and+ maintainers = field_o "maintainers" (repeat1 string) in + [ ("authors", authors) + ; ("maintainers", maintainers) + ]) + ;; + + let to_dyn t = + Dyn.List (List.map ~f:(fun (name, values_o) -> + let values = Option.value values_o ~default:[] in + let values = List.map ~f:(fun s -> Dyn.String s) values in + Dyn.Tuple [Dyn.String name; Dyn.List values] + ) t) ;; + (* + type t = + { authors : string list option + ; maintainers : string list option + } - let decode = repeat1 string + let to_dyn t = + let str_list_to_dyn_o lst = + let lst = Option.value lst ~default:[] in + let lst = List.map ~f:(fun s -> Dyn.String s) lst in + Dyn.List lst + in + Dyn.Record + [ ("authors", str_list_to_dyn_o t.authors) + ; ("maintainers", str_list_to_dyn_o t.maintainers) + ] + ;; + + let decode = + fields + (let+ authors = field_o "authors" (repeat1 string) + and+ maintainers = field_o "maintainers" (repeat1 string) in + { authors; maintainers }) + ;; + *) end module Terminal_persistence = struct @@ -147,7 +182,7 @@ module Dune_config = struct ; cache_storage_mode : Cache.Storage_mode.t field ; action_stdout_on_success : Action_output_on_success.t field ; action_stderr_on_success : Action_output_on_success.t field - ; default_authors : Default_authors.t field + ; project_defaults : Project_defaults.t field ; experimental : (string * (Loc.t * string)) list field } end @@ -175,7 +210,7 @@ module Dune_config = struct field a.action_stdout_on_success b.action_stdout_on_success ; action_stderr_on_success = field a.action_stderr_on_success b.action_stderr_on_success - ; default_authors = field a.default_authors b.default_authors + ; project_defaults = field a.project_defaults b.project_defaults ; experimental = field a.experimental b.experimental } ;; @@ -199,7 +234,7 @@ module Dune_config = struct ; cache_storage_mode ; action_stdout_on_success ; action_stderr_on_success - ; default_authors + ; project_defaults ; experimental } = @@ -219,8 +254,8 @@ module Dune_config = struct , field Action_output_on_success.to_dyn action_stdout_on_success ) ; ( "action_stderr_on_success" , field Action_output_on_success.to_dyn action_stderr_on_success ) - ; ( "default_authors" - , field Default_authors.to_dyn default_authors ) + ; ( "project_defaults" + , field Project_defaults.to_dyn project_defaults ) ; ( "experimental" , field Dyn.(list (pair string (fun (_, v) -> string v))) experimental ) ] @@ -244,7 +279,7 @@ module Dune_config = struct ; cache_storage_mode = None ; action_stdout_on_success = None ; action_stderr_on_success = None - ; default_authors = None + ; project_defaults = None ; experimental = None } ;; @@ -311,7 +346,7 @@ module Dune_config = struct ; cache_storage_mode = None ; action_stdout_on_success = Print ; action_stderr_on_success = Print - ; default_authors = [] + ; project_defaults = [] ; experimental = [] } ;; @@ -375,8 +410,8 @@ module Dune_config = struct field_o "action_stdout_on_success" (3, 0) Action_output_on_success.decode and+ action_stderr_on_success = field_o "action_stderr_on_success" (3, 0) Action_output_on_success.decode - and+ default_authors = - field_o "default_authors" (3, 0) Default_authors.decode + and+ project_defaults = + field_o "project_defaults" (3, 17) Project_defaults.decode and+ experimental = field_o "experimental" (3, 8) (repeat (pair string (located string))) in @@ -397,7 +432,7 @@ module Dune_config = struct ; cache_storage_mode ; action_stdout_on_success ; action_stderr_on_success - ; default_authors + ; project_defaults ; experimental } ;; diff --git a/src/dune_config_file/dune_config_file.mli b/src/dune_config_file/dune_config_file.mli index 714884542e8..c294961a85c 100644 --- a/src/dune_config_file/dune_config_file.mli +++ b/src/dune_config_file/dune_config_file.mli @@ -5,6 +5,18 @@ module Dune_config : sig open Dune_config module Display : module type of Display + module Project_defaults : sig + (* + type t = + { authors : string list option + ; maintainers : string list option + } + *) + type t = (string * string list option) list + + val decode : t Dune_lang.Decoder.t + end + module Default_authors : sig type t = string list @@ -62,6 +74,7 @@ module Dune_config : sig ; cache_storage_mode : Cache.Storage_mode.t field ; action_stdout_on_success : Action_output_on_success.t field ; action_stderr_on_success : Action_output_on_success.t field + ; project_defaults : Project_defaults.t field ; default_authors : Default_authors.t field ; experimental : (string * (Loc.t * string)) list field } diff --git a/src/dune_lang/package_info.ml b/src/dune_lang/package_info.ml index d23cbeab1fb..5b37096cb5b 100644 --- a/src/dune_lang/package_info.ml +++ b/src/dune_lang/package_info.ml @@ -41,12 +41,14 @@ let empty = } ;; -let example defaults = +let example (conf : (string * string list option) list) = + let authors = List.assoc conf "authors" in + let maintainers = List.assoc conf "maintainers" in { source = Some (Host (Source_kind.Host.Github { user = "username"; repo = "reponame" })) ; license = Some [ "LICENSE" ] - ; authors = Some defaults - ; maintainers = Some [ "Maintainer Name" ] + ; authors = Option.value authors ~default:(Some [ "Author Name" ]) + ; maintainers = Option.value maintainers ~default:(Some [ "Maintainer Name" ]) ; documentation = Some "https://url/to/documentation" (* homepage and bug_reports are inferred from the source *) diff --git a/src/dune_lang/package_info.mli b/src/dune_lang/package_info.mli index 3e34905b50b..fdfc2f9abf2 100644 --- a/src/dune_lang/package_info.mli +++ b/src/dune_lang/package_info.mli @@ -9,7 +9,7 @@ val documentation : t -> string option val maintainers : t -> string list option (** example package info (used for project initialization ) *) -val example : string list -> t +val example : (string * string list option) list -> t val empty : t val to_dyn : t Dyn.builder From 0431f2829e77e35a22e8c7874cd1f25b0253cda2 Mon Sep 17 00:00:00 2001 From: teague hansen Date: Mon, 19 Aug 2024 16:43:43 -0400 Subject: [PATCH 03/17] remove all "Default_author" references Signed-off-by: teague hansen --- bin/common.ml | 1 - src/dune_config_file/dune_config_file.mli | 7 ------- 2 files changed, 8 deletions(-) diff --git a/bin/common.ml b/bin/common.ml index f311859696b..cd460045682 100644 --- a/bin/common.ml +++ b/bin/common.ml @@ -489,7 +489,6 @@ let shared_with_config_file = ; action_stdout_on_success ; action_stderr_on_success ; project_defaults = None - ; default_authors = None ; experimental = None } ;; diff --git a/src/dune_config_file/dune_config_file.mli b/src/dune_config_file/dune_config_file.mli index c294961a85c..638a6d60594 100644 --- a/src/dune_config_file/dune_config_file.mli +++ b/src/dune_config_file/dune_config_file.mli @@ -17,12 +17,6 @@ module Dune_config : sig val decode : t Dune_lang.Decoder.t end - module Default_authors : sig - type t = string list - - val decode : t Dune_lang.Decoder.t - end - module Concurrency : sig type t = | Fixed of int @@ -75,7 +69,6 @@ module Dune_config : sig ; action_stdout_on_success : Action_output_on_success.t field ; action_stderr_on_success : Action_output_on_success.t field ; project_defaults : Project_defaults.t field - ; default_authors : Default_authors.t field ; experimental : (string * (Loc.t * string)) list field } end From e0cf5a375ebef858ae8a3cebb498324de9a4907e Mon Sep 17 00:00:00 2001 From: teague hansen Date: Mon, 19 Aug 2024 17:11:35 -0400 Subject: [PATCH 04/17] add support for license in config Signed-off-by: teague hansen --- src/dune_config_file/dune_config_file.ml | 6 ++++-- src/dune_lang/package_info.ml | 11 ++++++----- 2 files changed, 10 insertions(+), 7 deletions(-) diff --git a/src/dune_config_file/dune_config_file.ml b/src/dune_config_file/dune_config_file.ml index 3485296275a..70afc226516 100644 --- a/src/dune_config_file/dune_config_file.ml +++ b/src/dune_config_file/dune_config_file.ml @@ -22,9 +22,11 @@ module Dune_config = struct let decode = fields (let+ authors = field_o "authors" (repeat1 string) - and+ maintainers = field_o "maintainers" (repeat1 string) in + and+ maintainers = field_o "maintainers" (repeat1 string) + and+ license = field_o "license" (repeat1 string) in [ ("authors", authors) ; ("maintainers", maintainers) + ; ("license", license) ]) ;; @@ -411,7 +413,7 @@ module Dune_config = struct and+ action_stderr_on_success = field_o "action_stderr_on_success" (3, 0) Action_output_on_success.decode and+ project_defaults = - field_o "project_defaults" (3, 17) Project_defaults.decode + field_o "project_defaults" (3, 0) Project_defaults.decode and+ experimental = field_o "experimental" (3, 8) (repeat (pair string (located string))) in diff --git a/src/dune_lang/package_info.ml b/src/dune_lang/package_info.ml index 5b37096cb5b..f0f919f6d2d 100644 --- a/src/dune_lang/package_info.ml +++ b/src/dune_lang/package_info.ml @@ -42,13 +42,14 @@ let empty = ;; let example (conf : (string * string list option) list) = - let authors = List.assoc conf "authors" in - let maintainers = List.assoc conf "maintainers" in + let authors = Option.value_exn @@ List.assoc conf "authors" in + let maintainers = Option.value_exn @@ List.assoc conf "maintainers" in + let license = Option.value_exn @@ List.assoc conf "license" in { source = Some (Host (Source_kind.Host.Github { user = "username"; repo = "reponame" })) - ; license = Some [ "LICENSE" ] - ; authors = Option.value authors ~default:(Some [ "Author Name" ]) - ; maintainers = Option.value maintainers ~default:(Some [ "Maintainer Name" ]) + ; license = Some (Option.value license ~default:[ "LICENSE" ]) + ; authors = Some (Option.value authors ~default:[ "Author Name" ]) + ; maintainers = Some (Option.value maintainers ~default:[ "Maintainer Name" ]) ; documentation = Some "https://url/to/documentation" (* homepage and bug_reports are inferred from the source *) From a4254713101f592785b214998a93465a61a08032 Mon Sep 17 00:00:00 2001 From: teague hansen Date: Mon, 19 Aug 2024 17:52:41 -0400 Subject: [PATCH 05/17] apply clean up for existing tests Signed-off-by: teague hansen --- src/dune_lang/package_info.ml | 6 +++--- test/expect-tests/dune_config_file/dune_config_test.ml | 3 +++ 2 files changed, 6 insertions(+), 3 deletions(-) diff --git a/src/dune_lang/package_info.ml b/src/dune_lang/package_info.ml index f0f919f6d2d..5f61a451ea1 100644 --- a/src/dune_lang/package_info.ml +++ b/src/dune_lang/package_info.ml @@ -42,9 +42,9 @@ let empty = ;; let example (conf : (string * string list option) list) = - let authors = Option.value_exn @@ List.assoc conf "authors" in - let maintainers = Option.value_exn @@ List.assoc conf "maintainers" in - let license = Option.value_exn @@ List.assoc conf "license" in + let authors = Option.value ~default:None (List.assoc conf "authors") in + let maintainers = Option.value ~default:None (List.assoc conf "maintainers") in + let license = Option.value ~default:None (List.assoc conf "license") in { source = Some (Host (Source_kind.Host.Github { user = "username"; repo = "reponame" })) ; license = Some (Option.value license ~default:[ "LICENSE" ]) diff --git a/test/expect-tests/dune_config_file/dune_config_test.ml b/test/expect-tests/dune_config_file/dune_config_test.ml index 28948fdb4e7..663a1ac9431 100644 --- a/test/expect-tests/dune_config_file/dune_config_test.ml +++ b/test/expect-tests/dune_config_file/dune_config_test.ml @@ -27,6 +27,7 @@ let%expect_test "cache-check-probability 0.1" = ; cache_storage_mode = None ; action_stdout_on_success = Print ; action_stderr_on_success = Print + ; project_defaults = [] ; experimental = [] } |}] @@ -45,6 +46,7 @@ let%expect_test "cache-storage-mode copy" = ; cache_storage_mode = Some Copy ; action_stdout_on_success = Print ; action_stderr_on_success = Print + ; project_defaults = [] ; experimental = [] } |}] @@ -63,6 +65,7 @@ let%expect_test "cache-storage-mode hardlink" = ; cache_storage_mode = Some Hardlink ; action_stdout_on_success = Print ; action_stderr_on_success = Print + ; project_defaults = [] ; experimental = [] } |}] From 083f8de8edca18b54f04f91b9716bd104e16528f Mon Sep 17 00:00:00 2001 From: teague hansen Date: Mon, 19 Aug 2024 18:10:05 -0400 Subject: [PATCH 06/17] fmt Signed-off-by: teague hansen --- bin/init.ml | 3 ++- src/dune_config_file/dune_config_file.ml | 25 ++++++++++------------- src/dune_config_file/dune_config_file.mli | 2 +- 3 files changed, 14 insertions(+), 16 deletions(-) diff --git a/bin/init.ml b/bin/init.ml index 64d1052fd38..1763f03ce49 100644 --- a/bin/init.ml +++ b/bin/init.ml @@ -75,7 +75,8 @@ let context_cwd : Init_context.t Term.t = let builder = Common.Builder.set_default_root_is_cwd builder true in let common, config = Common.init builder in let project_defaults = config.project_defaults in - Scheduler.go ~common ~config (fun () -> Memo.run (Init_context.make path project_defaults)) + Scheduler.go ~common ~config (fun () -> + Memo.run (Init_context.make path project_defaults)) ;; module Public_name = struct diff --git a/src/dune_config_file/dune_config_file.ml b/src/dune_config_file/dune_config_file.ml index 70afc226516..c2168f63982 100644 --- a/src/dune_config_file/dune_config_file.ml +++ b/src/dune_config_file/dune_config_file.ml @@ -24,21 +24,20 @@ module Dune_config = struct (let+ authors = field_o "authors" (repeat1 string) and+ maintainers = field_o "maintainers" (repeat1 string) and+ license = field_o "license" (repeat1 string) in - [ ("authors", authors) - ; ("maintainers", maintainers) - ; ("license", license) - ]) + [ "authors", authors; "maintainers", maintainers; "license", license ]) ;; let to_dyn t = - Dyn.List (List.map ~f:(fun (name, values_o) -> - let values = Option.value values_o ~default:[] in - let values = List.map ~f:(fun s -> Dyn.String s) values in - Dyn.Tuple [Dyn.String name; Dyn.List values] - ) t) + Dyn.List + (List.map + ~f:(fun (name, values_o) -> + let values = Option.value values_o ~default:[] in + let values = List.map ~f:(fun s -> Dyn.String s) values in + Dyn.Tuple [ Dyn.String name; Dyn.List values ]) + t) ;; (* - type t = + type t = { authors : string list option ; maintainers : string list option } @@ -256,8 +255,7 @@ module Dune_config = struct , field Action_output_on_success.to_dyn action_stdout_on_success ) ; ( "action_stderr_on_success" , field Action_output_on_success.to_dyn action_stderr_on_success ) - ; ( "project_defaults" - , field Project_defaults.to_dyn project_defaults ) + ; "project_defaults", field Project_defaults.to_dyn project_defaults ; ( "experimental" , field Dyn.(list (pair string (fun (_, v) -> string v))) experimental ) ] @@ -412,8 +410,7 @@ module Dune_config = struct field_o "action_stdout_on_success" (3, 0) Action_output_on_success.decode and+ action_stderr_on_success = field_o "action_stderr_on_success" (3, 0) Action_output_on_success.decode - and+ project_defaults = - field_o "project_defaults" (3, 0) Project_defaults.decode + and+ project_defaults = field_o "project_defaults" (3, 17) Project_defaults.decode and+ experimental = field_o "experimental" (3, 8) (repeat (pair string (located string))) in diff --git a/src/dune_config_file/dune_config_file.mli b/src/dune_config_file/dune_config_file.mli index 638a6d60594..7ebcbf435f6 100644 --- a/src/dune_config_file/dune_config_file.mli +++ b/src/dune_config_file/dune_config_file.mli @@ -7,7 +7,7 @@ module Dune_config : sig module Project_defaults : sig (* - type t = + type t = { authors : string list option ; maintainers : string list option } From ecb5984f529f363278303203fc6d5cf07372f7c7 Mon Sep 17 00:00:00 2001 From: teague hansen Date: Mon, 19 Aug 2024 19:49:41 -0400 Subject: [PATCH 07/17] add initial test cases Signed-off-by: teague hansen --- .../test-cases/config-project-defaults.t | 63 +++++++++++++++++++ 1 file changed, 63 insertions(+) create mode 100644 test/blackbox-tests/test-cases/config-project-defaults.t diff --git a/test/blackbox-tests/test-cases/config-project-defaults.t b/test/blackbox-tests/test-cases/config-project-defaults.t new file mode 100644 index 00000000000..3350ae3d489 --- /dev/null +++ b/test/blackbox-tests/test-cases/config-project-defaults.t @@ -0,0 +1,63 @@ +Create a config file to use in all test that follow, adding the +'project_defaults' stanza to specify default values for various fields of the +generated 'dune-project' file. + + $ touch dune-config + $ cat >dune-config < (lang dune 3.17) + > (project_defaults + > (authors AuthorTest) + > (maintainers MaintainerTest) + > (license MIT)) + > EOF + +Initialize a new dune project providing the config file we just created and +check each of the stanzas that we set defaults for in the config file. + + $ dune init proj test_proj --config-file=dune-config + Entering directory 'test_proj' + Success: initialized project component named test_proj + Leaving directory 'test_proj' + + $ cat test_proj/dune-project | grep -i authors + (authors AuthorTest) + + $ cat test_proj/dune-project | grep -i maintainers + (maintainers MaintainerTest) + + $ cat test_proj/dune-project | grep -i license + (license MIT) + +Change the version of the config file to one which does not support the +'project_defaults' stanza to ensure the proper error is raised. + + $ sed -i -e '1s|.*|(lang dune 3.16)|' dune-config + $ dune init proj test_proj1 --config-file=dune-config + File "$TESTCASE_ROOT/dune-config", lines 2-5, characters 0-85: + 2 | (project_defaults + 3 | (authors AuthorTest) + 4 | (maintainers MaintainerTest) + 5 | (license MIT)) + Error: 'project_defaults' is only available since version 3.17 of the dune + language. Please update your dune-project file to have (lang dune 3.17). + [1] + + $ sed -i -e '1s|.*|(lang dune 3.17)|' dune-config + +Check to ensure that the default values are used when optional stanzas are +removed/not used. + + $ sed -i -e '3,5c\)' dune-config + $ dune init proj test_proj1 --config-file=dune-config + Entering directory 'test_proj1' + Success: initialized project component named test_proj1 + Leaving directory 'test_proj1' + + $ cat test_proj1/dune-project | grep -i authors + (authors "Author Name") + + $ cat test_proj1/dune-project | grep -i maintainers + (maintainers "Maintainer Name") + + $ cat test_proj1/dune-project | grep -i license + (license LICENSE) From eeb6f5455f28acaa8b1cfe7f3d057b8b21bdeb09 Mon Sep 17 00:00:00 2001 From: teague hansen Date: Mon, 19 Aug 2024 20:17:47 -0400 Subject: [PATCH 08/17] add inital documentation for project_defaults stanza Signed-off-by: teague hansen --- doc/reference/config/index.rst | 1 + doc/reference/config/project_defaults.rst | 50 +++++++++++++++++++++++ 2 files changed, 51 insertions(+) create mode 100644 doc/reference/config/project_defaults.rst diff --git a/doc/reference/config/index.rst b/doc/reference/config/index.rst index 5b78bb94512..667b3a36b3e 100644 --- a/doc/reference/config/index.rst +++ b/doc/reference/config/index.rst @@ -22,5 +22,6 @@ The ``config`` file can contain the following stanzas: cache_storage_mode display jobs + project_defaults sandboxing_preference terminal_persistence diff --git a/doc/reference/config/project_defaults.rst b/doc/reference/config/project_defaults.rst new file mode 100644 index 00000000000..21e9fd01dcc --- /dev/null +++ b/doc/reference/config/project_defaults.rst @@ -0,0 +1,50 @@ +project_defaults +---------------- + +Specifies default values for various stanzas in the generated ``dune-project`` +file when using ``dune init project``. The format of the project default stanza +is as follows: + +.. code:: dune + + (project_defaults + ) + +``) + + Specify authors. + + Example: + + .. code:: dune + + (project_defaults + (authors + "Jane Doe " + "John Doe ")) + +.. describe:: (maintainers ) + + Specify maintainers. + + Example: + + .. code:: dune + + (project_defaults + (maintainers + "Jane Doe " + "John Doe ")) + +.. describe:: (license ) + + Specify license. + + Example: + + .. code:: dune + + (project_defaults + (license "MIT")) From 7521fa0c2c6ca206b7c776b3bfaa3c9674a0ebb1 Mon Sep 17 00:00:00 2001 From: teague hansen Date: Mon, 19 Aug 2024 21:30:51 -0400 Subject: [PATCH 09/17] refactor how default values are passed from config to example Signed-off-by: teague hansen --- bin/dune_init.ml | 14 ++++++-- src/dune_config_file/dune_config_file.ml | 42 ++++++++--------------- src/dune_config_file/dune_config_file.mli | 12 +++---- src/dune_lang/package_info.ml | 5 +-- src/dune_lang/package_info.mli | 6 +++- 5 files changed, 37 insertions(+), 42 deletions(-) diff --git a/bin/dune_init.ml b/bin/dune_init.ml index 364bbd522cd..531e5aee0bb 100644 --- a/bin/dune_init.ml +++ b/bin/dune_init.ml @@ -376,7 +376,12 @@ module Component = struct let test common (() : Options.Test.t) = make "test" common [] (* A list of CSTs for dune-project file content *) - let dune_project ~opam_file_gen ~defaults dir (common : Options.Common.t) = + let dune_project + ~opam_file_gen + ~(defaults : Dune_config_file.Dune_config.Project_defaults.t) + dir + (common : Options.Common.t) + = let cst = let package = Package.create @@ -403,7 +408,12 @@ module Component = struct ] in let packages = Package.Name.Map.singleton (Package.name package) package in - let info = Package_info.example defaults in + let info = + Package_info.example + ~authors:defaults.authors + ~maintainers:defaults.maintainers + ~license:defaults.license + in Dune_project.anonymous ~dir info packages |> Dune_project.set_generate_opam_files opam_file_gen |> Dune_project.encode diff --git a/src/dune_config_file/dune_config_file.ml b/src/dune_config_file/dune_config_file.ml index c2168f63982..5193e9716ff 100644 --- a/src/dune_config_file/dune_config_file.ml +++ b/src/dune_config_file/dune_config_file.ml @@ -17,30 +17,19 @@ module Dune_config = struct let syntax = Stanza.syntax module Project_defaults = struct - type t = (string * string list option) list + type t = + { authors : string list option + ; maintainers : string list option + ; license : string list option + } let decode = fields (let+ authors = field_o "authors" (repeat1 string) and+ maintainers = field_o "maintainers" (repeat1 string) and+ license = field_o "license" (repeat1 string) in - [ "authors", authors; "maintainers", maintainers; "license", license ]) - ;; - - let to_dyn t = - Dyn.List - (List.map - ~f:(fun (name, values_o) -> - let values = Option.value values_o ~default:[] in - let values = List.map ~f:(fun s -> Dyn.String s) values in - Dyn.Tuple [ Dyn.String name; Dyn.List values ]) - t) + { authors; maintainers; license }) ;; - (* - type t = - { authors : string list option - ; maintainers : string list option - } let to_dyn t = let str_list_to_dyn_o lst = @@ -49,18 +38,11 @@ module Dune_config = struct Dyn.List lst in Dyn.Record - [ ("authors", str_list_to_dyn_o t.authors) - ; ("maintainers", str_list_to_dyn_o t.maintainers) + [ "authors", str_list_to_dyn_o t.authors + ; "maintainers", str_list_to_dyn_o t.maintainers + ; "license", str_list_to_dyn_o t.license ] ;; - - let decode = - fields - (let+ authors = field_o "authors" (repeat1 string) - and+ maintainers = field_o "maintainers" (repeat1 string) in - { authors; maintainers }) - ;; - *) end module Terminal_persistence = struct @@ -346,7 +328,11 @@ module Dune_config = struct ; cache_storage_mode = None ; action_stdout_on_success = Print ; action_stderr_on_success = Print - ; project_defaults = [] + ; project_defaults = + { authors = Some [ "Author Name" ] + ; maintainers = Some [ "Maintainer Name" ] + ; license = Some [ "LICENSE" ] + } ; experimental = [] } ;; diff --git a/src/dune_config_file/dune_config_file.mli b/src/dune_config_file/dune_config_file.mli index 7ebcbf435f6..c08d3969734 100644 --- a/src/dune_config_file/dune_config_file.mli +++ b/src/dune_config_file/dune_config_file.mli @@ -6,13 +6,11 @@ module Dune_config : sig module Display : module type of Display module Project_defaults : sig - (* - type t = - { authors : string list option - ; maintainers : string list option - } - *) - type t = (string * string list option) list + type t = + { authors : string list option + ; maintainers : string list option + ; license : string list option + } val decode : t Dune_lang.Decoder.t end diff --git a/src/dune_lang/package_info.ml b/src/dune_lang/package_info.ml index 5f61a451ea1..76bc7f8460f 100644 --- a/src/dune_lang/package_info.ml +++ b/src/dune_lang/package_info.ml @@ -41,10 +41,7 @@ let empty = } ;; -let example (conf : (string * string list option) list) = - let authors = Option.value ~default:None (List.assoc conf "authors") in - let maintainers = Option.value ~default:None (List.assoc conf "maintainers") in - let license = Option.value ~default:None (List.assoc conf "license") in +let example ~authors ~maintainers ~license = { source = Some (Host (Source_kind.Host.Github { user = "username"; repo = "reponame" })) ; license = Some (Option.value license ~default:[ "LICENSE" ]) diff --git a/src/dune_lang/package_info.mli b/src/dune_lang/package_info.mli index fdfc2f9abf2..7a5dd3e1dba 100644 --- a/src/dune_lang/package_info.mli +++ b/src/dune_lang/package_info.mli @@ -9,7 +9,11 @@ val documentation : t -> string option val maintainers : t -> string list option (** example package info (used for project initialization ) *) -val example : (string * string list option) list -> t +val example + : authors:string list option + -> maintainers:string list option + -> license:string list option + -> t val empty : t val to_dyn : t Dyn.builder From 0f38f2febcb1d734dd9bdbefc9fc26ce3cd2e120 Mon Sep 17 00:00:00 2001 From: teague hansen Date: Mon, 19 Aug 2024 22:09:52 -0400 Subject: [PATCH 10/17] attempt fix for failing tests Signed-off-by: teague hansen --- .../test-cases/config-project-defaults.t | 3 ++- .../dune_config_file/dune_config_test.ml | 18 +++++++++++++++--- 2 files changed, 17 insertions(+), 4 deletions(-) diff --git a/test/blackbox-tests/test-cases/config-project-defaults.t b/test/blackbox-tests/test-cases/config-project-defaults.t index 3350ae3d489..c0e6c6746e4 100644 --- a/test/blackbox-tests/test-cases/config-project-defaults.t +++ b/test/blackbox-tests/test-cases/config-project-defaults.t @@ -47,7 +47,8 @@ Change the version of the config file to one which does not support the Check to ensure that the default values are used when optional stanzas are removed/not used. - $ sed -i -e '3,5c\)' dune-config + $ sed -i -e '3,5c\ + > )' dune-config $ dune init proj test_proj1 --config-file=dune-config Entering directory 'test_proj1' Success: initialized project component named test_proj1 diff --git a/test/expect-tests/dune_config_file/dune_config_test.ml b/test/expect-tests/dune_config_file/dune_config_test.ml index 663a1ac9431..d9ec22d099c 100644 --- a/test/expect-tests/dune_config_file/dune_config_test.ml +++ b/test/expect-tests/dune_config_file/dune_config_test.ml @@ -27,7 +27,11 @@ let%expect_test "cache-check-probability 0.1" = ; cache_storage_mode = None ; action_stdout_on_success = Print ; action_stderr_on_success = Print - ; project_defaults = [] + ; project_defaults = + { authors = [ "Author Name" ] + ; maintainers = [ "Maintainer Name" ] + ; license = [ "LICENSE" ] + } ; experimental = [] } |}] @@ -46,7 +50,11 @@ let%expect_test "cache-storage-mode copy" = ; cache_storage_mode = Some Copy ; action_stdout_on_success = Print ; action_stderr_on_success = Print - ; project_defaults = [] + ; project_defaults = + { authors = [ "Author Name" ] + ; maintainers = [ "Maintainer Name" ] + ; license = [ "LICENSE" ] + } ; experimental = [] } |}] @@ -65,7 +73,11 @@ let%expect_test "cache-storage-mode hardlink" = ; cache_storage_mode = Some Hardlink ; action_stdout_on_success = Print ; action_stderr_on_success = Print - ; project_defaults = [] + ; project_defaults = + { authors = [ "Author Name" ] + ; maintainers = [ "Maintainer Name" ] + ; license = [ "LICENSE" ] + } ; experimental = [] } |}] From 994e3129ac4f6d9c347b22f55c8062392ccdd9d3 Mon Sep 17 00:00:00 2001 From: teague hansen Date: Wed, 21 Aug 2024 10:21:15 -0400 Subject: [PATCH 11/17] add additional test cases verifying stanza behavior Signed-off-by: teague hansen --- .../test-cases/config-project-defaults.t | 60 +++++++++++++++++++ 1 file changed, 60 insertions(+) diff --git a/test/blackbox-tests/test-cases/config-project-defaults.t b/test/blackbox-tests/test-cases/config-project-defaults.t index c0e6c6746e4..b8b085a7e4f 100644 --- a/test/blackbox-tests/test-cases/config-project-defaults.t +++ b/test/blackbox-tests/test-cases/config-project-defaults.t @@ -62,3 +62,63 @@ removed/not used. $ cat test_proj1/dune-project | grep -i license (license LICENSE) + +In the previous test all sub stanzas of the 'project_default' stanza where +removed so we will create a new config file continue testing. This time we will +used quoted string values and test the ability to add multiple +authors/maintainers. + + $ rm dune-config; touch dune-config + $ cat >dune-config < (lang dune 3.17) + > (project_defaults + > (authors "AuthorTest1" "AuthorTest2") + > (maintainers "Maintainer1" "Maintainer2" "Maintainer3") + > (license "BSD")) + > EOF + +Now we test to see if quoted list values are properly generated in the +dune-project file. + + $ dune init proj test_proj2 --config-file=dune-config + Entering directory 'test_proj2' + Success: initialized project component named test_proj2 + Leaving directory 'test_proj2' + + $ cat test_proj2/dune-project | grep -i authors + (authors AuthorTest1 AuthorTest2) + + $ cat test_proj2/dune-project | grep -i maintainers + (maintainers Maintainer1 Maintainer2 Maintainer3) + + $ cat test_proj2/dune-project | grep -i license + (license BSD) + +Ensure that an error is raised when an optional stanza is provided but its value +is omitted. + + $ sed -i -e '3s|.*|(authors)|' dune-config + $ dune init proj test_proj3 --config-file=dune-config + File "$TESTCASE_ROOT/dune-config", line 3, characters 0-9: + 3 | (authors) + ^^^^^^^^^ + Error: Not enough arguments for "authors" + [1] + + $ sed -i -e '3d' dune-config + $ sed -i -e '3s|.*|(maintainers)|' dune-config + $ dune init proj test_proj3 --config-file=dune-config + File "$TESTCASE_ROOT/dune-config", line 3, characters 0-13: + 3 | (maintainers) + ^^^^^^^^^^^^^ + Error: Not enough arguments for "maintainers" + [1] + + $ sed -i -e '3d' dune-config + $ sed -i -e '3s|.*|(license))|' dune-config + $ dune init proj test_proj3 --config-file=dune-config + File "$TESTCASE_ROOT/dune-config", line 3, characters 0-9: + 3 | (license)) + ^^^^^^^^^ + Error: Not enough arguments for "license" + [1] From 10f1e25585d657aba44d104e0c6ce13259cf1cda Mon Sep 17 00:00:00 2001 From: teague hansen Date: Wed, 21 Aug 2024 10:33:49 -0400 Subject: [PATCH 12/17] revise documentation page of project_defaults stanza Signed-off-by: teague hansen --- doc/reference/config/project_defaults.rst | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/doc/reference/config/project_defaults.rst b/doc/reference/config/project_defaults.rst index 21e9fd01dcc..15380ea564c 100644 --- a/doc/reference/config/project_defaults.rst +++ b/doc/reference/config/project_defaults.rst @@ -1,16 +1,16 @@ project_defaults ---------------- -Specifies default values for various stanzas in the generated ``dune-project`` -file when using ``dune init project``. The format of the project default stanza -is as follows: +Specify default values for stanzas ``authors``, ``maintainers``, and ``license`` +of the dune-project file when initializing a project with ``dune init proj``. +The format of the 'project_defaults' stanza is as follows: .. code:: dune (project_defaults ) -```` are: .. describe:: (authors ) From ad73096e407978265a162fd06f45fc1dcfb85a03 Mon Sep 17 00:00:00 2001 From: teague hansen Date: Wed, 28 Aug 2024 16:37:43 -0400 Subject: [PATCH 13/17] update package_info.ml to conform with recently pushed changes Signed-off-by: teague hansen --- src/dune_lang/package_info.ml | 6 ++++-- test/blackbox-tests/test-cases/config-project-defaults.t | 4 ++-- 2 files changed, 6 insertions(+), 4 deletions(-) diff --git a/src/dune_lang/package_info.ml b/src/dune_lang/package_info.ml index 76bc7f8460f..cfcce1b6eb8 100644 --- a/src/dune_lang/package_info.ml +++ b/src/dune_lang/package_info.ml @@ -45,8 +45,10 @@ let example ~authors ~maintainers ~license = { source = Some (Host (Source_kind.Host.Github { user = "username"; repo = "reponame" })) ; license = Some (Option.value license ~default:[ "LICENSE" ]) - ; authors = Some (Option.value authors ~default:[ "Author Name" ]) - ; maintainers = Some (Option.value maintainers ~default:[ "Maintainer Name" ]) + ; authors = Some (Option.value authors ~default:[ "Author Name " ]) + ; maintainers = + Some + (Option.value maintainers ~default:[ "Maintainer Name " ]) ; documentation = Some "https://url/to/documentation" (* homepage and bug_reports are inferred from the source *) diff --git a/test/blackbox-tests/test-cases/config-project-defaults.t b/test/blackbox-tests/test-cases/config-project-defaults.t index b8b085a7e4f..33541cc7560 100644 --- a/test/blackbox-tests/test-cases/config-project-defaults.t +++ b/test/blackbox-tests/test-cases/config-project-defaults.t @@ -55,10 +55,10 @@ removed/not used. Leaving directory 'test_proj1' $ cat test_proj1/dune-project | grep -i authors - (authors "Author Name") + (authors "Author Name ") $ cat test_proj1/dune-project | grep -i maintainers - (maintainers "Maintainer Name") + (maintainers "Maintainer Name ") $ cat test_proj1/dune-project | grep -i license (license LICENSE) From 9fdc492ac4fd5808758bcb27a12be010dae2d238 Mon Sep 17 00:00:00 2001 From: teague hansen Date: Wed, 28 Aug 2024 16:57:21 -0400 Subject: [PATCH 14/17] update defaults fixing failing test case Signed-off-by: teague hansen --- src/dune_config_file/dune_config_file.ml | 4 ++-- .../dune_config_file/dune_config_test.ml | 12 ++++++------ 2 files changed, 8 insertions(+), 8 deletions(-) diff --git a/src/dune_config_file/dune_config_file.ml b/src/dune_config_file/dune_config_file.ml index 8835da0a2c3..32e3c2f691b 100644 --- a/src/dune_config_file/dune_config_file.ml +++ b/src/dune_config_file/dune_config_file.ml @@ -329,8 +329,8 @@ module Dune_config = struct ; action_stdout_on_success = Print ; action_stderr_on_success = Print ; project_defaults = - { authors = Some [ "Author Name" ] - ; maintainers = Some [ "Maintainer Name" ] + { authors = Some [ "Author Name " ] + ; maintainers = Some [ "Maintainer Name " ] ; license = Some [ "LICENSE" ] } ; experimental = [] diff --git a/test/expect-tests/dune_config_file/dune_config_test.ml b/test/expect-tests/dune_config_file/dune_config_test.ml index b0e2cd8d6b3..41caa4df0d3 100644 --- a/test/expect-tests/dune_config_file/dune_config_test.ml +++ b/test/expect-tests/dune_config_file/dune_config_test.ml @@ -28,8 +28,8 @@ let%expect_test "cache-check-probability 0.1" = ; action_stdout_on_success = Print ; action_stderr_on_success = Print ; project_defaults = - { authors = [ "Author Name" ] - ; maintainers = [ "Maintainer Name" ] + { authors = [ "Author Name " ] + ; maintainers = [ "Maintainer Name " ] ; license = [ "LICENSE" ] } ; experimental = [] @@ -51,8 +51,8 @@ let%expect_test "cache-storage-mode copy" = ; action_stdout_on_success = Print ; action_stderr_on_success = Print ; project_defaults = - { authors = [ "Author Name" ] - ; maintainers = [ "Maintainer Name" ] + { authors = [ "Author Name " ] + ; maintainers = [ "Maintainer Name " ] ; license = [ "LICENSE" ] } ; experimental = [] @@ -74,8 +74,8 @@ let%expect_test "cache-storage-mode hardlink" = ; action_stdout_on_success = Print ; action_stderr_on_success = Print ; project_defaults = - { authors = [ "Author Name" ] - ; maintainers = [ "Maintainer Name" ] + { authors = [ "Author Name " ] + ; maintainers = [ "Maintainer Name " ] ; license = [ "LICENSE" ] } ; experimental = [] From 5af0e72caf8a41940579d272600727484a9fa5a3 Mon Sep 17 00:00:00 2001 From: teague hansen Date: Wed, 11 Sep 2024 19:00:18 -0400 Subject: [PATCH 15/17] allow empty but defined stanza copying dune-project behavior Signed-off-by: teague hansen --- src/dune_config_file/dune_config_file.ml | 6 ++-- .../test-cases/config-project-defaults.t | 29 ------------------- 2 files changed, 3 insertions(+), 32 deletions(-) diff --git a/src/dune_config_file/dune_config_file.ml b/src/dune_config_file/dune_config_file.ml index 32e3c2f691b..56000b62aad 100644 --- a/src/dune_config_file/dune_config_file.ml +++ b/src/dune_config_file/dune_config_file.ml @@ -25,9 +25,9 @@ module Dune_config = struct let decode = fields - (let+ authors = field_o "authors" (repeat1 string) - and+ maintainers = field_o "maintainers" (repeat1 string) - and+ license = field_o "license" (repeat1 string) in + (let+ authors = field_o "authors" (repeat string) + and+ maintainers = field_o "maintainers" (repeat string) + and+ license = field_o "license" (repeat string) in { authors; maintainers; license }) ;; diff --git a/test/blackbox-tests/test-cases/config-project-defaults.t b/test/blackbox-tests/test-cases/config-project-defaults.t index 33541cc7560..4bfd71e62d3 100644 --- a/test/blackbox-tests/test-cases/config-project-defaults.t +++ b/test/blackbox-tests/test-cases/config-project-defaults.t @@ -93,32 +93,3 @@ dune-project file. $ cat test_proj2/dune-project | grep -i license (license BSD) - -Ensure that an error is raised when an optional stanza is provided but its value -is omitted. - - $ sed -i -e '3s|.*|(authors)|' dune-config - $ dune init proj test_proj3 --config-file=dune-config - File "$TESTCASE_ROOT/dune-config", line 3, characters 0-9: - 3 | (authors) - ^^^^^^^^^ - Error: Not enough arguments for "authors" - [1] - - $ sed -i -e '3d' dune-config - $ sed -i -e '3s|.*|(maintainers)|' dune-config - $ dune init proj test_proj3 --config-file=dune-config - File "$TESTCASE_ROOT/dune-config", line 3, characters 0-13: - 3 | (maintainers) - ^^^^^^^^^^^^^ - Error: Not enough arguments for "maintainers" - [1] - - $ sed -i -e '3d' dune-config - $ sed -i -e '3s|.*|(license))|' dune-config - $ dune init proj test_proj3 --config-file=dune-config - File "$TESTCASE_ROOT/dune-config", line 3, characters 0-9: - 3 | (license)) - ^^^^^^^^^ - Error: Not enough arguments for "license" - [1] From 35003b0b3a17347fe7330de2df46782f4c765b52 Mon Sep 17 00:00:00 2001 From: teague hansen Date: Fri, 13 Sep 2024 08:43:43 -0400 Subject: [PATCH 16/17] clean up doc and add chagelog file Signed-off-by: teague hansen --- doc/changes/10835.md | 3 +++ doc/reference/config/project_defaults.rst | 9 ++++++--- 2 files changed, 9 insertions(+), 3 deletions(-) create mode 100644 doc/changes/10835.md diff --git a/doc/changes/10835.md b/doc/changes/10835.md new file mode 100644 index 00000000000..2b1028b98a2 --- /dev/null +++ b/doc/changes/10835.md @@ -0,0 +1,3 @@ +- Add support for specifying default values of the `authors`, `maintainers`, and + `license` stanzas of the `dune-project` file via the dune config file. Default + values are set using the `(project_defaults)` stanza (#10835, @H-ANSEN) diff --git a/doc/reference/config/project_defaults.rst b/doc/reference/config/project_defaults.rst index 15380ea564c..0bf5968b5d0 100644 --- a/doc/reference/config/project_defaults.rst +++ b/doc/reference/config/project_defaults.rst @@ -1,9 +1,11 @@ project_defaults ---------------- +.. versionadded:: 3.17 + Specify default values for stanzas ``authors``, ``maintainers``, and ``license`` -of the dune-project file when initializing a project with ``dune init proj``. -The format of the 'project_defaults' stanza is as follows: +of the :doc:`../dune-project/index` file when initializing a project with +``dune init proj``. The format of the 'project_defaults' stanza is as follows: .. code:: dune @@ -40,7 +42,8 @@ The format of the 'project_defaults' stanza is as follows: .. describe:: (license ) - Specify license. + Specify license, ideally as an identifier from the `SPDX License List + `__. Example: From 8fbff0460fc2cb6c0b0e6d83ba758722d434dad0 Mon Sep 17 00:00:00 2001 From: Rudi Grinberg Date: Sun, 15 Sep 2024 10:48:51 +0100 Subject: [PATCH 17/17] _ Signed-off-by: Rudi Grinberg --- src/dune_config_file/dune_config_file.ml | 13 +++---------- 1 file changed, 3 insertions(+), 10 deletions(-) diff --git a/src/dune_config_file/dune_config_file.ml b/src/dune_config_file/dune_config_file.ml index 56000b62aad..a2901197ebb 100644 --- a/src/dune_config_file/dune_config_file.ml +++ b/src/dune_config_file/dune_config_file.ml @@ -32,16 +32,9 @@ module Dune_config = struct ;; let to_dyn t = - let str_list_to_dyn_o lst = - let lst = Option.value lst ~default:[] in - let lst = List.map ~f:(fun s -> Dyn.String s) lst in - Dyn.List lst - in - Dyn.Record - [ "authors", str_list_to_dyn_o t.authors - ; "maintainers", str_list_to_dyn_o t.maintainers - ; "license", str_list_to_dyn_o t.license - ] + let f = Dyn.(option (list string)) in + Dyn.record + [ "authors", f t.authors; "maintainers", f t.maintainers; "license", f t.license ] ;; end