%%% -*- erlang-indent-level:4; indent-tabs-mode: nil -*- %%%------------------------------------------------------------------- %%% @copyright (C) 2025, QPQ AG %%% @copyright (C) 2017, Aeternity Anstalt %%% @doc Bootstrapping and querying the Gajumaru environment %%% %%% @end %%%------------------------------------------------------------------- -module(gmconfig). -export([get_env/2, get_env/3]). -export([user_config/0]). % returns current user config -export([load_main_config_schema/0, load_system_defaults/0]). -export([load_user_config/0, load_user_config/1]). -export([schema/0, schema/1, schema/2]). -export([load_schema/0]). % load_user_config() ensures schema is loaded -export([schema_default/1, schema_default/2]). -export([schema_keys/0, schema_keys/1]). -export([config_value/4]). -export([find_config/1, find_config/2, %% -> {ok, Value} | undefined get_config/1, get_config/2 %% -> Value (or exception) ]). -export([merge_config_maps/2]). -export([nested_map_get/2]). -export([load_config_file/1]). % apply system-/network-specific defaults -export([search_for_config_file/2]). -export([apply_os_env/0, apply_os_env/3]). -export([process_plain_args/0]). -export([data_dir/1]). -export([check_config/1]). -export([update_config/1, update_config/2, update_config/3, silent_update_config/1, delete_config_value/1, suggest_config/2, set_config_value/2]). %% (Path, Value) -export([export_config/0]). -export([ gmconfig_env/0 , gmconfig_env/1 , gmconfig_env/2 , set_gmconfig_env/1 , default_gmconfig_env/0 ]). -ifdef(TEST). -export([mock_config/0, mock_config/1, mock_system_defaults/0, mock_system_defaults/1, ensure_schema_loaded/0, unmock_schema/0, unmock_config/0]). -endif. -include_lib("kernel/include/logger.hrl"). -type extension() :: string(). %% file extension (without leading dot) -type decoder_return() :: config_tree() | {ok, config_tree()} | {error, any()}. -type decoder_fun() :: fun( (binary()) -> decoder_return() ). -type gmconfig() :: #{ os_env_prefix => string() , config_file_basename => string() | 'undefined' , config_file_os_env => string() | 'undefined' , config_file_search_path => [string() | fun(() -> string())] , config_plain_args => string() | 'undefined' , system_suffix => string() , config_formats => #{ extension() => decoder_fun() } , schema => string() | map() | fun(() -> map())}. -type basic_type() :: number() | binary() | boolean(). -type basic_or_list() :: basic_type() | [basic_type()]. -type config_tree() :: [{binary(), config_tree() | basic_or_list()}]. %% -type env_key() :: atom() | list(). -type config_key() :: binary() | [binary()]. -type find_opts() :: [user_config | schema_default | {env, atom(), atom()} | {value, any()}]. -export_type([ gmconfig/0 , find_opts/0 ]). -ifdef(TEST). mock_config() -> mock_config(#{}). mock_config(Cfg) -> ensure_schema_loaded(), store(Cfg, _Notify = false, _Mode = silent). unmock_config() -> gmconfig_schema_utils:clear(), ok. unmock_schema() -> gmconfig_schema_utils:clear(), ok. mock_system_defaults() -> mock_config(), load_system_defaults(silent). mock_system_defaults(Config) -> ensure_schema_loaded(), load_system_defaults(silent), mock_config(Config). -endif. -spec set_gmconfig_env(gmconfig()) -> ok. set_gmconfig_env(Env0) when is_map(Env0) -> Env = maps:merge(default_gmconfig_env(), Env0), persistent_term:put({?MODULE, gmconfig_env}, Env). -spec gmconfig_env() -> gmconfig(). gmconfig_env() -> persistent_term:get({?MODULE, gmconfig_env}, default_gmconfig_env()). -spec gmconfig_env(atom()) -> any(). gmconfig_env(Key) -> gmconfig_env(Key, undefined). gmconfig_env(Key, Default) -> maps:get(Key, gmconfig_env(), Default). search_path() -> search_path(config_file). search_path(Kind) -> Key = case Kind of config_file -> config_file_search_path; system_defaults -> system_defaults_search_path end, case gmconfig_env(Key, undefined) of undefined -> []; Path0 when is_list(Path0) -> lists:map( fun(F) when is_function(F, 0) -> F(); (D) when is_list(D) -> D end, Path0) end. default_gmconfig_env() -> #{ os_env_prefix => "GM" , config_file_basename => "gmconfig" , config_file_os_env => undefined , config_file_search_path => ["."] , config_formats => #{ "json" => fun json_decode/1 , "eterm" => fun eterm_consult/1 } , config_plain_args => undefined , system_defaults_search_path => [fun setup:data_dir/0] , system_suffix => "" }. %% This function is similar to application:get_env/2, except %% 1. It uses the setup:get_env/2 function, which supports a number %% of useful variable expansions (see the setup documentation) %% 2. It supports a hierarchical key format, [A,B,...], where each %% part of the key represents a level in a tree structure. %% Example: %% if get_env(A, a) returns {ok, {a, [{1, foo}, {2, bar}]}}, or %% {ok, [{a, [{1, foo}, {2, bar}]}]}, then %% get_env(A, [a,1]) will return {ok, foo} -spec get_env(atom(), atom() | list()) -> undefined | {ok, any()}. get_env(App, [H|T]) -> case setup:get_env(App, H) of {ok, V} -> get_env_l(T, V); undefined -> undefined end; get_env(App, K) when is_atom(K) -> setup:get_env(App, K). get_env(App, K, Default) -> case get_env(App, K) of {ok, V} -> V; undefined -> Default end. get_env_l([], V) -> {ok, V}; get_env_l([H|T], [_|_] = L) -> case lists:keyfind(H, 1, L) of {_, V} -> get_env_l(T, V); false -> undefined end; get_env_l(_, _) -> undefined. -spec user_config() -> config_tree(). user_config() -> pt_get_config(). config_value(CfgKey, App, Env, Default) -> {ok, Value} =find_config(CfgKey, [ user_config , {env, App, Env} , schema_default , {value, Default} ]), Value. %%% ==================================================================================== %%% Config lookup API %%% %%% These are the preferred functions for config data lookup get_config(CfgKey) -> get_config(CfgKey, [user_config, schema_default]). get_config(CfgKey, Path) -> case find_config(CfgKey, Path) of {ok, Value} -> Value; undefined -> error(expected_value, [CfgKey, Path]) end. find_config(CfgKey) -> find_config(CfgKey, [user_config, schema_default]). find_config(CfgKey, [H|T]) -> case find_config_(CfgKey, H) of undefined -> find_config(CfgKey, T); {ok,_} = Ok -> Ok end; find_config(_, []) -> undefined. find_config_(K, user_config ) -> user_map(K); find_config_(_, {env, App, EnvKey}) -> get_env(App, EnvKey); find_config_(K, schema_default ) -> schema_default(K); find_config_(_, {value, V} ) -> {ok, V}. %%% ==================================================================================== %%% Merging config maps %%% %%% This function implements a deep map merge, ensuring that sub-maps also get merged. -spec merge_config_maps(map(), map()) -> map(). merge_config_maps(A, B) -> {A1, B1} = maps:fold( fun(K, V, {Ca, Cb}) when is_map(V), is_map(map_get(K, Cb)) -> {Ca#{K := merge_config_maps(V, map_get(K, Cb))}, maps:remove(K, Cb)}; (_, _, Acc) -> Acc end, {A, B}, A), maps:merge(A1, B1). %% The user_map() functions are equivalent to user_config(), but %% operate on a tree of maps rather than a tree of {K,V} tuples. %% Actually, the user_map() data is the original validated object, %% which is then transformed to the Key-Value tree used in user_config(). -spec user_map() -> map(). user_map() -> pt_get_config(). -spec user_map([any()] | any()) -> {ok, any()} | undefined. user_map(Key) when is_list(Key) -> M = user_map(), case maps:find(Key, M) of {ok, _} = Ok -> Ok; error -> nested_map_get(Key, M) end; user_map(Key) -> case maps:find(Key, user_map()) of {ok, _} = Ok -> Ok; error -> undefined end. nested_map_get([], V) -> {ok, V}; nested_map_get([H|T], M) when is_map(M) -> case maps:find(H, M) of {ok, M1} when is_map(M1); is_list(M1) -> nested_map_get(T, M1); {ok, V} when T == [] -> {ok, V}; _ -> undefined end; nested_map_get([H|T], L) when is_list(L) -> case lists_map_key_find(H, L) of {ok, V} when is_map(V); is_list(V) -> nested_map_get(T, V); {ok, V} when T == [] -> {ok, V}; error -> undefined end. lists_map_key_find({K,V,Then} = Pat, [#{} = H|T]) -> case maps:find(K, H) of {ok, V} -> maps:find(Then, H); {ok, _} -> lists_map_key_find(Pat, T); error -> lists_map_key_find(Pat, T) end; lists_map_key_find(K, [#{} = H|T]) -> case maps:find(K, H) of {ok, _} = Ok -> Ok; error -> lists_map_key_find(K, T) end; lists_map_key_find(K, [{K, V}|_]) -> {ok, V}; lists_map_key_find(_, []) -> error. schema() -> case pt_get_schema(undefined) of undefined -> load_schema(), pt_get_schema(); S -> S end. pt_get_schema() -> gmconfig_schema_utils:get_schema(). pt_get_schema(Default) -> gmconfig_schema_utils:get_schema(Default). pt_set_schema(Schema) -> gmconfig_schema_utils:set_schema(Schema). pt_get_config() -> gmconfig_schema_utils:get_config(). pt_set_config(Config) -> gmconfig_schema_utils:set_config(Config). schema(Key) -> gmconfig_schema_utils:schema(Key). schema(Key, Schema) -> gmconfig_schema_utils:schema(Key, Schema). schema_keys() -> schema_keys([]). schema_keys(Path) -> case schema(Path) of undefined -> undefined; {ok, Map} -> just_schema_keys(Map) end. just_schema_keys(#{<<"properties">> := Ps}) -> maps:fold(fun(K, V, Acc) -> Acc#{K => just_schema_keys(V)} end, #{}, Ps); just_schema_keys(#{<<"patternProperties">> := Ps}) -> maps:fold(fun(K, V, Acc) -> Acc#{{'$pat', K} => just_schema_keys(V)} end, #{}, Ps); just_schema_keys(#{<<"type">> := <<"array">>, <<"items">> := Items}) -> case Items of #{<<"type">> := <<"object">>} -> [just_schema_keys(Items)]; #{<<"type">> := T} -> [binary_to_atom(T, utf8)]; #{<<"pattern">> := _} -> [string] end; just_schema_keys(#{<<"oneOf">> := List}) -> #{<<"oneOf">> => lists:foldr( fun(Alt, Acc) -> case just_schema_keys(Alt) of [] -> [maps:fold( fun(K, #{<<"type">> := T}, Acc1) -> Acc1#{K => binary_to_atom(T, utf8)}; (_, _, Acc1) -> Acc1 end, #{}, Alt) | Acc]; Other -> [Other|Acc] end end, [], List)}; just_schema_keys(#{<<"type">> := T}) -> binary_to_atom(T, utf8); just_schema_keys(#{properties := Ps}) -> maps:fold(fun(K, V, Acc) -> Acc#{K => just_schema_keys(V)} end, #{}, Ps); just_schema_keys(#{patternProperties := Ps}) -> maps:fold(fun(K, V, Acc) -> Acc#{{'$pat', K} => just_schema_keys(V)} end, #{}, Ps); just_schema_keys(#{type := array, items := Items}) -> case Items of #{type := object} -> [just_schema_keys(Items)]; #{type := T} -> [T]; #{pattern := _} -> [string] end; just_schema_keys(#{oneOf := List}) -> #{oneOf => lists:foldr( fun(Alt, Acc) -> case just_schema_keys(Alt) of [] -> [maps:fold( fun(K, #{type := T}, Acc1) -> Acc1#{K => T}; (_, _, Acc1) -> Acc1 end, #{}, Alt) | Acc]; Other -> [Other|Acc] end end, [], List)}; just_schema_keys(#{type := T}) -> T; just_schema_keys(_) -> []. schema_default(Path) when is_list(Path) -> schema_default(Path, schema()). schema_default(Path, Schema) -> case schema(Path, Schema) of undefined -> undefined; {ok, Tree} -> case schema_default_(Tree) of undefined -> undefined; Res -> {ok, Res} end end. schema_default_(#{<<"type">> := <<"object">>, <<"properties">> := Props}) -> maps:map(fun(_, #{<<"type">> := <<"object">>} = PP) -> schema_default_(PP); (_, #{<<"type">> := <<"array">>, <<"default">> := Def}) -> Def; (_, #{<<"type">> := <<"array">>, <<"items">> := Items}) -> [schema_default_(Items)]; (_, #{<<"default">> := Def}) -> Def; (_, _) -> undefined end, Props); schema_default_(#{<<"type">> := <<"array">>, <<"default">> := Def}) -> Def; schema_default_(#{<<"type">> := <<"array">>, <<"items">> := Items}) -> [schema_default_(Items)]; schema_default_(#{<<"default">> := Def}) -> Def; schema_default_(#{type := <<"object">>, properties := Props}) -> maps:map(fun(_, #{<<"type">> := <<"object">>} = PP) -> schema_default_(PP); (_, #{type := array, default := Def}) -> Def; (_, #{type := array, items := Items}) -> [schema_default_(Items)]; (_, #{default := Def}) -> Def; (_, _) -> undefined end, Props); schema_default_(#{type := array, default := Def}) -> Def; schema_default_(#{type := array, items := Items}) -> [schema_default_(Items)]; schema_default_(#{default := Def}) -> Def; schema_default_(_) -> undefined. load_user_config() -> load_user_config(silent). load_user_config(Mode) when Mode =:= check; Mode =:= silent; Mode =:= report -> case config_file() of undefined -> info_msg(Mode, "No config file specified; using default settings~n", []), ok; F -> info_msg(Mode, "Reading config file ~s~n", [F]), do_load_user_config(F, store, Mode) end. load_config_file(File) -> load_config_file(File, report). load_config_file(File, Mode) when Mode =:= check; Mode =:= silent; Mode =:= report -> do_load_user_config(File, store, Mode). apply_os_env() -> Pfx = os_env_prefix(), ConfigMap = pt_get_config(), case apply_os_env(Pfx, schema(), ConfigMap) of NewConfig when is_map(NewConfig) -> pt_set_config(NewConfig), NewConfig; Other -> Other end. os_env_prefix() -> gmconfig_env(os_env_prefix, "GM"). %% Plugin API version, using plugin schema and config. %% The plugin API might decide to publish a specific event... apply_os_env(Pfx, Schema, ConfigMap) -> %% We sort on variable names to allow specific values to override object %% definitions at a higher level (e.g. GM__MEMPOOL followed by GM__MEMPOOL__TX_TTL) %% Note that all schema name parts are converted to uppercase. try Names = lists:keysort(1, schema_key_names(Pfx, Schema)), error_logger:info_msg("OS env config: ~p~n", [Names]), Map = lists:foldl( fun({_Name, Key, Value}, Acc) -> Value1 = coerce_type(Key, Value, Schema), update_map(to_map(Key, Value1), Acc) end, #{}, Names), error_logger:info_msg("Map for OS env config: ~p~n", [Map]), if map_size(Map) > 0 -> update_config_(Map, ConfigMap, Schema, report); true -> no_change end catch error:E:ST -> error_logger:info_msg("CAUGHT error:~p / ~p~n", [E, ST]), error(E) end. process_plain_args() -> case gmconfig_env(config_plain_args, undefined) of undefined -> ok; Str -> PlainArgs = init:get_plain_arguments(), Schema = schema(), Map = process_plain_args_(PlainArgs, Str, schema(), #{}), ?LOG_INFO("Map from plain args: ~p", [Map]), if map_size(Map) > 0 -> update_config_(Map, pt_get_config(), Schema, report); true -> no_change end end. process_plain_args_([Tag, K, V | Rest], Tag, Schema, Map) -> Path = plain_path_arg(K), Value = coerce_type(Path, V, Schema), Map1 = update_map(to_map(Path, Value), Map), process_plain_args_(Rest, Tag, Schema, Map1); process_plain_args_([_ | T], Tag, Schema, Map) -> process_plain_args_(T, Tag, Schema, Map); process_plain_args_([], _, _, Map) -> Map. plain_path_arg(Str) -> re:split(Str, <<"__">>, [{return, binary}]). to_map(K, V) -> to_map(K, V, #{}). to_map([K], Val, M) -> M#{K => Val}; to_map([H|T], Val, M) -> SubMap = maps:get(H, M, #{}), M#{H => to_map(T, Val, SubMap)}. coerce_type(Key, Value, Schema) -> case schema(Key, Schema) of {ok, #{<<"type">> := Type}} -> case Type of <<"integer">> -> to_integer(Value); <<"string">> -> to_string(Value); <<"boolean">> -> to_bool(Value); <<"array">> -> json:decode(list_to_binary(Value)); <<"object">> -> json:decode(list_to_binary(Value)) end; _ -> error({unknown_key, Key}) end. to_integer(I) when is_integer(I) -> I; to_integer(L) when is_list(L) -> list_to_integer(L); to_integer(B) when is_binary(B) -> binary_to_integer(B). to_string(L) when is_list(L) -> list_to_binary(L); to_string(B) when is_binary(B) -> B. to_bool("true") -> true; to_bool("false") -> false; to_bool(B) when is_boolean(B) -> B; to_bool(Other) -> error({expected_boolean, Other}). schema_key_names(Prefix, Schema) -> case Schema of #{<<"$schema">> := _, <<"properties">> := Props} -> schema_key_names(Prefix, [], Props, []); _ -> [] end. schema_key_names(NamePfx, KeyPfx, Map, Acc0) when is_map(Map) -> maps:fold( fun(SubKey, SubMap, Acc) -> NamePfx1 = NamePfx ++ "__" ++ string:to_upper(binary_to_list(SubKey)), KeyPfx1 = KeyPfx ++ [SubKey], EnvKey = unhyphenate(NamePfx1), Acc1 = case os:getenv(EnvKey) of false -> Acc; Value -> [{EnvKey, KeyPfx1, Value} | Acc] end, case maps:find(<<"properties">>, SubMap) of error -> Acc1; {ok, Props} -> schema_key_names(NamePfx1, KeyPfx1, Props, Acc1) end end, Acc0, Map). %% Unfortunately, the config schema contains some names with hyphens in them. %% Since hyphens aren't allowed in OS environment names, we replace them with underscores. %% This should be safe, since we DO NOT stupidly have names that differ only on '-' v '_'. unhyphenate(Str) -> re:replace(Str, <<"\\-">>, <<"_">>, [global, {return, list}]). check_config(F) -> do_load_user_config(F, check, check). data_dir(Name) when is_atom(Name) -> filename:join([setup:data_dir(), Name]). config_file() -> case command_line_config_file() of undefined -> default_config_file(); F -> F end. command_line_config_file() -> case init:get_argument('-config') of {ok, [[F]]} -> F; _ -> undefined end. default_config_file() -> case gmconfig_env(config_file_os_env, undefined) of undefined -> search_default_config(); E -> case os:getenv(E) of false -> search_default_config(); F -> F end end. search_default_config() -> case gmconfig_env(config_file_basename, undefined) of undefined -> undefined; Basename -> Dirs = search_path(), SystemSuffix = get_system_suffix(), ExtPattern = extension_pattern(), Fname = Basename ++ SystemSuffix ++ ExtPattern, search_for_config_file(Dirs, Fname) end. config_formats() -> gmconfig_env(config_formats). extension_pattern() -> Exts = maps:keys(config_formats()), lists:flatten([".{", intersperse(Exts),"}"]). intersperse([H|T]) -> [H | [[",", X] || X <- T]]. search_for_config_file(Dirs, FileWildcard) -> lists:foldl( fun(D0, undefined) -> D = to_list_string(D0), error_logger:info_msg("Searching for config file ~s " "in directory ~s~n", [FileWildcard, D]), case filelib:wildcard(FileWildcard, D) of [] -> undefined; [F|_] -> filename:join(D, F) end; (_, Acc) -> Acc end, undefined, Dirs). to_list_string(S) when is_binary(S) -> binary_to_list(S); to_list_string(S) when is_list(S) -> binary_to_list(iolist_to_binary(S)). do_load_user_config(F, Action, Mode) -> {Ext, Decoder} = pick_decoder(F), case Action of store -> store(read_file(F, Ext, Decoder, Mode), Mode); check -> check_config_(catch read_file(F, Ext, Decoder, Mode)) end. pick_decoder(F) -> "." ++ Ext = filename:extension(F), {Ext, maps:get(Ext, config_formats())}. store(Vars, Mode) when is_map(Vars) -> case pt_get_config() of Map when map_size(Map) == 0 -> check_validation([validate_(Vars)], [Vars], set_config_value, report), pt_set_config(Vars); Map -> ?LOG_DEBUG("Existing config, updating ...", []), update_config(Vars, Map, Mode) end; store([Vars], Mode) when is_map(Vars) -> store(Vars, Mode). check_config_({yamerl_exception, _StackTrace} = Error) -> {error, Error}; check_config_({'EXIT', Reason}) -> ShortError = pp_error(Reason), {error, ShortError}; check_config_([Vars]) -> {ok, {Vars, to_tree(Vars)}}. pp_error({validation_failed, _}) -> validation_failed; pp_error(Other) -> Other. pp_error_({error, {schema_file_not_found, Schema}}, Mode) -> error_format("Schema not found : ~s", [Schema], Mode); pp_error_({error, [{data_invalid, _Schema, Type, Value, Pos}]}, Mode) -> PosStr = pp_pos(Pos), ValStr = pp_val(Value), TypeStr = pp_type(Type), case Mode of check -> io:format("Validation failed~n" "Position: ~s~n" "Value : ~s~n" "Reason : ~s~n", [PosStr, ValStr, TypeStr]); report -> error_format("Validation failed, Pos: ~s~n" "Value: ~s~n" "Reason: ~s", [PosStr, ValStr, TypeStr], Mode) end; pp_error_({error, [{schema_invalid, Section, Description}]}, Mode) -> SchemaStr = schema_string(Section, Mode), error_format("Reading schema failed~n" "Section: ~n~s~n" "Reason: ~p~n", [SchemaStr, Description], Mode). silent_as_report(silent) -> report; silent_as_report(Mode ) -> Mode. schema_string(Schema, Mode) -> JSONSchema = json_encode(Schema), case Mode of check -> json:format(JSONSchema, #{indent => 2}); report -> JSONSchema end. json_encode(J) -> iolist_to_binary(json:encode(J)). error_format(Fmt, Args, check) -> io:format(Fmt, Args); error_format(Fmt, Args, report) -> Str = io_lib:format(Fmt, Args), Parts = re:split(Str, <<"\n">>), Out = iolist_to_binary( [hd(Parts) | [[" | ", P] || P <- tl(Parts)]]), Out = re:replace(Str, <<"\n">>, <<" | ">>, [global, {return, binary}]), ?LOG_ERROR("~s", [Out]). pp_pos([H | T]) -> [to_string(H) | [pp_pos_(X) || X <- T]]. pp_pos_(I) when is_integer(I) -> ["[", integer_to_list(I), "]"]; pp_pos_(S) when is_binary(S) -> ["/", S]. pp_val(I) when is_integer(I) -> integer_to_list(I); pp_val(S) when is_binary(S) -> ["\"", S, "\""]; pp_val(X) -> try schema_string(X, report) catch error:_ -> io_lib:fwrite("~w", [X]) end. pp_type(data_invalid) -> "Data invalid"; pp_type(missing_id_field) -> "Missing ID field"; pp_type(missing_required_property) -> "Missing required property"; pp_type(no_match ) -> "No match"; pp_type(no_extra_properties_allowed) -> "No extra properties allowed"; pp_type(no_extra_items_allowed) -> "No extra items allowed"; pp_type(not_allowed) -> "Not allowed"; pp_type(not_unique) -> "Not unique"; pp_type(not_in_enum) -> "Not in enum"; pp_type(not_in_range) -> "Not in range"; pp_type(not_divisible) -> "Not divisible"; pp_type(wrong_type) -> "Wrong type"; pp_type(wrong_size) -> "Wrong size"; pp_type(wrong_length) -> "Wrong length"; pp_type(wrong_format) -> "Wrong format"; pp_type(too_many_properties) -> "Too many properties"; pp_type(too_few_properties) -> "Too few properties"; pp_type(all_schemas_not_valid) -> "The 'allOf' requirement is not upheld"; pp_type(any_schemas_not_valid) -> "The 'anyOf' requirement is not upheld"; pp_type(not_multiple_of) -> "Not an instance of 'multipleOf'"; pp_type(not_one_schema_valid) -> "The 'oneOf' requirement is not upheld"; pp_type(not_schema_valid) -> "The 'not' requirement is not upheld"; pp_type(wrong_not_schema) -> "Wrong not schema"; pp_type(external) -> "External"; pp_type(Other) -> io_lib:fwrite("~w", [Other]). to_tree(Vars) -> to_tree_(expand_maps(Vars)). expand_maps(M) when is_map(M) -> [{K, expand_maps(V)} || {K, V} <- maps:to_list(M)]; expand_maps(L) when is_list(L) -> [expand_maps(E) || E <- L]; expand_maps(E) -> E. to_tree_(L) when is_list(L) -> lists:flatten([to_tree_(E) || E <- L]); to_tree_({K, V}) -> {K, to_tree_(V)}; to_tree_(E) -> E. silent_update_config(Map) -> update_config(Map, _Notify = false, silent). update_config(Map) when is_map(Map) -> update_config(Map, report). update_config(Map, Mode) when is_map(Map) -> ConfigMap = pt_get_config(), update_config(Map, ConfigMap, Mode). update_config(Map, ConfigMap, Mode) -> Schema = pt_get_schema(), ConfigMap1 = update_config_(Map, ConfigMap, Schema, Mode), ?LOG_DEBUG("New config: ~p", [ConfigMap1]), pt_set_config(ConfigMap1), ok. export_config() -> Config = pt_get_config(), JSON = json:format(Config, #{indent => 2}), TS = calendar:system_time_to_rfc3339(erlang:system_time(second)), File = filename:join(setup:log_dir(), "user_config-" ++ TS ++ ".json"), file:write_file(File, JSON). -spec delete_config_value(config_key()) -> boolean(). delete_config_value(Key) when is_binary(Key) -> delete_config_value([Key]); delete_config_value(Path) when is_list(Path) -> Config = pt_get_config(), case delete_(Path, Config) of Config1 when Config1 =/= Config -> pt_set_config(Config1), true; _ -> false end. delete_([H], Config) when is_map_key(H, Config) -> maps:remove(H, Config); delete_([H|T], Map) when T =/= [], is_map_key(H, Map) -> Map#{H := delete_(T, maps:get(H, Map))}; delete_(_, C) -> C. set_config_value(Path, Value) -> ConfigMap = pt_get_config(), NewConfig = set_config_value(Path, ConfigMap, Value), check_validation([validate_(NewConfig)], [NewConfig], set_config_value, report), pt_set_config(NewConfig). set_config_value([K], Map, Value) when is_map(Map) -> Map#{K => Value}; set_config_value([H|T], Map, Value) when is_map(Map) -> case maps:find(H, Map) of {ok, Sub} when is_map(Sub) -> Map#{H := set_config_value(T, Sub, Value)}; _ -> Map#{H => set_config_value(T, #{}, Value)} end. %% Checks if a given config key (list of binary keys corresponding to the GM %% config schema) is already configured. If not, the suggested value is used. suggest_config(Key, Value) -> case find_config(Key, [user_config]) of {ok, _} -> {error, already_configured}; undefined -> Map = kv_to_config_map(Key, Value), update_config(Map), ok end. kv_to_config_map([H], V) -> #{H => V}; kv_to_config_map([H|T], V) -> #{H => kv_to_config_map(T, V)}. update_config_(Map, _ConfigMap, Schema, Mode) when Mode =:= check; Mode =:= silent; Mode =:= report -> NewConfig = gmconfig_schema_utils:update_config(Map), %% NewConfig = update_map(Map, ConfigMap), ?LOG_DEBUG("NewConfig = ~p", [NewConfig]), %% Note: We must validate the *resulting* config, since some validation %% steps will require the full structure (e.g. multiple required fields in %% the original config, which should not have to be included in the update) check_validation([validate_(NewConfig, Schema)], [NewConfig], update_config, Mode), NewConfig. update_map(With, Map) when is_map(With), is_map(Map) -> maps:fold( fun(K, V, Acc) -> case maps:find(K, Acc) of {ok, Submap} when is_map(Submap) -> Acc#{K => update_map(V, Submap)}; {ok, _} -> Acc#{K => V}; error -> Acc#{K => V} end end, Map, With). read_file(F, Type, Decoder, Mode) -> case setup_file:read_file(F) of {ok, Bin} -> validate( try_decode_bin(Bin, Decoder, Type, Mode), F, Mode); {error, Reason} -> error_msg(Mode, "Read error ~s - ~p", [F, Reason]), error({read_error, F, Reason}) end. json_decode(Str) when is_list(Str) -> json:decode(iolist_to_binary(Str)); json_decode(Bin) when is_binary(Bin) -> json:decode(Bin). eterm_consult(Bin) -> case setup_file:consult_binary(Bin) of {ok, [Map]} when is_map(Map) -> {ok, normalize_config(Map)}; {ok, Other} -> error({unknown_data, Other}); {error, _} = Error -> Error end. normalize_config(Map) when is_map(Map) -> try json:decode(iolist_to_binary(json:encode(Map))) catch error:E -> error({cannot_normalize, E, Map}) end. try_decode_bin(Bin, Decoder, Fmt, Mode) -> try decode_bin(Bin, Decoder) catch error:E:T -> error_msg(Mode, "CAUGHT for ~p: ~p / ~p", [Fmt, E, T]), error(E) end. decode_bin(Str, Decoder) when is_list(Str) -> decode_bin(iolist_to_binary(Str), Decoder); decode_bin(Bin, Decoder) when is_binary(Bin), is_function(Decoder, 1) -> case Decoder(Bin) of {ok, Map} when is_map(Map) -> Map; Map when is_map(Map) -> Map; {error, E} -> error(E); Other -> error({bad_decoder_return, Other}) end. validate(JSON, F, Mode) when is_map(JSON) -> check_validation([validate_(JSON)], JSON, F, Mode). vinfo(Mode, Res, F) -> case Res of {ok, _} -> info_report(Mode, [{validation, F}, {result, Res}]); {error, Errors} -> Mode1 = silent_as_report(Mode), [pp_error_(E, Mode1) || E <- Errors], ok end. info_report(report, Info) -> error_logger:info_report(Info); info_report(_, _) -> ok. info_msg(report, Fmt, Args) -> error_logger:info_msg(Fmt, Args); info_msg(_, _,_ ) -> ok. error_msg(report, Fmt, Args) -> error_logger:error_msg(Fmt, Args); error_msg(_, _, _) -> ok. check_validation(Res, _JSON, F, Mode) -> case lists:foldr( fun({ok, M}, {Ok,Err}) when is_map(M) -> {[M|Ok], Err}; (Other, {Ok,Err}) -> {Ok, [Other|Err]} end, {[], []}, Res) of {Ok, []} -> vinfo(Mode, {ok, Ok}, F), Ok; {_, Errors} -> vinfo(Mode, {error, Errors}, F), erlang:error(validation_failed) end. validate_(JSON) -> Schema = ensure_schema_loaded(), validate_(JSON, Schema). validate_(JSON, Schema) -> _ = gmconfig_schema_utils:valid(JSON, Schema), {ok, JSON}. load_main_config_schema() -> _ = load_schema(), ?LOG_INFO("Loaded config schema", []), ok. load_system_defaults() -> load_system_defaults(report). load_system_defaults(Mode) -> case gmconfig_env(config_file_basename, undefined) of undefined -> ok; Basename -> SystemSuffix = get_system_suffix(), Fname = Basename ++ "_defaults" ++ SystemSuffix ++ ".{yaml,json}", Path = search_path(system_defaults), case search_for_config_file(Path, Fname) of undefined -> ok; ConfigFile -> ?LOG_DEBUG("Loading system defaults from ~s", [ConfigFile]), load_config_file(ConfigFile, Mode) end end. get_system_suffix() -> case init:get_argument('-system') of error -> Pfx = os_env_prefix(), case os:getenv(Pfx ++ "_SYSTEM") of false -> ""; Suffix -> "_" ++ Suffix end; {ok, [[Suffix]]} -> "_" ++ Suffix end. ensure_schema_loaded() -> case pt_get_schema(undefined) of undefined -> Res = load_schema(), %% ?LOG_INFO("Schema Res = ~p", [Res]), Res; S -> S end. load_schema() -> JSON = gmconfig_schema(), Decode = maps:get("json", config_formats()), Schema = decode_bin(JSON, Decode), pt_set_schema(Schema), Schema. gmconfig_schema() -> case gmconfig_env(schema, #{}) of File when is_list(File) -> json_consult(File); Json when is_map(Json) -> Json; F when is_function(F, 0) -> F() end. json_consult(F) -> Decode = maps:get("json", config_formats()), case setup_file:read_file(F) of {ok, Bin} -> decode_bin(Bin, Decode); {error, Reason} -> ?LOG_ERROR("Read error ~s - ~p", [F, Reason]), error({read_error, F, Reason}) end.