diff --git a/.github/scripts/otp-compliance.es b/.github/scripts/otp-compliance.es index 56128bf6c99f..a34b4fc618c7 100755 --- a/.github/scripts/otp-compliance.es +++ b/.github/scripts/otp-compliance.es @@ -61,10 +61,14 @@ test_originator_Ericsson/1, test_versionInfo_not_empty/1, test_package_hasFiles/1, test_project_purl/1, test_packages_purl/1, test_download_location/1, test_package_relations/1, test_has_extracted_licenses/1, - test_vendor_packages/1, test_erts/1%%, + test_vendor_packages/1, test_erts/1, test_download_vendor_location/1 %% test_copyright_format/1, test_files_licenses/1, ]). +%% openvex tests +-export([test_openvex_branched_otp_tree/0, + test_openvex_branched_otp_tree_idempotent/0]). + -define(default_classified_result, "scan-result-classified.json"). -define(default_scan_result, "scan-result.json"). -define(diff_classified_result, "scan-result-diff.json"). @@ -82,7 +86,8 @@ ~"referenceCategory" => ~"PACKAGE-MANAGER", ~"referenceLocator" => ~"pkg:github/erlang/otp", ~"referenceType" => ~"purl"}). - +-define(VexPath, ~"vex/"). +-define(ErlangPURL, "pkg:github/erlang/otp"). %% Add more relations if necessary. -type spdx_relations() :: #{ 'DOCUMENTATION_OF' => [], @@ -220,8 +225,46 @@ cli() -> > .github/scripts/otp-compliance.es sbom vendor --sbom-file otp.spdx.json """, arguments => [ sbom_option()], - handler => fun sbom_vendor/1} + handler => fun sbom_vendor/1}, + + "osv-scan" => + #{ help => + """ + Performs vulnerability scanning on vendor libraries + + Example: + + > .github/scripts/otp-compliance.es sbom osv-scan --version maint-28 + """, + arguments => [ versions_file(), fail_option() ], + handler => fun osv_scan/1} }}, + "vex" => + #{ + help => """ + Create VEX statements + Update CVEs and generate OpenVex Statements + """, + commands => + #{"init" => + #{ help => + """ + Initialise an openvex file. + """, + arguments => [ input_option(~"make/openvex.table"), branch_option(), vex_path_option()], + handler => fun init_openvex/1}, + "run" => + #{ help => + """ + Updates an openvex file. + """, + arguments => [ input_option(~"make/openvex.table"), branch_option(), vex_path_option()], + handler => fun run_openvex/1}, + + "test" => + #{handler => fun test_openvex/1} + } + }, "explore" => #{ help => """ Explore license data. @@ -320,6 +363,19 @@ sbom_option() -> default => "bom.spdx.json", long => "-sbom-file"}. +versions_file() -> + #{name => version, + type => binary, + long => "-version"}. + +fail_option() -> + #{name => fail_if_cve, + type => boolean, + default => false, + long => "-fail_if_cve"}. +%% useful for pull requests since we do not want to +%% add Github Security per found CVE on each PR. + ntia_checker() -> #{name => ntia_checker, type => boolean, @@ -368,6 +424,20 @@ base_file(DefaultFile) -> default => DefaultFile, long => "-base-file"}. +branch_option() -> + #{name => branch, + type => binary, + required => true, + short => $b, + long => "-branch"}. + +vex_path_option() -> + #{name => vex_path, + type => binary, + required => false, + default => ?VexPath, + help => "Path to folder containing openvex statements, e.g., `vex/`", + long => "-vex-path"}. %% %% Commands @@ -498,7 +568,7 @@ fix_project_purl(#{~"referenceLocator" := RefLoc}=Purl, #{ ~"documentDescribes" Packages1= [case maps:get(~"SPDXID", Package) of RootProject -> VersionInfo = maps:get(~"versionInfo", Package), - Purl1 = Purl#{~"referenceLocator" := <>}, + Purl1 = Purl#{~"referenceLocator" := <>}, Package#{ ~"externalRefs" => [Purl1]}; _ -> Package @@ -1297,6 +1367,267 @@ generate_vendor_purl(Package) -> [create_externalRef_purl(Description, <>)] end. +osv_scan(#{version := <<"maint">>}=Opt) -> + VersionNumber = erlang:list_to_binary(string:trim(os:cmd("cat OTP_VERSION | cut -d. -f1"))), + osv_scan(Opt#{version := <<"maint-", VersionNumber/binary>>}); +osv_scan(#{version := Version, + fail_if_cve := FailIfCVEFound}) -> + application:ensure_all_started([ssl, inets]), + _ = valid_scan_branches(Version), + OSVQuery = vendor_by_version(Version), + + io:format("[OSV] Information sent~n~s~n", [json:format(OSVQuery)]), + + OSV = json:encode(OSVQuery), + + Format = "application/x-www-form-urlencoded", + URI = "https://api.osv.dev/v1/querybatch", + Content = {URI, [], Format, OSV}, + Result = httpc:request(post, Content, [], []), + Vulns = + case Result of + {ok,{{_, 200,_}, _Headers, Body}} -> + #{~"results" := OSVResults} = json:decode(erlang:list_to_binary(Body)), + [{NameVersion, [Id || #{~"id" := Id} <- Ids]} || + NameVersion <- osv_names(OSVQuery) && #{~"vulns" := Ids} <- OSVResults]; + {error, Error} -> + {error, [URI, Error]} + end, + + %% Substract from Vulns the OpenVex statements that dealt with them + %% Result Vulns1 are vulnerabilities not yet covered in OpenVex statements + Vulns1 = ignore_vex_cves(Version, Vulns), + + %% vulnerability reporting can fail if new issues appear + FormattedVulns = format_vulnerabilities(Vulns1), + case FailIfCVEFound of + false -> + report_vulnerabilities(FormattedVulns); + true -> + case Vulns1 of + [] -> + report_vulnerabilities(FormattedVulns); + _ -> + Failure = + """ + [Vulnerability] Contact OTP team. + The following CVEs must be checked in OpenVex statements for ~s: + ~s + Please follow instructions from: + https://github.com/erlang/otp/blob/master/HOWTO/SBOM.md#vex + """, + fail(Failure, [Version, FormattedVulns]) + end + end. + +ignore_vex_cves(Branch, Vulns) -> + OpenVex = get_otp_openvex_file(Branch), + OpenVex1 = format_vex_statements(OpenVex), + + case OpenVex1 of + [] -> + []; + _ when is_list(OpenVex1) -> + io:format("Ignoring vulnerabilities already present in OpenVex file.~n~n") + end, + lists:foldl(fun({{Purl, _CommitId}=Package, CVEs}, Acc) -> + %% Ignore commit id when an OpenVEX statement exists. + %% OSV will report a vulnerability as long as Erlang/OTP does not + %% update its vendor.info file for openssl. we can only do this + %% when we actually vendor a different version of openssl, thus + %% the commit ids do not match. instead of basing vendor CVE checks + %% on commit id, if OTP adds an OpenVEX statement in which it claims + %% that there is no vulnerability, then there is no vulnerability. + %% If there is a vulnerability, then OTP must update the vendor file + %% to remove the vulnerability. + CVEsMatches = lists:filtermap(fun ({{PurlX, _}, CVEList}) when Purl == PurlX -> + {true, CVEList}; + (_) -> + false + end, OpenVex1), + case CVEs -- lists:flatten(CVEsMatches) of + [] -> + Acc; + Ls -> + [{Package, Ls} | Acc] + end + end, [], Vulns). + +format_vex_statements(OpenVex) -> + Stmts = maps:get(~"statements", OpenVex, []), + lists:foldl(fun (#{~"vulnerability" := #{~"name":=Name}, + ~"products" := Products}, Acc) -> + Result = + lists:map(fun (#{~"@id" := <<"pkg:github/", Package/binary>>}) -> + {PkgName, VersionPart} = string:take(Package, "@", true, leading), + <<"@", Version/binary>> = VersionPart, + {{<<"github.com/", PkgName/binary>>, Version}, [Name]}; + (_) -> + Acc + end, Products), + Result ++ Acc + end, [], Stmts). + +get_otp_openvex_file(Branch) -> + OpenVexPath = fetch_openvex_filename(Branch), + OpenVexStr = erlang:binary_to_list(OpenVexPath), + GithubURI = "https://raw.githubusercontent.com/erlang/otp/refs/heads/master/" ++ OpenVexStr, + + io:format("Checking OpenVex statements in '~s' from~n'~s'...~n", [OpenVexPath, GithubURI]), + + ValidURI = "curl -I -Lj --silent " ++ GithubURI ++ " | head -n1 | cut -d' ' -f2", + case string:trim(os:cmd(ValidURI)) of + "200" -> + io:format("OpenVex file found.~n~n"), + Command = "curl -LJ " ++ GithubURI ++ " --output " ++ OpenVexStr, + os:cmd(Command, #{ exception_on_failure => true }), + decode(OpenVexStr); + E -> + io:format("[~p] No OpenVex file found.~n~n", [E]), + #{} + end. + +fetch_openvex_filename(Branch) -> + _ = valid_scan_branches(Branch), + Version = case Branch of + ~"master" -> + %% Master corresponds to possible patched versions of OTP_VERSION-1. + VersionNumber = erlang:list_to_integer(string:trim(os:cmd("cat OTP_VERSION | cut -d. -f1"))), + BinVersionNumber = erlang:integer_to_binary(VersionNumber-1), + <<"otp-", BinVersionNumber/binary>>; + <<"maint-", Vers/binary>> -> + <<"otp-", Vers/binary>> + end, + vex_path(Version). + +valid_scan_branches(Branch) -> + case Branch of + ~"master" -> + ok; + <<"maint-", _Vers/binary>> -> + ok; + _ -> + fail("[ERROR] Valid branch names are `master` or `maint-XX`.~n'~s' is neither of them", [Branch]) + end. + +format_vulnerabilities({error, ErrorContext}) -> + {error, ErrorContext}; +format_vulnerabilities(ExistingVulnerabilities) when is_list(ExistingVulnerabilities) -> + lists:map(fun ({{N, _}, Ids}) -> + io_lib:format("- ~s: ~s~n", [N, lists:join(",", Ids)]) + end, ExistingVulnerabilities). + +report_vulnerabilities([]) -> + io:format("[OSV] No new vulnerabilities reported.~n"); +report_vulnerabilities({error, [URI, Error]}) -> + fail("[OSV] POST request to ~p errors: ~p", [URI, Error]); +report_vulnerabilities(FormatVulns) -> + io:format("[OSV] There are existing vulnerabilities:~n~s", [FormatVulns]). + +osv_names(#{~"queries" := Packages}) -> + lists:map(fun osv_names/1, Packages); +osv_names(#{~"package" := #{~"name" := Name }, ~"commit" := Commit}) -> + {Name, Commit}; +osv_names(#{~"package" := #{~"name" := Name }, ~"version" := Version}) -> + {Name, Version}. + + +generate_osv_query(Packages) -> + #{~"queries" => lists:usort(lists:foldl(fun generate_osv_query/2, [], Packages))}. +generate_osv_query(#{~"versionInfo" := Vsn, ~"ecosystem" := Ecosystem, ~"name" := Name}, Acc) -> + Package = #{~"package" => #{~"name" => Name, ~"ecosystem" => Ecosystem}, ~"version" => Vsn}, + [Package | Acc]; +generate_osv_query(#{~"sha" := SHA, ~"downloadLocation" := Location}, Acc) -> + case string:prefix(Location, ~"https://") of + nomatch -> + Acc; + URI -> + Package = #{~"package" => #{~"name" => URI}, ~"commit" => SHA}, + [Package | Acc] + end; +generate_osv_query(_, Acc) -> + Acc. + +%% when we no longer need to maintain maint-27, we can remove +%% this hard-coded commits and versions. +vendor_by_version(~"maint-26") -> + #{~"queries" => + [#{%% v1.2.13 + ~"commit"=> ~"04f42ceca40f73e2978b50e93806c2a18c1281fc", + ~"package"=> #{~"name"=> ~"github.com/madler/zlib"}}, + + #{~"commit"=> ~"915186f6c5c2f5a4638e5cb97ccc23d741521a64", + ~"package"=> #{~"name"=> ~"github.com/asmjit/asmjit"}}, + + #{~"commit"=> ~"e745bad3b1d05b5b19ec652d68abb37865ffa454", + ~"package"=> #{~"name"=> ~"github.com/microsoft/STL"}}, + + #{~"commit"=> ~"844864ac213bdbf1fb57e6f51c653b3d90af0937", + ~"package"=> #{~"name"=> ~"github.com/ulfjack/ryu"}}, + + #{% 3.1.4 + ~"commit"=> ~"01d5e2318405362b4de5e670c90d9b40a351d053", + ~"package"=> #{~"name"=> ~"github.com/openssl/openssl"}}, + + #{% 8.45, not offial but the official sourceforge is not available + ~"commit"=> ~"3934406b50b8c2a4e2fc7362ed8026224ac90828", + ~"package"=> #{~"name"=> ~"github.com/nektro/pcre-8.45"}}, + + #{~"version"=> ~"2.32", + ~"package"=> #{~"ecosystem"=> ~"npm", + ~"name"=> ~"tablesorter"}}, + + #{~"version"=> ~"3.7.1", + ~"package"=> #{~"ecosystem"=> ~"npm", + ~"name"=> ~"jquery"}} + ]}; +vendor_by_version(~"maint-27") -> + #{~"queries" => + [#{ %% v1.2.13 + ~"commit"=> ~"04f42ceca40f73e2978b50e93806c2a18c1281fc", + ~"package"=> #{~"name"=> ~"github.com/madler/zlib"}}, + + #{~"commit"=> ~"a465fe71ab3d0e224b2b4bd0fac69ae68ab9239d", + ~"package"=> #{ ~"name"=> ~"github.com/asmjit/asmjit"}}, + + #{~"commit"=> ~"e745bad3b1d05b5b19ec652d68abb37865ffa454", + ~"package"=> #{~"name"=> ~"github.com/microsoft/STL"}}, + + #{~"commit"=> ~"844864ac213bdbf1fb57e6f51c653b3d90af0937", + ~"package"=>#{~"name"=> ~"github.com/ulfjack/ryu"}}, + + #{ % 3.1.4 + ~"commit"=> ~"01d5e2318405362b4de5e670c90d9b40a351d053", + ~"package"=> #{~"name"=> ~"github.com/openssl/openssl"}}, + + #{% 8.45, not offial but the official sourceforge is not available + ~"commit"=> ~"3934406b50b8c2a4e2fc7362ed8026224ac90828", + ~"package"=> #{ ~"name"=> ~"github.com/nektro/pcre-8.45"}}, + + #{~"version"=> ~"2.32", + ~"package"=> #{~"ecosystem"=> ~"npm", + ~"name"=> ~"tablesorter"}}, + + #{~"version"=> ~"3.7.1", + ~"package"=> #{~"ecosystem"=> ~"npm", + ~"name"=> ~"jquery"}} + ]}; +vendor_by_version(_) -> + VendorSrcFiles = find_vendor_src_files("."), + Packages = generate_vendor_info_package(VendorSrcFiles), + Packages1 = ignore_non_vulnerable_vendors(Packages), + generate_osv_query(Packages1). + +%% OTP only vendors the documentation from wx, so we can ignore +%% any vulnerability. The user should still look into possible +%% issues with wx if they link to it. +non_vulnerable_vendor_packages() -> + [~"wx"]. + +ignore_non_vulnerable_vendors(Packages) -> + lists:filter(fun (#{~"ID" := Id}) -> not lists:member(Id, non_vulnerable_vendor_packages()) + end, Packages). + cleanup_path(<<"./", Path/binary>>) when is_binary(Path) -> Path; cleanup_path(Path) when is_binary(Path) -> Path. @@ -1532,7 +1863,7 @@ test_file(#{sbom_file := SbomFile, ntia_checker := Verification}) -> ok. test_ntia_checker(false, _SbomFile) -> ok; -test_ntia_checker(true, SbomFile) -> +test_ntia_checker(true, SbomFile) -> have_tool("ntia-checker"), Cmd = "sbomcheck --comply ntia --file " ++ SbomFile, io:format("~nRunning: NTIA Compliance Checker~n[~ts]~n", [Cmd]), @@ -1542,7 +1873,7 @@ test_ntia_checker(true, SbomFile) -> cmd(Cmd) -> string:trim(os:cmd(unicode:characters_to_list(Cmd), - #{ exception_on_failure => true })). + #{ exception_on_failure => true })). have_tool(Tool) -> case os:find_executable(Tool) of @@ -1557,27 +1888,27 @@ fail(Fmt, Args) -> test_generator(Sbom) -> io:format("~nRunning: verification of OTP SBOM integrity~n"), ok = project_generator(Sbom), - ok = package_generator(Sbom), + ok = package_generator(Sbom), ok. --define(CALL_TEST_FUNCTIONS(Tests, Sbom), +-define(CALL_TEST_FUNCTIONS(Tests, Sbom), (begin io:format("[~s]~n", [?FUNCTION_NAME]), lists:all(fun (Fun) -> Module = ?MODULE, Result = apply(Module, Fun, [Sbom]), L = length(atom_to_list(Fun)), - io:format("- ~s~s~s~n", [Fun, lists:duplicate(40 - L, "."), Result]), + io:format("- ~s~s~s~n", [Fun, lists:duplicate(40 - L, "."), Result]), ok == Result end, Tests) end)). -project_generator(Sbom) -> +project_generator(Sbom) -> Tests = [test_project_name, test_name, test_creators_tooling, test_spdx_version], - true = ?CALL_TEST_FUNCTIONS(Tests, Sbom), + true = ?CALL_TEST_FUNCTIONS(Tests, Sbom), ok. package_generator(Sbom) -> @@ -1607,6 +1938,7 @@ package_generator(Sbom) -> test_project_purl, test_packages_purl, test_download_location, + test_download_vendor_location, test_package_relations, test_has_extracted_licenses, test_vendor_packages], @@ -1651,7 +1983,6 @@ test_minimum_apps(#{~"documentDescribes" := [ProjectName], ~"packages" := Packag true = lists:all(fun (#{~"SPDXID" := Id, ~"versionInfo" := Version}) -> case lists:keyfind(Id, 1, AppNamesVersion) of {_, TableVersion} -> - io:format("Table ~p AppVersion ~p, ~p~n", [TableVersion, Version, Id]), TableVersion == Version; false -> true @@ -1672,7 +2003,7 @@ root_vendor_packages() -> minimum_vendor_packages() -> %% self-contained root_vendor_packages() ++ - [~"tcl", ~"STL", ~"json-test-suite", ~"openssl", ~"Autoconf", ~"wx", ~"jquery", ~"jquery-tablesorter"]. + [~"tcl", ~"STL", ~"json-test-suite", ~"openssl", ~"Autoconf", ~"wx", ~"jquery", ~"tablesorter"]. test_copyright_not_empty(#{~"packages" := Packages}) -> true = lists:all(fun (#{~"copyrightText" := Copyright}) -> Copyright =/= ~"" end, Packages), @@ -1876,6 +2207,17 @@ test_download_location(#{~"packages" := Packages}) -> true = lists:all(fun (#{~"downloadLocation" := Loc}) -> Loc =/= ~"" end, Packages), ok. +%% vendor location should use https://github.com where possible due to integration with OSV. +%% see generate_osv_query/1. +test_download_vendor_location(#{~"packages" := Packages}) -> + %% update list below if new runtime dependencies without git repo appear. + KnownExcludedNames = [~"Autoconf", ~"tcl", ~"Unicode Character Database"], + true = lists:all(fun (#{~"downloadLocation" := Loc, ~"name" := Name}) -> + lists:member(Name, KnownExcludedNames) + orelse string:prefix(Loc, ~"https://github.com") =/= nomatch + end, Packages), + ok. + test_package_hasFiles(#{~"packages" := Packages}) -> %% test files are not repeated AllFiles = lists:foldl(fun (#{~"hasFiles" := FileIds}, Acc) -> FileIds ++ Acc end, [], Packages), @@ -1894,7 +2236,7 @@ test_package_hasFiles(#{~"packages" := Packages}) -> test_project_purl(#{~"documentDescribes" := [ProjectName], ~"packages" := Packages}=_Sbom) -> [#{~"externalRefs" := [Purl], ~"versionInfo" := VersionInfo}] = lists:filter(fun (#{~"SPDXID" := Id}) -> ProjectName == Id end, Packages), RefLoc = ?spdx_project_purl, - true = Purl == RefLoc#{ ~"referenceLocator" := <<"pkg:github/erlang/otp@", VersionInfo/binary>> }, + true = Purl == RefLoc#{ ~"referenceLocator" := <> }, ok. test_packages_purl(#{~"documentDescribes" := [ProjectName], ~"packages" := Packages}=_Sbom) -> @@ -1947,14 +2289,14 @@ test_package_relations(#{~"packages" := Packages}=Spdx) -> true = lists:all(fun (#{~"relatedSpdxElement" := Related, ~"relationshipType" := Relation, ~"spdxElementId" := PackageId}=Rel) -> - Result = + Result = lists:member(Relation, [~"PACKAGE_OF", ~"DEPENDS_ON", ~"TEST_OF", ~"OPTIONAL_DEPENDENCY_OF", ~"DOCUMENTATION_OF"]) andalso lists:member(Related, PackageIds) andalso lists:member(PackageId, PackageIds) andalso PackageId =/= Related andalso PackageId =/= ?spdxref_project_name, - case Result of + case Result of false -> io:format("Error in relation: ~p~n", [Rel]), false; @@ -2005,3 +2347,572 @@ extracted_license_info() -> %% %% REUSE-IgnoreEnd %% + +%% input: file points to the list of items openvex.table +%% branch: tell us which branch from openvex.table we take into account +%% +%% We take items from 'input.branch' and check that the openvex file +%% contains those exact changes. if not, a new change is issued +%% +%% Documentation in HOWTO/SBOM.md +%% + +vex_path(Branch) -> + VexPath = ?VexPath, + vex_path(VexPath, Branch). +vex_path(VexPath, Branch) -> + <>. + +init_openvex(#{input_file := File, branch := Branch, vex_path := VexPath}) -> + InitVex = vex_path(VexPath, Branch), + VexStmts = case filelib:is_file(InitVex) of + true -> % file exists + maps:get(~"statements", decode(InitVex)); + false -> % create file + Init = init_openvex_file(Branch), + file:write_file(InitVex, json:format(Init)), + maps:get(~"statements", Init) + end, + run_openvex1(VexStmts, File, Branch, VexPath). + +run_openvex(#{input_file := File, branch := Branch, vex_path := VexPath}) -> + InitVex = vex_path(VexPath, Branch), + VexStmts = maps:get(~"statements", decode(InitVex)), + run_openvex1(VexStmts, File, Branch, VexPath). + +run_openvex1(VexStmts, VexTableFile, Branch, VexPath) -> + Statements = calculate_statements(VexStmts, VexTableFile, Branch, VexPath), + lists:foreach(fun (St) -> io:format("~ts", [St]) end, Statements). + +calculate_statements(VexStmts, VexTableFile, Branch, VexPath) -> + VexTable = decode(VexTableFile), + case maps:get(Branch, VexTable, error) of + error -> + fail("Could not find '~ts' in file '~ts'.~nDid you forget to add an entry with name '~ts' into 'openvex.table'?", + [Branch, VexTableFile, Branch]); + CVEs -> + calculate_statements_from_cves(VexStmts, CVEs, Branch, VexPath) + end. + +calculate_statements_from_cves(VexStmts, CVEs, Branch, VexPath) -> + %% make the function idempotent, i.e., can be called consecutive times producing the same input + Filter = fun (Stmts) -> lists:filter(fun ([]) -> false; (_) -> true end, Stmts) end, + Filter(lists:flatmap( + fun (#{~"status" := Status}=M) -> + [{Purl, CVE}] = maps:to_list(maps:remove(~"status", M)), + ExistingEntry = lists:any(fun (#{~"vulnerability" := #{~"name" := VexCVE}}) when VexCVE =/= CVE -> + false; + (#{~"products" := Products}) -> + VexIds = lists:map(fun(M0) -> maps:get(~"@id", M0) end, Products), + lists:member(Purl, VexIds) + end, VexStmts), + case ExistingEntry of + true -> + %% entry exists, ignore to make operation idempotent + []; + false -> + InitVex = vex_path(VexPath, Branch), + FixedStatus = maps:is_key(~"fixed", Status), + AffectedStatus = maps:is_key(~"affected", Status), + case Purl of + <> -> + case {FixedStatus, AffectedStatus} of + {true, true} -> + throw("Erlang/OTP release versions, (e.g.) OTP-26.1 do not support fixed and affected status"); + _ -> + [format_vexctl(InitVex, Purl, CVE, Status)] + end; + <<"pkg:otp/", _/binary>> -> % handle OTP Apps, pkg:otp/ssl@4.3.1 + FixedRange = + case FixedStatus orelse AffectedStatus of + true -> + case maps:get(~"fixed", Status, <<>>) of + <<>> -> + []; + L when is_list(L) -> + L + end; + false -> + %% not affected and we return all Erlang intermediate + %% versions and all intermediate apps + all + end, + {OTPVersionsAffected, OTPVersionsFixed} = fetch_otp_purl_versions(Purl, FixedRange), + format_vexctl(InitVex, OTPVersionsAffected, OTPVersionsFixed, CVE, Status); + _ -> + AppsR = case maps:get(~"apps", Status, <<>>) of + <<>> -> + []; + Apps -> + case {FixedStatus, AffectedStatus} of + {true, true} -> + %% this case is not accepted as input, e.g. + %% the following is rejected + %% {"pkg:github/madler/zlib@04f42ceca40f73e2978b50e93806c2a18c1281fc": "FIKA-2026-BROD", + %% "status": { "affected": "Mitigation message, update to the next release", + %% "fixed": ["pkg:github/madler/zlib@04f42thiscommitfixesthecve"], + %% "apps": ["pkg:otp/erts@14.2.5.10"]} } + %% the current syntax from above has no way to understand when in erts this was fixed. + %% + %% If this case arises, write the CVE for zlib and then for OTP. + fail("Case containing 'affected', 'fixed', and 'apps' (all three) not supported.", []); + _ -> + {OTPVersionsAffected, OTPVersionsFixed} = + lists:foldl(fun (App, {Af, Fx}) -> + {Affected, Fixed} = fetch_otp_purl_versions(App, all), + {merge_otp_version_binaries(Affected, Af), + merge_otp_version_binaries(Fixed, Fx)} + end, {<<>>, <<>>}, Apps), + format_vexctl(InitVex, OTPVersionsAffected, OTPVersionsFixed, CVE, Status) + end + end, + % handle vendor dependencies. we lack sha-1 information to create + % a range of commits. if one wants to provide specific vendor information, + % e.g., false positive for openssl, one can do that manually using vexctl. + % if one wants to mention that erts-10.9.4 is not vulnerable to CVE-XXX + % in openssl, that's possible and goes via first case, pkg:otp/erts@10.9.4. + FixedRange = maps:get(~"fixed", Status, <<>>), + AppsR ++ format_vexctl(InitVex, Purl, FixedRange, CVE, Status) + end + end + end, CVEs)). + +format_vexctl(InitVex, Affected, Fixed, CVE, Status) -> + [ + format_vexctl(InitVex, Affected, CVE, Status), + format_vexctl(InitVex, Fixed, CVE, ~"fixed") + ]. + +format_vexctl(_VexPath, <<>>, _CVE, _) -> + ""; +format_vexctl(VexPath, Versions, CVE, #{~"not_affected" := ~"vulnerable_code_not_present"}) -> + io_lib:format("vexctl add --in-place ~ts --product='~ts' --vuln='~ts' --status='~ts' --justification='~ts'~n", + [VexPath, Versions, CVE, ~"not_affected", ~"vulnerable_code_not_present"]); +format_vexctl(VexPath, Versions, CVE, #{~"affected" := Mitigation}) -> + io_lib:format("vexctl add --in-place ~ts --product='~ts' --vuln='~ts' --status='~ts' --action-statement='~ts'~n", + [VexPath, Versions, CVE, ~"affected", Mitigation]); +format_vexctl(VexPath, Versions, CVE, S) when S =:= ~"fixed"; + S =:= ~"under_investigation"; + S =:= ~"affected" -> + io_lib:format("vexctl add --in-place ~ts --product='~ts' --vuln='~ts' --status='~ts'~n", + [VexPath, Versions, CVE, S]). + + +-spec fetch_otp_purl_versions(OTP :: binary(), FixedVersions :: [binary()] ) -> OTPAppVersions :: binary(). +fetch_otp_purl_versions(<>, _FixedVersions) -> + %% ignore + false; +fetch_otp_purl_versions(<<"pkg:otp/", OTPApp/binary>>, all=_FixedVersions) -> + %% Used to fetch all OTP releases and OTPApp versions + %% starting from OTPApp Version + + AffectedVersions = fetch_version_from_table(OTPApp), + ErlangOTPRelease = erlang:hd(AffectedVersions), + {MajorVersion, _} = string:take(ErlangOTPRelease, ".", true, leading), + + All = fetch_otp_major_version_from_table(MajorVersion), + RelevantVersions = take_otp_versions_from(All, AffectedVersions), + + {AffResult, FixResult} = + lists:foldl(fun (V, {AffectedPurls, FixedPurls}) -> + All2 = fetch_app_from_table(V, OTPApp), + LastVersion = erlang:list_to_binary("pkg:otp/" ++ string:replace(All2, ~"-", ~"@")), + {AfP, FxP} = fetch_otp_purl_versions(LastVersion, []), + AfPResult = merge_otp_version_binaries(AfP, AffectedPurls), + FxPResult = merge_otp_version_binaries(FxP, FixedPurls), + {AfPResult, FxPResult} + end, {<<>>, <<>>}, RelevantVersions), + {AffResult, FixResult}; +fetch_otp_purl_versions(<<"pkg:otp/", OTPApp/binary>>, FixedVersions) -> + AffectedVersions = fetch_version_from_table(OTPApp), + FixedRangeVersions = lists:flatmap(fun (<<"pkg:otp/", App/binary>>) -> + fetch_version_from_table(App) + end, FixedVersions), + + % Proceed to figure out OTP affected versions + AffectedOTPVersionsInTree = calculate_otp_range_versions(AffectedVersions, FixedRangeVersions), + OTPVersions = build_erlang_version_from_list(AffectedOTPVersionsInTree), + OTPPurls = lists:map(fun erlang_purl/1, OTPVersions), + AppVersions = lists:uniq( + lists:flatmap(fun (V) -> + Apps = fetch_app_from_table(V, OTPApp), + lists:map(fun (X) -> "pkg:otp/" ++ string:replace(X, ~"-", ~"@") end, Apps) + end, OTPVersions)), + + AffectedPurls = erlang:list_to_binary(lists:join(",", OTPPurls ++ AppVersions)), + + % Proceed to create fixed versions + FixedOTPVersions = lists:map(fun erlang_purl/1, + build_erlang_version_from_list(otp_version_to_number(FixedRangeVersions))), + FixedAppVersions = lists:map(fun erlang:binary_to_list/1, FixedVersions), + FixedPurls = erlang:list_to_binary(lists:join(",", FixedOTPVersions ++ FixedAppVersions)), + + {AffectedPurls, FixedPurls}; +fetch_otp_purl_versions(_, _) -> + false. + +erlang_purl(Release) when is_list(Release) -> + ?ErlangPURL ++ "@OTP-" ++ Release. + +take_otp_versions_from(Versions, AffectedVersions) -> + F = fun (OTPRel) -> not lists:member(OTPRel, AffectedVersions) end, + AffectedVersions ++ lists:takewhile(F, Versions). + +merge_otp_version_binaries(A, B) -> + case {A, B} of + {<<>>, B} -> + B; + {_, <<>>} -> + A; + {_, _} -> + remove_duplicate_versions(<>) + end. + +-spec remove_duplicate_versions(ListOfVulnerabilities :: binary()) -> binary(). +remove_duplicate_versions(Version) -> + binary:join( + lists:uniq( + binary:split(Version, ~",", [global])), + <<",">>). + + +%% Versions = [ [26, 0], [26, 1, 2], ... ] represents ["26.1", "26.1.2"] +build_erlang_version_from_list(Versions) -> + lists:map(fun (X) -> + lists:join(".", lists:map(fun erlang:integer_to_list/1, X)) + end, Versions). + +calculate_otp_range_versions(AffectedVersions, FixedRangeVersions) -> + Vs = get_otp_version_tree(AffectedVersions), + AffectedVersionsNumber = otp_version_to_number(AffectedVersions), + FixedVersionsNumber = otp_version_to_number(FixedRangeVersions), + Tree = build_tree(Vs), + prune_trees(Tree, AffectedVersionsNumber, FixedVersionsNumber). + +-spec build_tree(OTPTree :: list()) -> [{branch, Tree :: list()}]. +build_tree(OTPTree) -> + Sorted = lists:sort(fun less_than/2, OTPTree), + Tree = build_tree(Sorted, 1, []), + lists:map(fun ({branch, _}=Branch) -> Branch; + (Root) when is_list(Root) -> {branch, Root} + end, Tree). + +build_tree([], Pos, Acc) when Pos >= 4 -> + {Acc, 0, []}; +build_tree([], _Pos, Acc) -> + [Acc]; +build_tree([N| Ns], LastPos, Acc) when length(N) < 4, LastPos < 4 -> + build_tree(Ns, length(N), [N | Acc]); +build_tree([N| Ns], LastPos, Acc) when length(N) >= 4, LastPos >= 4 -> + build_tree(Ns, length(N), [N | Acc]); +build_tree([N| Ns], LastPos, Acc) when length(N) < 4, LastPos >= 4 -> + {Acc, length(N), [N|Ns]}; +build_tree([N | Ns], LastPos, Acc) when length(N) == 4, LastPos < 4 -> + %% this is a new branch + {Branch, N1, Continuation} = build_tree(Ns, length(N), [N | Acc]), + [{branch, Branch} | build_tree(Continuation, N1, Acc)]. + + +get_otp_version_tree(AffectedVersions) -> + lists:uniq( + lists:flatmap(fun (Version) -> + "OTP-"++Version1 = Version, + [Major|_] = convert_range(Version1), + OTPFlatTree = fetch_otp_major_version_from_table("OTP-"++Major), + lists:map(fun (X) -> + lists:map(fun erlang:list_to_integer/1, convert_range(X)) + end, OTPFlatTree) + end, AffectedVersions)). + +%% OTPVersion :: "OTP-26", e.g. +-spec otp_version_to_number(Ls) -> [Versions] when + Ls :: [OTPVersion], + OTPVersion :: string(), + Versions :: string(). +otp_version_to_number(Ls) -> + lists:map(fun (X) -> + {_, Version} = string:take(string:trim(X, both), "OTP-"), + lists:map(fun erlang:list_to_integer/1, convert_range(Version)) + end, Ls). + +prune_trees(Trees, AffectedVersions, FixedVersions) -> + lists:sort(lists:uniq( + lists:flatmap(fun({branch, Branch}) -> + Result = prune_tree(Branch, FixedVersions, lt), + prune_tree(Result, AffectedVersions, gt) + end, Trees) ++ AffectedVersions) -- FixedVersions). + +%% assumption: list versions are sorted, as per otp_versions. +prune_tree(Ls, Affected, Comparator) -> + Comp = case Comparator of + lt -> true; + gt -> false + end, + lists:uniq([L || A <:- Affected, lists:member(A, Ls), L <:- Ls, less_than(L, A) == Comp ]). + +less_than([], []) -> + true; +less_than([M | Ms], []) -> + less_than([M | Ms], [0]); +less_than([], [N | Ns]) -> + less_than([0], [ N | Ns]); +less_than([M | Ms], [N | Ns]) when M == N -> + less_than(Ms, Ns); +less_than([M | _], [N | _]) when M =< N -> + true; +less_than([M | _], [N | _]) when M > N -> + false. + +-spec fetch_version_from_table(OTPApp :: binary()) -> [string()]. +fetch_version_from_table(OTPApp) -> + App = erlang:list_to_binary(string:replace(OTPApp, ~"@", ~"-")), + fetch_from_table(erlang:binary_to_list(App)). + +-spec fetch_otp_major_version_from_table(Major :: string()) -> [string()]. +fetch_otp_major_version_from_table(Major) -> + Ls = fetch_otp_from_version_table(Major), + lists:map(fun ("OTP-"++Version) -> Version end, Ls). + +fetch_from_table(Str) -> + Vulns = os:cmd("grep '"++ Str ++ " ' otp_versions.table | cut -d' ' -f1"), + lists:filter(fun (L) -> L=/= [] end, string:split(Vulns, ~"\n", all)). + +fetch_otp_from_version_table(OTPVersion) -> + Vulns = os:cmd("grep '"++ OTPVersion ++ "' otp_versions.table | cut -d' ' -f1"), + lists:filter(fun (L) -> L=/= [] end, string:split(Vulns, ~"\n", all)). + +%% OTPVersion = "OTP-26.3.1" +%% App = "ssl-XXXX" +fetch_app_from_table(OTPVersion, App0) -> + App = lists:takewhile(fun (Char) -> Char =/= $@ end, erlang:binary_to_list(App0)), + Version = os:cmd("grep '" ++ OTPVersion ++ " : ' otp_versions.table"), + Vulns = string:split(Version, ~" ", all), + lists:filter(fun (L) -> + case string:prefix(L, App) of + nomatch -> + false; + _ -> + true + end + end, Vulns). + +convert_range(Version) -> + string:split(Version, ".", all). + + +init_openvex_file(Branch) -> + Ts = calendar:system_time_to_rfc3339(erlang:system_time(microsecond), [{unit, microsecond}]), + #{ + ~"@context" => ~"https://openvex.dev/ns/v0.2.0", + ~"@id" => <<"https://openvex.dev/docs/public/otp/vex-", Branch/binary>>, + ~"author" => ~"vexctl", + ~"timestamp" => erlang:list_to_binary(Ts), + ~"version" => 1, + ~"statements" => [] + }. + +test_openvex(_) -> + Tests = [ + test_openvex_branched_otp_tree, + test_openvex_branched_otp_tree_idempotent + ], + lists:all(fun (Fun) -> + Module = ?MODULE, + Result = apply(Module, Fun, []), + L = length(atom_to_list(Fun)), + io:format("- ~s~s~s~n", [Fun, lists:duplicate(80 - L, "."), Result]), + ok == Result + end, Tests), + ok. + + +test_openvex_branched_otp_tree() -> + {VexPath, Branch, VexStmts} = setup_openvex_test(), + CVEs = fixup_openvex_branched_otp_tree(), + Result = calculate_statements_from_cves(VexStmts, CVEs, Branch, VexPath), + Expected = [~"vexctl add --in-place otp-23.openvex.json --product='pkg:github/erlang/otp@OTP-23.2.2,pkg:github/erlang/otp@OTP-23.2.3,pkg:github/erlang/otp@OTP-23.2.4,pkg:github/erlang/otp@OTP-23.2.5,pkg:github/erlang/otp@OTP-23.2.6,pkg:github/erlang/otp@OTP-23.2.7,pkg:github/erlang/otp@OTP-23.2.7.1,pkg:github/erlang/otp@OTP-23.3,pkg:github/erlang/otp@OTP-23.3.1,pkg:github/erlang/otp@OTP-23.3.2,pkg:github/erlang/otp@OTP-23.3.3,pkg:github/erlang/otp@OTP-23.3.4,pkg:github/erlang/otp@OTP-23.3.4.1,pkg:otp/ssl@10.2.1,pkg:otp/ssl@10.2.2,pkg:otp/ssl@10.2.3,pkg:otp/ssl@10.2.4,pkg:otp/ssl@10.2.4.1,pkg:otp/ssl@10.3,pkg:otp/ssl@10.3.1' --vuln='CVE-2025-26618' --status='affected' --action-statement='Update to the next version'\n", + ~"vexctl add --in-place otp-23.openvex.json --product='pkg:github/erlang/otp@OTP-23.3.4.4,pkg:github/erlang/otp@OTP-23.3.4.3,pkg:github/erlang/otp@OTP-23.3.4.2,pkg:github/erlang/otp@OTP-23.2.7.3,pkg:github/erlang/otp@OTP-23.2.7.2,pkg:otp/ssl@10.3.1.1,pkg:otp/ssl@10.2.4.2' --vuln='CVE-2025-26618' --status='fixed'\n", + ~"vexctl add --in-place otp-23.openvex.json --product='pkg:github/madler/zlib@04f42ceca40f73e2978b50e93806c2a18c1281fc' --vuln='FIKA-2026-BROD' --status='affected' --action-statement='Mitigation message, update to the next release'\n", + ~"vexctl add --in-place otp-23.openvex.json --product='pkg:github/erlang/otp@OTP-26.0,pkg:otp/erts@14.0,pkg:github/erlang/otp@OTP-26.0.1,pkg:otp/erts@14.0.1,pkg:github/erlang/otp@OTP-26.0.2,pkg:otp/erts@14.0.2,pkg:github/erlang/otp@OTP-26.1,pkg:github/erlang/otp@OTP-26.1.1,pkg:otp/erts@14.1,pkg:github/erlang/otp@OTP-26.1.2,pkg:otp/erts@14.1.1,pkg:github/erlang/otp@OTP-26.2,pkg:otp/erts@14.2,pkg:github/erlang/otp@OTP-26.2.1,pkg:otp/erts@14.2.1,pkg:github/erlang/otp@OTP-26.2.2,pkg:otp/erts@14.2.2,pkg:github/erlang/otp@OTP-26.2.3,pkg:otp/erts@14.2.3,pkg:github/erlang/otp@OTP-26.2.4,pkg:otp/erts@14.2.4,pkg:github/erlang/otp@OTP-26.2.5,pkg:otp/erts@14.2.5,pkg:github/erlang/otp@OTP-26.2.5.1,pkg:otp/erts@14.2.5.1,pkg:github/erlang/otp@OTP-26.2.5.2,pkg:otp/erts@14.2.5.2,pkg:github/erlang/otp@OTP-26.2.5.3,pkg:otp/erts@14.2.5.3,pkg:github/erlang/otp@OTP-26.2.5.4,pkg:github/erlang/otp@OTP-26.2.5.5,pkg:otp/erts@14.2.5.4,pkg:github/erlang/otp@OTP-26.2.5.6,pkg:otp/erts@14.2.5.5,pkg:github/erlang/otp@OTP-26.2.5.7,pkg:otp/erts@14.2.5.6,pkg:github/erlang/otp@OTP-26.2.5.8,pkg:otp/erts@14.2.5.7,pkg:github/erlang/otp@OTP-26.2.5.9,pkg:otp/erts@14.2.5.8,pkg:github/erlang/otp@OTP-26.2.5.10,pkg:github/erlang/otp@OTP-26.2.5.11,pkg:otp/erts@14.2.5.9,pkg:github/erlang/otp@OTP-26.2.5.12,pkg:github/erlang/otp@OTP-26.2.5.13,pkg:otp/erts@14.2.5.10,pkg:github/erlang/otp@OTP-26.2.5.14,pkg:otp/erts@14.2.5.11' --vuln='CVE-2024-9143' --status='not_affected' --justification='vulnerable_code_not_present'\n", + ~"vexctl add --in-place otp-23.openvex.json --product='pkg:github/openssl/openssl@0foobar' --vuln='CVE-2024-9143' --status='not_affected' --justification='vulnerable_code_not_present'\n", + ~"vexctl add --in-place otp-23.openvex.json --product='pkg:github/erlang/otp@OTP-26.0,pkg:otp/erts@14.0,pkg:github/erlang/otp@OTP-26.0.1,pkg:otp/erts@14.0.1,pkg:github/erlang/otp@OTP-26.0.2,pkg:otp/erts@14.0.2,pkg:github/erlang/otp@OTP-26.1,pkg:github/erlang/otp@OTP-26.1.1,pkg:otp/erts@14.1,pkg:github/erlang/otp@OTP-26.1.2,pkg:otp/erts@14.1.1,pkg:github/erlang/otp@OTP-26.2,pkg:otp/erts@14.2,pkg:github/erlang/otp@OTP-26.2.1,pkg:otp/erts@14.2.1,pkg:github/erlang/otp@OTP-26.2.2,pkg:otp/erts@14.2.2,pkg:github/erlang/otp@OTP-26.2.3,pkg:otp/erts@14.2.3,pkg:github/erlang/otp@OTP-26.2.4,pkg:otp/erts@14.2.4,pkg:github/erlang/otp@OTP-26.2.5,pkg:otp/erts@14.2.5,pkg:github/erlang/otp@OTP-26.2.5.1,pkg:otp/erts@14.2.5.1,pkg:github/erlang/otp@OTP-26.2.5.2,pkg:otp/erts@14.2.5.2,pkg:github/erlang/otp@OTP-26.2.5.3,pkg:otp/erts@14.2.5.3,pkg:github/erlang/otp@OTP-26.2.5.4,pkg:github/erlang/otp@OTP-26.2.5.5,pkg:otp/erts@14.2.5.4,pkg:github/erlang/otp@OTP-26.2.5.6,pkg:otp/erts@14.2.5.5,pkg:github/erlang/otp@OTP-26.2.5.7,pkg:otp/erts@14.2.5.6,pkg:github/erlang/otp@OTP-26.2.5.8,pkg:otp/erts@14.2.5.7,pkg:github/erlang/otp@OTP-26.2.5.9,pkg:otp/erts@14.2.5.8,pkg:github/erlang/otp@OTP-26.2.5.10,pkg:github/erlang/otp@OTP-26.2.5.11,pkg:otp/erts@14.2.5.9,pkg:github/erlang/otp@OTP-26.2.5.12,pkg:github/erlang/otp@OTP-26.2.5.13,pkg:otp/erts@14.2.5.10,pkg:github/erlang/otp@OTP-26.2.5.14,pkg:otp/erts@14.2.5.11' --vuln='CVE-2024-4444' --status='not_affected' --justification='vulnerable_code_not_present'\n", + ~"vexctl add --in-place otp-23.openvex.json --product='pkg:github/openssl/openssl@0foobar' --vuln='CVE-2024-4444' --status='not_affected' --justification='vulnerable_code_not_present'\n" + ], + TestFun = fun (R) -> lists:member(erlang:list_to_binary(R), Expected) end, + true = lists:all(TestFun, Result), + ok. + +%% idempotent: script runs once. if run again, no new vex statements are introduced, +%% because there was no change. +test_openvex_branched_otp_tree_idempotent() -> + {VexPath, Branch, VexStmts} = setup_openvex_test(fixup_openvex_branched_otp_tree_stmts()), + CVEs = fixup_openvex_branched_otp_tree(), + Result = calculate_statements_from_cves(VexStmts, CVEs, Branch, VexPath), + true = Result == [], + ok. + +setup_openvex_test() -> + VexPath = ~"", + Branch = ~"otp-23", + VexStmts = [], + {VexPath, Branch, VexStmts}. +setup_openvex_test(Stmts) -> + {VexPath, Branch, _} = setup_openvex_test(), + {VexPath, Branch, Stmts}. + + +fixup_openvex_branched_otp_tree() -> +[ #{ ~"pkg:otp/ssl@10.2.1" => ~"CVE-2025-26618", + ~"status" => #{ ~"affected" => ~"Update to the next version", + ~"fixed" => [~"pkg:otp/ssl@10.3.1.1", ~"pkg:otp/ssl@10.2.4.2"]} }, + #{ ~"pkg:github/madler/zlib@04f42ceca40f73e2978b50e93806c2a18c1281fc" => ~"FIKA-2026-BROD", + ~"status" => #{ ~"affected" => ~"Mitigation message, update to the next release"}}, + + #{ ~"pkg:github/openssl/openssl@0foobar" => ~"CVE-2024-9143", + ~"status" => #{ ~"not_affected" => ~"vulnerable_code_not_present", + ~"apps" => [~"pkg:otp/erts@14.0"]}}, + + #{ ~"pkg:github/openssl/openssl@0foobar" => ~"CVE-2024-4444", + ~"status" => #{ ~"not_affected" => ~"vulnerable_code_not_present", + ~"apps" => [~"pkg:otp/erts@14.2.5.10"]}} + +]. + +fixup_openvex_branched_otp_tree_stmts() -> + [#{ ~"vulnerability"=> + #{"name"=> ~"CVE-2025-26618"}, + ~"products"=> + [ + #{~"@id"=> ~"pkg:github/erlang/otp@OTP-23.2.2"}, + #{~"@id"=> ~"pkg:github/erlang/otp@OTP-23.2.3"}, + #{~"@id"=> ~"pkg:github/erlang/otp@OTP-23.2.4"}, + #{~"@id"=> ~"pkg:github/erlang/otp@OTP-23.2.5"}, + #{~"@id"=> ~"pkg:github/erlang/otp@OTP-23.2.6"}, + #{~"@id"=> ~"pkg:github/erlang/otp@OTP-23.2.7"}, + #{~"@id"=> ~"pkg:github/erlang/otp@OTP-23.2.7.1"}, + #{~"@id"=> ~"pkg:github/erlang/otp@OTP-23.3"}, + #{~"@id"=> ~"pkg:github/erlang/otp@OTP-23.3.1"}, + #{~"@id"=> ~"pkg:github/erlang/otp@OTP-23.3.2"}, + #{~"@id"=> ~"pkg:github/erlang/otp@OTP-23.3.3"}, + #{~"@id"=> ~"pkg:github/erlang/otp@OTP-23.3.4"}, + #{~"@id"=> ~"pkg:github/erlang/otp@OTP-23.3.4.1"}, + #{~"@id"=> ~"pkg:otp/ssl@10.2.1"}, + #{~"@id"=> ~"pkg:otp/ssl@10.2.2"}, + #{~"@id"=> ~"pkg:otp/ssl@10.2.3"}, + #{~"@id"=> ~"pkg:otp/ssl@10.2.4"}, + #{~"@id"=> ~"pkg:otp/ssl@10.2.4.1"}, + #{~"@id"=> ~"pkg:otp/ssl@10.3"}, + #{~"@id"=> ~"pkg:otp/ssl@10.3.1"} + ], + ~"status"=> ~"affected", + ~"action_statement"=> ~"Update to the next version" + }, + #{ ~"vulnerability"=> + #{~"name"=> ~"CVE-2025-26618"}, + ~"products"=> + [ + #{~"@id"=> ~"pkg:github/erlang/otp@OTP-23.3.4.4"}, + #{~"@id"=> ~"pkg:github/erlang/otp@OTP-23.3.4.3"}, + #{~"@id"=> ~"pkg:github/erlang/otp@OTP-23.3.4.2"}, + #{~"@id"=> ~"pkg:github/erlang/otp@OTP-23.2.7.3"}, + #{~"@id"=> ~"pkg:github/erlang/otp@OTP-23.2.7.2"}, + #{~"@id"=> ~"pkg:otp/ssl@10.3.1.1"}, + #{~"@id"=> ~"pkg:otp/ssl@10.2.4.2"} + ], + ~"status"=> ~"fixed" + }, + #{~"vulnerability"=> + #{~"name"=> ~"FIKA-2026-BROD"}, + ~"products"=> + [ + #{~"@id"=> ~"pkg:github/madler/zlib@04f42ceca40f73e2978b50e93806c2a18c1281fc"} + ], + ~"status"=> ~"affected", + ~"action_statement"=> ~"Mitigation message, update to the next release" + }, + #{ ~"vulnerability" => + #{ ~"name" => ~"CVE-2024-9143" }, + ~"timestamp" => ~"2025-08-19T13:18:05.434247759+02:00", + ~"products" => + [ + #{~"@id" => ~"pkg:github/erlang/otp@OTP-26.0"}, + #{~"@id" => ~"pkg:github/erlang/otp@OTP-26.0.1"}, + #{~"@id" => ~"pkg:github/erlang/otp@OTP-26.0.2"}, + #{~"@id" => ~"pkg:otp/erts@14.0"}, + #{~"@id" => ~"pkg:otp/erts@14.0.1"}, + #{~"@id" => ~"pkg:otp/erts@14.0.2"}, + #{~"@id" => ~"pkg:github/erlang/otp@OTP-26.1"}, + #{~"@id" => ~"pkg:github/erlang/otp@OTP-26.1.1"}, + #{~"@id" => ~"pkg:github/erlang/otp@OTP-26.1.2"}, + #{~"@id" => ~"pkg:otp/erts@14.1"}, + #{~"@id" => ~"pkg:otp/erts@14.1.1"}, + #{~"@id" => ~"pkg:github/erlang/otp@OTP-26.2"}, + #{~"@id" => ~"pkg:github/erlang/otp@OTP-26.2.1"}, + #{~"@id" => ~"pkg:github/erlang/otp@OTP-26.2.2"}, + #{~"@id" => ~"pkg:github/erlang/otp@OTP-26.2.3"}, + #{~"@id" => ~"pkg:github/erlang/otp@OTP-26.2.4"}, + #{~"@id" => ~"pkg:github/erlang/otp@OTP-26.2.5"}, + #{~"@id" => ~"pkg:github/erlang/otp@OTP-26.2.5.1"}, + #{~"@id" => ~"pkg:github/erlang/otp@OTP-26.2.5.2"}, + #{~"@id" => ~"pkg:github/erlang/otp@OTP-26.2.5.3"}, + #{~"@id" => ~"pkg:github/erlang/otp@OTP-26.2.5.4"}, + #{~"@id" => ~"pkg:github/erlang/otp@OTP-26.2.5.5"}, + #{~"@id" => ~"pkg:github/erlang/otp@OTP-26.2.5.6"}, + #{~"@id" => ~"pkg:github/erlang/otp@OTP-26.2.5.7"}, + #{~"@id" => ~"pkg:github/erlang/otp@OTP-26.2.5.8"}, + #{~"@id" => ~"pkg:github/erlang/otp@OTP-26.2.5.9"}, + #{~"@id" => ~"pkg:github/erlang/otp@OTP-26.2.5.10"}, + #{~"@id" => ~"pkg:github/erlang/otp@OTP-26.2.5.11"}, + #{~"@id" => ~"pkg:github/erlang/otp@OTP-26.2.5.12"}, + #{~"@id" => ~"pkg:github/erlang/otp@OTP-26.2.5.13"}, + #{~"@id" => ~"pkg:github/erlang/otp@OTP-26.2.5.14"}, + #{~"@id" => ~"pkg:otp/erts@14.2"}, + #{~"@id" => ~"pkg:otp/erts@14.2.1"}, + #{~"@id" => ~"pkg:otp/erts@14.2.2"}, + #{~"@id" => ~"pkg:otp/erts@14.2.3"}, + #{~"@id" => ~"pkg:otp/erts@14.2.4"}, + #{~"@id" => ~"pkg:otp/erts@14.2.5"}, + #{~"@id" => ~"pkg:otp/erts@14.2.5.1"}, + #{~"@id" => ~"pkg:otp/erts@14.2.5.2"}, + #{~"@id" => ~"pkg:otp/erts@14.2.5.3"}, + #{~"@id" => ~"pkg:otp/erts@14.2.5.4"}, + #{~"@id" => ~"pkg:otp/erts@14.2.5.5"}, + #{~"@id" => ~"pkg:otp/erts@14.2.5.6"}, + #{~"@id" => ~"pkg:otp/erts@14.2.5.7"}, + #{~"@id" => ~"pkg:otp/erts@14.2.5.8"}, + #{~"@id" => ~"pkg:otp/erts@14.2.5.9"}, + #{~"@id" => ~"pkg:otp/erts@14.2.5.10"}, + #{~"@id" => ~"pkg:otp/erts@14.2.5.11"} + ], + ~"status" => ~"not_affected", + ~"justification" => ~"vulnerable_code_not_present" + }, + #{ ~"vulnerability" => #{ ~"name" => ~"CVE-2024-9143" }, + ~"timestamp" => ~"2025-08-19T13:18:23.396290497+02:00", + ~"products" => + [ + #{ ~"@id" => ~"pkg:github/openssl/openssl@0foobar" } + ], + ~"status" => ~"not_affected", + ~"justification" => ~"vulnerable_code_not_present" }, + #{ ~"vulnerability" => + #{ ~"name" => ~"CVE-2024-4444" }, + ~"timestamp" => ~"2025-08-19T13:18:05.434247759+02:00", + ~"products" => + [#{~"@id" => ~"pkg:github/erlang/otp@OTP-26.2.5.14"}, + #{~"@id" => ~"pkg:otp/erts@14.2.5.11"}, + #{~"@id" => ~"pkg:github/erlang/otp@OTP-26.2.5.12"}, + #{~"@id" => ~"pkg:github/erlang/otp@OTP-26.2.5.13"}, + #{~"@id" => ~"pkg:otp/erts@14.2.5.10"}], + ~"status" => ~"not_affected", + ~"justification" => ~"vulnerable_code_not_present" + }, + #{ ~"vulnerability" => #{ ~"name" => ~"CVE-2024-4444" }, + ~"timestamp" => ~"2025-08-19T13:18:23.396290497+02:00", + ~"products" => + [ + #{ ~"@id" => ~"pkg:github/openssl/openssl@0foobar" } + ], + ~"status" => ~"not_affected", + ~"justification" => ~"vulnerable_code_not_present" } + ]. diff --git a/.github/workflows/main.yaml b/.github/workflows/main.yaml index 62e80994045a..28d1d4c46ef7 100644 --- a/.github/workflows/main.yaml +++ b/.github/workflows/main.yaml @@ -456,6 +456,31 @@ jobs: docker run otp "erl ${OPTION} -noshell -s init stop" done + modified-vendor-files: + name: Check if vendor files changed + runs-on: ubuntu-latest + outputs: + vendor-files: ${{ steps.vendor-files.outputs.MODIFIED_FILES != '0' }} + steps: + - name: Get modified vendor files + id: vendor-files + run: | + echo "MODIFIED_FILES=$(git diff --name-only '${{ github.base_ref }}' 'HEAD' | grep 'vendor\.info$' | wc -l || 1)" + + # this is a call to a workflow_call + pr-vendor-vulnerability-analysis: + needs: modified-vendor-files + if: ${{ needs.modified-vendor-files.outputs.vendor-files != 0 && github.event_name == 'pull_request'}} + permissions: + security-events: read + name: Vendor Vulnerability Scanning + uses: ./.github/workflows/reusable-vendor-vulnerability-scanner.yml + with: + fail_if_cve: true + checkout: false + version: ${{ github.event_name == 'pull_request' && github.base_ref || github.ref_name }} + # equivalent of ${{ env.BASE_BRANCH }} but reusable-workflows do not allow to pass env. + build: name: Build Erlang/OTP runs-on: ubuntu-latest @@ -929,18 +954,17 @@ jobs: fail-on: ${{ github.ref_type == 'tag' && '' || 'violations,issues' }} sw-version: ${{ env.OTP_SBOM_VERSION }} - vendor-analysis: - name: Vendor Dependency Analysis + vendor-dependency-upload: + name: Vendor Dependency Upload runs-on: ubuntu-latest - if: github.event_name == 'push' needs: - sbom - pack + if: github.repository == 'erlang/otp' ## Needed to use Github Dependency API permissions: contents: write id-token: write - steps: - uses: actions/checkout@11bd71901bbe5b1630ceea73d27597364c9af683 # ratchet:actions/checkout@v4.2.2 - uses: ./.github/actions/build-base-image @@ -959,7 +983,13 @@ jobs: --sbom-file /github/bom.spdx.json" # allows Dependabot to give us alert of the vendor libraries that use semantic versioning + # it also allows dependencies to be looked up from github dependencies + # + # trigger the upload only on merged pull requests + # + # - name: Upload SBOM to Github Dependency API + if: github.event_name == 'pull_request' && github.event.action == 'closed' && github.event.pull_request.merged == true uses: advanced-security/spdx-dependency-submission-action@5530bab9ee4bbe66420ce8280624036c77f89746 # ratchet:advanced-security/spdx-dependency-submission-action@v0.1.1 ## If this is an "OTP-*" tag that has been pushed we do some release work diff --git a/.github/workflows/osv-scanner-scheduled.yml b/.github/workflows/osv-scanner-scheduled.yml index 989669443979..00f798b6434b 100644 --- a/.github/workflows/osv-scanner-scheduled.yml +++ b/.github/workflows/osv-scanner-scheduled.yml @@ -24,7 +24,6 @@ name: Open Source Vulnerabilities Scanner on: pull_request: - push: workflow_dispatch: schedule: - cron: 0 1 * * * @@ -60,33 +59,20 @@ jobs: permissions: actions: write steps: - - uses: actions/checkout@11bd71901bbe5b1630ceea73d27597364c9af683 # ratchet:actions/checkout@v4.2.2 - with: - ref: ${{ matrix.type }} - + # this call to a workflow_dispatch ref=master is important because + # using ref={{matrix.type}} would trigger the workflow + # reusable-vendor-vulnerability-scanner.yml in that ref/branch. since + # there is no such files in maint-25, maint-26, etc, the result would + # ignore the vulnerability scanning for those branches. + # - name: Trigger Vulnerability Scanning env: GH_TOKEN: ${{ github.token }} - if: ${{ hashFiles('.github/workflows/osv-scanner-scheduled.yml') != '' }} + REPO: ${{ github.repository }} # in testing cases, this is your fork, e.g., kikofernandez/otp run: | gh api \ --method POST \ -H "Accept: application/vnd.github+json" \ -H "X-GitHub-Api-Version: 2022-11-28" \ - /repos/${{ github.repository }}/actions/workflows/osv-scanner-scheduled.yml/dispatches \ - -f "ref=${{ matrix.type }}" - - scan-pr: - # run-scheduled-scan triggers this job - # PRs and pushes trigger this job - if: github.event_name != 'schedule' - permissions: - # Require writing security events to upload SARIF file to security tab - security-events: write - # Required to upload SARIF file to CodeQL. - # See: https://github.com/github/codeql-action/issues/2117 - actions: read - contents: read - uses: "google/osv-scanner-action/.github/workflows/osv-scanner-reusable.yml@e69cc6c86b31f1e7e23935bbe7031b50e51082de" # ratchet:google/osv-scanner-action/.github/workflows/osv-scanner-reusable.yml@v2.1.0" - with: - upload-sarif: ${{ github.repository == 'erlang/otp' }} + /repos/${{ github.repository }}/actions/workflows/reusable-vendor-vulnerability-scanner.yml/dispatches \ + -f 'ref=master' -f "inputs[checkout]=true" -f "inputs[version]=${{ matrix.type }}" -f "inputs[fail_if_cve]=true" diff --git a/.github/workflows/reusable-vendor-vulnerability-scanner.yml b/.github/workflows/reusable-vendor-vulnerability-scanner.yml new file mode 100644 index 000000000000..fea326a5a481 --- /dev/null +++ b/.github/workflows/reusable-vendor-vulnerability-scanner.yml @@ -0,0 +1,120 @@ +# %CopyrightBegin% +# +# SPDX-License-Identifier: Apache-2.0 +# +# Copyright Ericsson AB 2024-2025. All Rights Reserved. +# +# Licensed under the Apache License, Version 2.0 (the "License"); +# you may not use this file except in compliance with the License. +# You may obtain a copy of the License at +# +# http://www.apache.org/licenses/LICENSE-2.0 +# +# Unless required by applicable law or agreed to in writing, software +# distributed under the License is distributed on an "AS IS" BASIS, +# WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied. +# See the License for the specific language governing permissions and +# limitations under the License. +# +# %CopyrightEnd% + +name: Vendor Vulnerability Scanning +run-name: "[${{ inputs.version }}] Vendor Vulnerability Scanning" +description: 'Vulnerability scanning' + +# 'inputs' must be repeated twice for the different use cases. +# there is no current way to share 'inputs' for workflow dispatch +# and call. +# +# version: reference branch to checkout and analyse for CVE. +# +# fail_if_cve: makes the job fail if a CVE is found. +# This is 'true' when analysing PRs, as we prefer a failure to detect that the PR +# introduces a vulnerability. +# + +on: + workflow_dispatch: + inputs: + # this option is needed for scheduled scans. on pull requests (`main.yaml`) + # the PR already contains a branch on which to run and there is a known + # base_ref. on scheduled runs of this job, `base_ref` does not exist and + # we need to specify which repo branch to checkout. + checkout: + description: 'Checkout branch in version?' + required: false + default: false + type: boolean + version: + description: 'Reference branch to fetch OpenVEX statements' + required: true + default: 'master' + type: 'string' + fail_if_cve: + description: 'Fail if CVE is found' + required: true + default: false + type: boolean + workflow_call: + inputs: + # this option is needed for scheduled scans. on pull requests (`main.yaml`) + # the PR already contains a branch on which to run and there is a known + # base_ref. on scheduled runs of this job, `base_ref` does not exist and + # we need to specify which repo branch to checkout. + checkout: + description: 'Checkout branch in version?' + required: false + default: false + type: boolean + version: + description: 'Reference branch to fetch OpenVEX statements' + required: true + default: 'master' + type: 'string' + fail_if_cve: + description: 'Fail if CVE is found' + required: true + default: false + type: boolean + +env: + VERSION: ${{ inputs.version }} + +jobs: + analysis-vendor-dependencies: + name: "Vulnerability Scanning of Vendor Dependencies" + # This job always fetches otp-compliance escript from `master`. + # internally, the job downloads OpenVEX statements from `vex` folder. + # the main reason is that maint-25, maint-26, etc do not have this file + # committed into them. thus, a workflow_dispatch or workflow_call would + # not work, and we would not be able to analyse vendor dependecies there. + runs-on: ubuntu-latest + env: + GH_TOKEN: ${{ secrets.GITHUB_TOKEN }} + permissions: + security-events: read + steps: + - uses: actions/checkout@11bd71901bbe5b1630ceea73d27597364c9af683 # ratchet:actions/checkout@v4.2.2 + with: + ref: ${{ inputs.checkout && inputs.version || ''}} # '' = default branch + + - uses: erlef/setup-beam@5304e04ea2b355f03681464e683d92e3b2f18451 # racket:actions/checkout@v1 + with: + otp-version: '28' + + - name: 'Analysis of dependencies from OpenVEX in ${{ inputs.version }}' + id: analysis + run: | + curl -L \ + -H "Accept: application/vnd.github+json" \ + -H "Authorization: Bearer ${GH_TOKEN}" \ + -H "X-GitHub-Api-Version: 2022-11-28" \ + https://api.github.com/repos/erlang/otp/contents/.github/scripts/otp-compliance.es \ + | jq -r '.content' | base64 -d > otp-compliance.es + chmod +x otp-compliance.es + cp otp-compliance.es /home/runner/work/otp/otp/.github/scripts/otp-compliance.es + cd /home/runner/work/otp/otp && \ + mkdir -p vex && \ + .github/scripts/otp-compliance.es sbom osv-scan \ + --version ${{ inputs.version }} \ + --fail_if_cve ${{ inputs.fail_if_cve }} diff --git a/HOWTO/SBOM.md b/HOWTO/SBOM.md index 44f7c29283ee..1b361e7d6e93 100644 --- a/HOWTO/SBOM.md +++ b/HOWTO/SBOM.md @@ -183,6 +183,7 @@ This file may be a list of JSON objects. For simplicity, we document the fields "licenseDeclared": "Zlib", "name": "asmjit", "versionInfo": "029075b84bf0161a761beb63e6eda519a29020db", + "sha": "029075b84bf0161a761beb63e6eda519a29020db", "path": "./erts/emulator/asmjit", "exclude": ["./erts/emulator/asmjit/vendor.info"], "supplier": "Person: Petr Kobalicek", @@ -202,11 +203,15 @@ Fields summary: - If you are unsure about the name of the `SPDX-TOP-LEVEL-PACKAGE`, take a look at the source SBOM to identify packages (under key `packages` in the SBOM). - `description`: a brief description of what this vendor library does. - `copyrightText`: copyright text associated with the top-level package/library/3pp using [SPDX License Identifiers](https://spdx.org/licenses/). -- `downloadLocation`: URI of the vendor library to download. +- `downloadLocation`: URI of the vendor library to download. If using Github, use preferably `https//` rather than `git+https//` or similars. + This is because the download location is used for vulnerability scanning in `.github/scripts/otp-compliance.es`. - `homepage`: homepage of the vendor library. - `licenseDeclared`: license as declared by the vendor, following a [SPDX license identifier](https://spdx.org/licenses/). - `name`: name of the library. - `versionInfo`: version of the library/project/3pp. In case of no version number being available, write the commit sha. +- `sha`: sha commit for `versionInfo`, they need to be updated together! +- `ecosystem`: List of valid ecosystems in [OSV Ecosystems](https://ossf.github.io/osv-schema/#defined-ecosystems) + where this value is omitted for C/C++ code (e.g., `asmjit`, `pcre2`, `zlib`, `zstd`, etc), and used in `vendor.json` for `jquery`. - `path`: path to the vendor library inside Erlang/OTP. This can point to a folder or a list of files. - Folder: any file inside the folder is considered part of the vendor library (e.g., asmjit [vendor.info](../erts/emulator/asmjit/vendor.info)). - List of files: only the files listed here are part of a vendor library (e.g., erts-config [vendor.info](../erts/autoconf/vendor.info)). @@ -225,8 +230,7 @@ and re-run the source SBOM generation steps ([Erlang/OTP source SBOM]). ### Add a New Vendor Dependency Follow the same steps as in [Update SPDX Vendor Packages]. -When running the SBOM generator, make sure to check that the new vendor dependency exists -in its own package. +When running the SBOM generator, make sure to check that the new vendor dependency exists in its own package. The [`renovate.json5`](../renovate.json5) file also needs to be updated to make sure that the new vendored dependency gets updated as it should. @@ -237,3 +241,482 @@ Delete the code and any remaining `vendor.info` files. Re-run the source SBOM generation steps ([Erlang/OTP source SBOM]). Delete the proper sections in [`renovate.json5`](../renovate.json5). + +## VEX + +VEX files allow to communicate which vulnerabilities are false positives and which ones are actual vulnerabilities. VEX files are important to explicitly state that some vendor dependencies are (not) vulnerabilities in your software. + +Erlang/OTP has chosen to communicate VEX information using the OpenVEX implementation. + +### Dependencies + +Install `vexctl`, which is written in Go. + +#### Installing Go + +An easy way to install go on Ubuntu is to type the following: + +```bash +sudo snap install go --classic +``` + +and add to your PATH the `snap` apps (e.g., to your `.bashrc`), + +```bash +export PATH=$PATH:/snap/bin +``` + +Alternatively, install [Go from source or binaries](https://go.dev/doc/install). + +#### Installing vexctl + +**Automatic** + +``` +go install github.com/openvex/vexctl@latest +``` + +**From source** + +Download and install `vextctl` as follows + +```bash +git clone https://github.com/openvex/vexctl.git +cd vexctl +make +``` + +Add to your path the binary, + +```bash +export PATH=$PATH:/vexctl/ +``` + +### HOW-TO + +Erlang/OTP will maintain VEX files for the latests three releases. +Because of this, Erlang/OTP will always contain the latest information in the `master` branch. +Any OpenVEX file in other branches is considered outdated. + +The OpenVEX files are located in `vex/otp-26.openvex.json`, `vex/otp-27.openvex.json`, and `vex/otp-28.openvex.json` (e.g.). These files are generated from the `make/openvex.table` and the script `.github/scripts/otp-compliance.es`. + +- `make/openvex.table` contains all known CVEs on a per release basis, with top-level objects for `otp-XX` branches, where each `otp-XX` object has as value a list of dependencies with their CVE and the status. + + Example: + + ```json + "otp-28": + [ + { + "pkg:github/openssl/openssl@636dfadc70ce26f2473870570bfd9ec352806b1d" : "CVE-2025-4575", + "status": {"not_affected": "vulnerable_code_not_present"} + }, + + { + "pkg:github/PCRE2Project/pcre2@2dce7761b1831fd3f82a9c2bd5476259d945da4d": "OSV-2025-300", + "status": {"not_affected": "vulnerable_code_not_present"} + }, + ... + ] + ``` + +The `status` corresponds to the possible status from the [OpenVEX specification](https://github.com/openvex/spec/blob/main/OPENVEX-SPEC.md). +In case of `not_affected`, a reason must be provided (similar to the [specification](https://github.com/openvex/spec/blob/main/OPENVEX-SPEC.md)). +**The `make/openvex.table` is considered to be an append-only structure, where one should not do modifications to existing data nor removal**. +Changes should be done via `.github/scripts/otp-compliance.es` applied on the `openvex.table`. The main reason is to use +`openvex.table` as a simple source of truth without boilerplate, since VEX statements can be long due to the way in which one +must express range versions for a vulnerability. + +In the example above, `pkg:github/openssl/openssl@636dfadc70ce26f2473870570bfd9ec352806b1d` corresponds to +the package URL for the OpenSSL version with commit `636dfadc70ce26f2473870570bfd9ec352806b1d`, which corresponds +to the version of OpenSSL used in OTP-X. Starting from OTP 28, this information can be found in the corresponding +`vendor.info` file for OpenSSL (e.g., `/erts/emulator/openssl/vendor.info` in the `sha` field). + +### Further Format Details of openvex.table + +The file `openvex.table` is a subset of fields of the OpenVEX specification. +The format is a JSON object that contains OTP VEX statements. A top-level valid field is the +OTP version key (e.g., `otp-29`), followed by a list of objects. Each JSON object can have the following structure. + +- A key with a Purl, which uniquely identifies the application that the statement talks about, + and a CVE string as value. +- A key `status` with value `Status :: "affected" | "fixed" | "under_investigation | "not_affected" | Affected`, + where `Affected` is an object explained below. +- `Affected` is an object that may have the following keys + - `affected` with value string that explains mitigation strategies + - `fixed` with value where the fix was introduced. + +**Example** + +Assume the following ficticious case, where we want to report `CVE-2023-48795` on OTP 23. + +```json +{ + "otp-23": [ + { + "pkg:otp/ssh@4.10.1": "CVE-2023-48795", + "status": + { "affected": "Mitigation: If strict KEX availability cannot be ensured on both connection sides, affected encryption modes(CHACHA and CBC) can be disabled with standard ssh configuration. This will provide protection against vulnerability, but at a cost of affecting interoperability" + } + }, + { + "pkg:github/madler/zlib@04f42ceca40f73e2978b50e93806c2a18c1281fc": "FIKA-2026-BROD", + "status": { "affected": "Mitigation message, update to the next release"} + } + ] +} +``` + + +### Use Cases + +In all the cases explained below, the running of the tool `.github/scripts/otp-compliance.es vex` does not commit changes. +One has to execute the output commands to introduce changes. + + +**Code Generation** + +Erlang/OTP creates releases (e.g., OTP-28) and also divides apps in different versions, which means that one can declare +vulnerabilities in multiple ways. + +Example, should we mention that the `ssh` app in OTP-23 is vulnerable or that `ssh-4.10.1` which released in OTP-23 is vulnerable, or both? +To help us produce accurate results, Erlang/OTP favours to write the exact application version in which a bug was introduced or detected, +and the exact app version in which the app was fixed, within its OTP release. + +For example, if we place in `openvex.table`: + +```json +{ + "otp-23": [ + { + "pkg:otp/ssh@4.10.1": "CVE-2023-48795", + "status": { "affected": "Mitigation: If strict KEX availability cannot be ensured on both connection sides, affected encryption modes(CHACHA and CBC) can be disabled with standard ssh configuration. This will provide protection against vulnerability, but at a cost of affecting interoperability", + "fixed": ["pkg:otp/ssh@4.11.1.6"] + } + } + ] +} +``` + +and execute the script + +```bash +.github/scripts/otp-compliance.es vex run -b otp-23 | bash +``` + +Generates the following VEX commands + +```bash +vexctl add --in-place vex/otp-23.openvex.json --product='pkg:otp/erlang@23.1,pkg:otp/erlang@23.1.1,pkg:otp/erlang@23.1.2,pkg:otp/erlang@23.1.3,pkg:otp/erlang@23.1.4,pkg:otp/erlang@23.1.5,pkg:otp/erlang@23.2,pkg:otp/erlang@23.2.1,pkg:otp/erlang@23.2.2,pkg:otp/erlang@23.2.3,pkg:otp/erlang@23.2.4,pkg:otp/erlang@23.2.5,pkg:otp/erlang@23.2.6,pkg:otp/erlang@23.2.7,pkg:otp/erlang@23.3,pkg:otp/erlang@23.3.1,pkg:otp/erlang@23.3.2,pkg:otp/erlang@23.3.3,pkg:otp/erlang@23.3.4,pkg:otp/erlang@23.3.4.1,pkg:otp/erlang@23.3.4.2,pkg:otp/erlang@23.3.4.3,pkg:otp/erlang@23.3.4.4,pkg:otp/erlang@23.3.4.5,pkg:otp/erlang@23.3.4.6,pkg:otp/erlang@23.3.4.7,pkg:otp/erlang@23.3.4.8,pkg:otp/erlang@23.3.4.9,pkg:otp/erlang@23.3.4.10,pkg:otp/erlang@23.3.4.11,pkg:otp/erlang@23.3.4.12,pkg:otp/erlang@23.3.4.13,pkg:otp/erlang@23.3.4.14,pkg:otp/ssh@4.10.1,pkg:otp/ssh@4.10.2,pkg:otp/ssh@4.10.3,pkg:otp/ssh@4.10.4,pkg:otp/ssh@4.10.5,pkg:otp/ssh@4.10.6,pkg:otp/ssh@4.10.7,pkg:otp/ssh@4.10.8,pkg:otp/ssh@4.11,pkg:otp/ssh@4.11.1,pkg:otp/ssh@4.11.1.1,pkg:otp/ssh@4.11.1.2,pkg:otp/ssh@4.11.1.3,pkg:otp/ssh@4.11.1.4,pkg:otp/ssh@4.11.1.5' --vuln='CVE-2023-48795' --status='affected' --action-statement='Mitigation: If strict KEX availability cannot be ensured on both connection sides, affected encryption modes(CHACHA and CBC) can be disabled with standard ssh configuration. This will provide protection against vulnerability, but at a cost of affecting interoperability' + +vexctl add --in-place vex/otp-23.openvex.json --product='pkg:otp/erlang@23.3.4.19,pkg:otp/erlang@23.3.4.18,pkg:otp/erlang@23.3.4.17,pkg:otp/erlang@23.3.4.16,pkg:otp/erlang@23.3.4.15,pkg:otp/ssh@4.11.1.6' --vuln='CVE-2023-48795' --status='fixed' +``` + +The first command in the script has figured out the exact OTP versions that are vulnerable from the range of affected and fixed exact versions, +as well as created the range of `ssh` applications that are affected by the vulnerability. + +The second command simply states which OTP application versions are fixed. + +Below we continue with how to initialize and use the tool to report various states, +and show examples for Erlang/OTP applications and third party application on which Erlang/OTP builds upon. + +#### Init + +This will only be needed once, but if you need to initialize and provide existing known CVEs, you can use `.github/scripts/otp-compliance.es`. + +The first time that we generate OpenVEX statements we call `.github/scripts/otp-compliance.es vex init --input-file make/openvex.table -b otp-28`. This init script outputs instructions to execute in the shell, which invokes commands from `vexctl` ([Installation steps here](https://github.com/openvex/vexctl)). You can run and execute the scripts as follows, `.github/scripts/otp-compliance.es vex init --input-file make/openvex.table -b otp-28 | bash` (if you use bash). + +The script is idempotent, meaning that running consecutive times the script will not change its input. +Because of this, you run this command only for a new OTP release, and for coming CVEs you use `.github/scripts/otp-compliance.es vex run ...`. +This last command will not update the time and assumes that the `otp-XX.openvex.json` exists (because the `init` command must be run first). + +**Example for new Release** + +To release VEX files for a new release, OTP-29, add the name branch to `make/openvex.table` (assuming there are known CVEs): + +``` +{ + "otp-29": [] +} +``` + +Execute the script to create the VEX statements for OTP-29: + +```bash +.github/scripts/otp-compliance.es vex init --input-file make/openvex.table -b otp-29 +``` + +There are no known vulnerabilities, so this VEX statement can be published as is. + + +#### Add `under_investigation` + +For vendor CVEs, it may make sense to communicate with the ecosystem that a CVE for vendor X is under investigation. +If it is trivial to know whether we are affected, one could skip reporting `under_investigation` and add directly the `fixed`, or `vulnerable` statements. + +To update or insert VEX statements for OTP-29, update the `make/openvex.table` and run: + +```bash +.github/scripts/otp-compliance.es vex run --input-file make/openvex.table -b otp-29 +``` + +The script will output commands to run (similar to a dry-run). Once piped to `bash`, they are executed. + +``` +.github/scripts/otp-compliance.es vex run --input-file make/openvex.table -b otp-29 | bash +``` + +Add and commit the changes. + +**Example** + +`make/openvex.table` contains: + +``` +{ + "otp-29": [] +} +``` + +Lets assume there is `FIKA-2026-BROD` detected in `zlib`. We can issue an `under_investigation` statement updating the `make/openvex.table` + + +```json +{ + "otp-29": [ + { + "pkg:github/madler/zlib@04f42ceca40f73e2978b50e93806c2a18c1281fc": "FIKA-2026-BROD", + "status": "under_investigation" + } + ] +} +``` + +Execute the command below to update the OpenVEX statements. + +```bash +.github/scripts/otp-compliance.es vex run --input-file make/openvex.table -b otp-29 | bash +``` + +Erlang/OTP should not issue an `under_investigation` unless it is known that it will take some days to understand if Erlang/OTP is vulnerable to a vendor dependency. + +#### Add `not_affected` + +If the vulnerability under investigation is a false positive, one can convey this information using OpenVEX statements. +To do this, one adds a reason for why the vulnerability does not apply. These justifications can be found in the [OpenVEX spec](https://github.com/openvex/spec/blob/main/OPENVEX-SPEC.md#status-justifications). + +**Example** + +OTP was investigating the CVE `FIKA-2026-BROD` and found themselves not affected. +We continue from the example in the previous section, that contained `zlib` with status `under_investigation`: + +```json +{ + "otp-29": [ + { + "pkg:github/madler/zlib@04f42ceca40f73e2978b50e93806c2a18c1281fc": "FIKA-2026-BROD", + "status": "under_investigation" + } + ] +} +``` + +One can update the `make/openvex.table` with the reason of "code not present", meaning, the component is included +in OTP but the vulnerable code is not present. It is important to note that any statement written in the table +should not be updated, the table is append only. + +```json +{ + "otp-29": [ + { + "pkg:github/madler/zlib@04f42ceca40f73e2978b50e93806c2a18c1281fc": "FIKA-2026-BROD", + "status": "under_investigation" + }, + { + "pkg:github/madler/zlib@04f42ceca40f73e2978b50e93806c2a18c1281fc": "FIKA-2026-BROD", + "status": {"not_affected": "vulnerable_code_not_present"} + } + ] +} +``` + +To update the OpenVEX statements, run: + +```bash +.github/scripts/otp-compliance.es vex run --input-file make/openvex.table -b otp-29 | bash +``` + +It produces a new entry in the openvex statements for OTP-29 stating that OTP-29 is not vulnerable to the CVE `FIKA-2026-BROD`. + + +#### Add `affected` + +When OTP is affected by a CVE, one can communicate this using the `affected` status. + +**Example** + +OTP was investigating the CVE `FIKA-2026-BROD` and found themselves affected. + +```json +{ + "otp-29": [ + { + "pkg:github/madler/zlib@04f42ceca40f73e2978b50e93806c2a18c1281fc": "FIKA-2026-BROD", + "status": "under_investigation" + } + ] +} +``` + +One can write then in `make/openvex.table`: + +```json +{ + "otp-29": [ + { + "pkg:github/madler/zlib@04f42ceca40f73e2978b50e93806c2a18c1281fc": "FIKA-2026-BROD", + "status": "under_investigation" + }, + { + "pkg:github/madler/zlib@04f42ceca40f73e2978b50e93806c2a18c1281fc": "FIKA-2026-BROD", + "status": "affected" + } + ] +} +``` + +where the version affected is written as part of the package url `pkg:github/madler/zlib@04f42ceca40f73e2978b50e93806c2a18c1281fc`. + +Execute the command below to update the OpenVEX statements. + +```bash +.github/scripts/otp-compliance.es vex run --input-file make/openvex.table -b otp-29 | bash +``` + +It produces a new entry in the openvex statements for OTP-29. +One can run multiple times the same statement without introducing each time the same statement. +(the script makes the operation idempotent). + +In some cases, it may be useful to provide additional information to mitigate the vulnerability. +To specify this, write the `status` value as an object with free text. + +```json +{ + "otp-29": [ + { + "pkg:github/madler/zlib@04f42ceca40f73e2978b50e93806c2a18c1281fc": "FIKA-2026-BROD", + "status": "under_investigation" + }, + { + "pkg:github/madler/zlib@04f42ceca40f73e2978b50e93806c2a18c1281fc": "FIKA-2026-BROD", + "status": {"affected" : "do not use this component until there is a fix"} + } + ] +} +``` + and run the `otp-compliance` script as stated above. + +#### Add `fixed` + +One can specify that the CVE is fixed in a specific version using the `fixed` keyword in the `make/openvex.table` statements. + +**Example** + +OTP was affected the CVE `FIKA-2026-BROD`, reported in `make/openvex.table`. + +```json +{ + "otp-29": [ + { + "pkg:github/madler/zlib@04f42ceca40f73e2978b50e93806c2a18c1281fc": "FIKA-2026-BROD", + "status": "under_investigation" + }, + { + "pkg:github/madler/zlib@04f42ceca40f73e2978b50e93806c2a18c1281fc": "FIKA-2026-BROD", + "status": "affected" + } + ] +} +``` + +OTP creates an emergency patch to fix this vendor dependency, and states that the package url (product and version) +`pkg:github/madler/zlib@04f42cecafika2026brod` fixes the vulnerability. + +```json +{ + "otp-29": [ + { + "pkg:github/madler/zlib@04f42ceca40f73e2978b50e93806c2a18c1281fc": "FIKA-2026-BROD", + "status": "under_investigation" + }, + { + "pkg:github/madler/zlib@04f42ceca40f73e2978b50e93806c2a18c1281fc": "FIKA-2026-BROD", + "status": "affected" + }, + { + "pkg:github/madler/zlib@04f42cecafika2026brod": "FIKA-2026-BROD", + "status": "fix" + }, + ] +} +``` + + +Execute the command below to update the OpenVEX statements. + +```bash +.github/scripts/otp-compliance.es vex run --input-file make/openvex.table -b otp-29 | bash +``` + +Alternatively, one can write the affected and fixed versions in a single object for OTP applications. + +```json + "otp-29": [ + { + "pkg:otp/erts@10.3.4": "FIKA-2026-BROD", + "status": "under_investigation" + }, + { + "pkg:otp/erts@10.3.4": "FIKA-2026-BROD", + "status": { "affected": "Mitigation message, update to the next release", + "fixed": ["pkg:otp/erts@10.3.20"]} + } + ] +``` + +#### Vendor Statements + +Some vendor applications may be tied to the runtime system, such as `openssl` is tied to `erts` and `erl_interface`. +When there is a CVE towards a third party tied to an Erlang/OTP package (almost always!), +where Erlang/OTP is not affected (almost all cases of `openssl`), one can write the following, +where `apps` is a list of applications not affected, started from their package url version +(`14.2.5.10`) until implicitly their last version in the tree. + +```json + { + "pkg:github/openssl/openssl@0foobar": "CVE-2024-9143", + "status": { "not_affected": "vulnerable_code_not_present", + "apps": ["pkg:otp/erts@14.2.5.10"]} + }, +``` + + +In case of wanting to explicitly state that Erlang/OTP is vulnerable or not to a vendor CVE, +one can write the following, but the script will not generate range queries due to these +been at the sha-1 commit hash level. + +```json +{ + "otp-29": [ + { + "pkg:github/madler/zlib@04f42ceca40f73e2978b50e93806c2a18c1281fc": "FIKA-2026-BROD", + "status": "under_investigation" + }, + { + "pkg:github/madler/zlib@04f42ceca40f73e2978b50e93806c2a18c1281fc": "FIKA-2026-BROD", + "status": { "affected": "Mitigation message, update to the next release", + "fixed": ["pkg:github/madler/zlib@04f42thiscommitfixesthecve"]} + } + ] +} +``` diff --git a/erts/emulator/openssl/vendor.info b/erts/emulator/openssl/vendor.info index 2dbc6371bf9a..6dd37defce3c 100644 --- a/erts/emulator/openssl/vendor.info +++ b/erts/emulator/openssl/vendor.info @@ -15,6 +15,7 @@ "licenseDeclared": "Apache-2.0", "name": "openssl", "versionInfo": "3.5", + "sha": "636dfadc70ce26f2473870570bfd9ec352806b1d", "path": "./erts/emulator/openssl", "exclude": ["./erts/emulator/openssl/vendor.info", "./erts/emulator/openssl/README", diff --git a/erts/emulator/pcre/vendor.info b/erts/emulator/pcre/vendor.info index 3bdb2297e7ce..21d25d19347b 100644 --- a/erts/emulator/pcre/vendor.info +++ b/erts/emulator/pcre/vendor.info @@ -19,6 +19,7 @@ "exclude": ["./erts/emulator/pcre/vendor.info", "./erts/emulator/pcre/README.pcre_update.md", "./erts/emulator/pcre/pcre.mk"], + "sha": "2dce7761b1831fd3f82a9c2bd5476259d945da4d", "supplier": "Person: Philip Hazel", "purl": "pkg:generic/pcre2" } diff --git a/erts/emulator/ryu/vendor.info b/erts/emulator/ryu/vendor.info index a98d92e42308..d3f70daac626 100644 --- a/erts/emulator/ryu/vendor.info +++ b/erts/emulator/ryu/vendor.info @@ -22,8 +22,7 @@ "./erts/emulator/ryu/digit_table.h", "./erts/emulator/ryu/ryu.h", "./erts/emulator/ryu/LICENSE-Apache2", - "./erts/emulator/ryu/LICENSE-Boost" - ], + "./erts/emulator/ryu/LICENSE-Boost"], "supplier": "Person: Ulf Adams", "purl": "pkg:github/ulfjack/ryu#ryu", "update": "./erts/emulator/ryu/update.sh", diff --git a/erts/emulator/zlib/vendor.info b/erts/emulator/zlib/vendor.info index 716f1ea0953b..a0ae3dce97e3 100644 --- a/erts/emulator/zlib/vendor.info +++ b/erts/emulator/zlib/vendor.info @@ -10,15 +10,16 @@ "ID": "erts-zlib", "description": "interface of the 'zlib' general purpose compression library", "copyrightText": "Copyright (C) 1995-2024 Jean-loup Gailly and Mark Adler", - "downloadLocation": "https://zlib.net/", + "downloadLocation": "https://github.com/madler/zlib", "homepage": "https://zlib.net/", "licenseDeclared": "Zlib", "name": "zlib", "versionInfo": "1.3.1", + "sha": "1a8db63788c34a50e39e273d39b7e1033208aea2", "path": "./erts/emulator/zlib", "exclude": ["./erts/emulator/zlib/vendor.info", "./erts/emulator/zlib/zlib.mk"], "supplier": "Person: Mark Adler (zlib@gzip.org)", - "purl": "pkg:generic/zlib" + "purl": "pkg:github/madler/zlib" } ] diff --git a/erts/emulator/zstd/vendor.info b/erts/emulator/zstd/vendor.info index fe5b5b945854..53e34eee3218 100644 --- a/erts/emulator/zstd/vendor.info +++ b/erts/emulator/zstd/vendor.info @@ -15,6 +15,7 @@ "licenseDeclared": "BSD-3-Clause OR GPL-2.0-only", "name": "zstd", "versionInfo": "v1.5.7", + "sha": "f8745da6ff1ad1e7bab384bd1f9d742439278e99", "path": "./erts/emulator/zstd", "exclude": ["./erts/emulator/zstd/vendor.info", "./erts/emulator/zstd/update.sh", diff --git a/lib/common_test/priv/vendor.info b/lib/common_test/priv/vendor.info index 2526eed77092..119fa886bb78 100644 --- a/lib/common_test/priv/vendor.info +++ b/lib/common_test/priv/vendor.info @@ -13,6 +13,7 @@ "downloadLocation": "https://github.com/jquery/jquery", "homepage": "https://jquery.com", "licenseDeclared": "MIT", + "ecosystem": "npm", "name": "jquery", "versionInfo": "3.7.1", "path": ["./lib/common_test/priv/jquery-latest.js"], @@ -26,7 +27,8 @@ "downloadLocation": "https://github.com/Mottie/tablesorter", "homepage": "https://github.com/Mottie/tablesorter", "licenseDeclared": "BSD-3-Clause OR GPL-2.0-only", - "name": "jquery-tablesorter", + "ecosystem": "npm", + "name": "tablesorter", "versionInfo": "2.32", "path": ["./lib/common_test/priv/jquery.tablesorter.min.js"], "supplier": "Person: Christian Bach", diff --git a/lib/erl_interface/src/openssl/vendor.info b/lib/erl_interface/src/openssl/vendor.info index e1abf3576fe8..dccd4695418b 100644 --- a/lib/erl_interface/src/openssl/vendor.info +++ b/lib/erl_interface/src/openssl/vendor.info @@ -15,6 +15,7 @@ "licenseDeclared": "Apache-2.0", "name": "openssl", "versionInfo": "3.5", + "sha": "636dfadc70ce26f2473870570bfd9ec352806b1d", "path": "./lib/erl_interface/src/openssl", "exclude": ["./lib/erl_interface/src/openssl/vendor.info", "./lib/erl_interface/src/openssl/README", diff --git a/lib/wx/vendor.info b/lib/wx/vendor.info index 9dd3992951e0..6c0427d31e44 100644 --- a/lib/wx/vendor.info +++ b/lib/wx/vendor.info @@ -15,6 +15,7 @@ "licenseDeclared": "LicenseRef-scancode-wxwindows-free-doc-3", "name": "wx", "versionInfo": "dc585039bbd426829e3433002023a93f9bedd0c2", + "sha": "dc585039bbd426829e3433002023a93f9bedd0c2", "path": "./lib/wx", "comments": "This only applies to the source code of Erlang files in 'src', and specifically to the documentation embedded in them", "supplier": "NOASSERTION", diff --git a/make/openvex.table b/make/openvex.table new file mode 100644 index 000000000000..2026fed3377d --- /dev/null +++ b/make/openvex.table @@ -0,0 +1,226 @@ +{ + "otp-26": [ + { + "pkg:github/madler/zlib@04f42ceca40f73e2978b50e93806c2a18c1281fc": "CVE-2023-45853", + "status": { "not_affected": "vulnerable_code_not_present", + "apps": ["pkg:otp/erts@14.0"]} + }, + { + "pkg:github/openssl/openssl@01d5e2318405362b4de5e670c90d9b40a351d053": "CVE-2023-6129", + "status": { "not_affected": "vulnerable_code_not_present", + "apps": ["pkg:otp/erts@14.0", "pkg:otp/erl_interface@5.4"]} + }, + { + "pkg:github/openssl/openssl@01d5e2318405362b4de5e670c90d9b40a351d053": "CVE-2023-6237", + "status": { "not_affected": "vulnerable_code_not_present", + "apps": ["pkg:otp/erts@14.0", "pkg:otp/erl_interface@5.4"]} + }, + { + "pkg:github/openssl/openssl@01d5e2318405362b4de5e670c90d9b40a351d053": "CVE-2024-0727", + "status": { "not_affected": "vulnerable_code_not_present", + "apps": ["pkg:otp/erts@14.0", "pkg:otp/erl_interface@5.4"]} + }, + { + "pkg:github/openssl/openssl@01d5e2318405362b4de5e670c90d9b40a351d053": "CVE-2024-13176", + "status": { "not_affected": "vulnerable_code_not_present", + "apps": ["pkg:otp/erts@14.0", "pkg:otp/erl_interface@5.4"]} + }, + { + "pkg:github/openssl/openssl@01d5e2318405362b4de5e670c90d9b40a351d053": "CVE-2024-2511", + "status": { "not_affected": "vulnerable_code_not_present", + "apps": ["pkg:otp/erts@14.0", "pkg:otp/erl_interface@5.4"]} + }, + { + "pkg:github/openssl/openssl@01d5e2318405362b4de5e670c90d9b40a351d053": "CVE-2024-4603", + "status": { "not_affected": "vulnerable_code_not_present", + "apps": ["pkg:otp/erts@14.0", "pkg:otp/erl_interface@5.4"]} + }, + { + "pkg:github/openssl/openssl@01d5e2318405362b4de5e670c90d9b40a351d053": "CVE-2024-4741", + "status": { "not_affected": "vulnerable_code_not_present", + "apps": ["pkg:otp/erts@14.0", "pkg:otp/erl_interface@5.4"]} + }, + { + "pkg:github/openssl/openssl@01d5e2318405362b4de5e670c90d9b40a351d053": "CVE-2024-5535", + "status": { "not_affected": "vulnerable_code_not_present", + "apps": ["pkg:otp/erts@14.0", "pkg:otp/erl_interface@5.4"]} + }, + { + "pkg:github/openssl/openssl@01d5e2318405362b4de5e670c90d9b40a351d053": "CVE-2024-6119", + "status": { "not_affected": "vulnerable_code_not_present", + "apps": ["pkg:otp/erts@14.0", "pkg:otp/erl_interface@5.4"]} + }, + { + "pkg:github/openssl/openssl@01d5e2318405362b4de5e670c90d9b40a351d053": "CVE-2024-9143", + "status": { "not_affected": "vulnerable_code_not_present", + "apps": ["pkg:otp/erts@14.0", "pkg:otp/erl_interface@5.4"]} + }, + { + "pkg:github/openssl/openssl@01d5e2318405362b4de5e670c90d9b40a351d053": "CVE-2025-4575", + "status": { "not_affected": "vulnerable_code_not_present", + "apps": ["pkg:otp/erts@14.0", "pkg:otp/erl_interface@5.4"]} + }, + { + "pkg:otp/ssh@5.1": "CVE-2023-48795", + "status": { "affected": "Mitigation: If strict KEX availability cannot be ensured on both connection sides, affected encryption modes(CHACHA and CBC) can be disabled with standard ssh configuration. This will provide protection against vulnerability, but at a cost of affecting interoperability", + "fixed": ["pkg:otp/ssh@5.1.1"] + } + }, + { + "pkg:otp/ssh@5.0": "CVE-2025-26618", + "status": { "affected": "Update to the next version", + "fixed": ["pkg:otp/ssh@5.1.4.6"] + } + }, + { + "pkg:otp/ssh@5.1.4.7": "CVE-2025-32433", + "status": { "affected": "A temporary workaround involves disabling the SSH server or to prevent access via firewall rules.", + "fixed": ["pkg:otp/ssh@5.1.4.8"] + } + }, + { + "pkg:otp/ssh@5.1.1": "CVE-2025-46712", + "status": { "affected": "Update to the next version", + "fixed": ["pkg:otp/ssh@5.1.4.9"] + } + }, + { + "pkg:otp/stdlib@5.0": "CVE-2025-4748", + "status": { "affected": "Mitigation: Update to pkg:otp/stdlib@5.2.3.4", + "fixed": ["pkg:otp/stdlib@5.2.3.4"] + } + }, + { + "pkg:otp/ssh@5.0": "CVE-2025-30211", + "status": { "affected": "Workaround: set option `parallel_login` to false. Reduce `max_sessions` option.", + "fixed": ["pkg:otp/ssh@5.1.4.7"] + } + }, + { + "pkg:otp/ssl@11.1": "CVE-2025-53846", + "status": { "affected": "Update to ssl@11.1.4.6", + "fixed": ["pkg:otp/ssl@11.1.4.6"] + } + } + ], + "otp-27": [ + { + "pkg:github/madler/zlib@04f42ceca40f73e2978b50e93806c2a18c1281fc": "CVE-2023-45853", + "status": { "not_affected": "vulnerable_code_not_present", + "apps": ["pkg:otp/erts@15.0"]} + }, + { + "pkg:github/openssl/openssl@01d5e2318405362b4de5e670c90d9b40a351d053": "CVE-2023-6129", + "status": { "not_affected": "vulnerable_code_not_present", + "apps": ["pkg:otp/erts@15.0", "pkg:otp/erl_interface@5.5.2"]} + }, + { + "pkg:github/openssl/openssl@01d5e2318405362b4de5e670c90d9b40a351d053": "CVE-2023-6237", + "status": { "not_affected": "vulnerable_code_not_present", + "apps": ["pkg:otp/erts@15.0", "pkg:otp/erl_interface@5.5.2"]} + }, + { + "pkg:github/openssl/openssl@01d5e2318405362b4de5e670c90d9b40a351d053": "CVE-2024-0727", + "status": { "not_affected": "vulnerable_code_not_present", + "apps": ["pkg:otp/erts@15.0", "pkg:otp/erl_interface@5.5.2"]} + }, + { + "pkg:github/openssl/openssl@01d5e2318405362b4de5e670c90d9b40a351d053": "CVE-2024-13176", + "status": { "not_affected": "vulnerable_code_not_present", + "apps": ["pkg:otp/erts@15.0", "pkg:otp/erl_interface@5.5.2"]} + }, + { + "pkg:github/openssl/openssl@01d5e2318405362b4de5e670c90d9b40a351d053": "CVE-2024-2511", + "status": { "not_affected": "vulnerable_code_not_present", + "apps": ["pkg:otp/erts@15.0", "pkg:otp/erl_interface@5.5.2"]} + }, + { + "pkg:github/openssl/openssl@01d5e2318405362b4de5e670c90d9b40a351d053": "CVE-2024-4603", + "status": { "not_affected": "vulnerable_code_not_present", + "apps": ["pkg:otp/erts@15.0", "pkg:otp/erl_interface@5.5.2"]} + }, + { + "pkg:github/openssl/openssl@01d5e2318405362b4de5e670c90d9b40a351d053": "CVE-2024-4741", + "status": { "not_affected": "vulnerable_code_not_present", + "apps": ["pkg:otp/erts@15.0", "pkg:otp/erl_interface@5.5.2"]} + }, + { + "pkg:github/openssl/openssl@01d5e2318405362b4de5e670c90d9b40a351d053": "CVE-2024-5535", + "status": { "not_affected": "vulnerable_code_not_present", + "apps": ["pkg:otp/erts@15.0", "pkg:otp/erl_interface@5.5.2"]} + }, + { + "pkg:github/openssl/openssl@01d5e2318405362b4de5e670c90d9b40a351d053": "CVE-2024-6119", + "status": { "not_affected": "vulnerable_code_not_present", + "apps": ["pkg:otp/erts@15.0", "pkg:otp/erl_interface@5.5.2"]} + }, + { + "pkg:github/openssl/openssl@01d5e2318405362b4de5e670c90d9b40a351d053": "CVE-2024-9143", + "status": { "not_affected": "vulnerable_code_not_present", + "apps": ["pkg:otp/erts@15.0", "pkg:otp/erl_interface@5.5.2"]} + }, + { + "pkg:github/openssl/openssl@01d5e2318405362b4de5e670c90d9b40a351d053": "CVE-2025-4575", + "status": { "not_affected": "vulnerable_code_not_present", + "apps": ["pkg:otp/erts@15.0", "pkg:otp/erl_interface@5.5.2"]} + }, + { + "pkg:otp/ssh@5.2": "CVE-2025-26618", + "status": { "affected": "Update to the next version", + "fixed": ["pkg:otp/ssh@5.2.7"] + } + }, + { + "pkg:otp/ssh@5.2.9": "CVE-2025-32433", + "status": { "affected": "A temporary workaround involves disabling the SSH server or to prevent access via firewall rules.", + "fixed": ["pkg:otp/ssh@5.2.10"] + } + }, + { + "pkg:otp/ssh@5.2": "CVE-2025-46712", + "status": { "affected": "Update to ssh@5.2.11", + "fixed": ["pkg:otp/ssh@5.2.11"] + } + }, + { + "pkg:otp/stdlib@6.0": "CVE-2025-4748", + "status": { "affected": "Mitigation: Update to pkg:otp/stdlib@6.2.2.1", + "fixed": ["pkg:otp/stdlib@6.2.2.1"] + } + }, + { + "pkg:otp/ssh@5.2": "CVE-2025-30211", + "status": { "affected": "Workaround: set option `parallel_login` to false. Reduce `max_sessions` option.", + "fixed": ["pkg:otp/ssh@5.2.9"] + } + }, + { + "pkg:otp/ssl@11.2": "CVE-2025-53846", + "status": { "affected": "Update to ssl@11.2.5", + "fixed": ["pkg:otp/ssl@11.2.5"] + } + } + ], + "otp-28": [ + { + "pkg:github/PCRE2Project/pcre2@2dce7761b1831fd3f82a9c2bd5476259d945da4d": "OSV-2025-300", + "status": { "not_affected": "vulnerable_code_not_present", + "apps": ["pkg:otp/erts@16.0"]} + }, + { + "pkg:github/madler/zlib@1a8db63788c34a50e39e273d39b7e1033208aea2": "CVE-2023-45853", + "status": { "not_affected": "vulnerable_code_not_present" } + }, + { + "pkg:otp/stdlib@7.0": "CVE-2025-4748", + "status": { "affected": "Mitigation: Update to pkg:otp/stdlib@7.0.1", + "fixed": ["pkg:otp/stdlib@7.0.1"] + } + }, + { + "pkg:github/openssl/openssl@01d5e2318405362b4de5e670c90d9b40a351d053": "CVE-2025-4575", + "status": { "not_affected": "vulnerable_code_not_present", + "apps": ["pkg:otp/erts@16.0", "pkg:otp/erl_interface@5.6"]} + } + ] +} diff --git a/make/openvex.table.license b/make/openvex.table.license new file mode 100644 index 000000000000..1ea854fee3f9 --- /dev/null +++ b/make/openvex.table.license @@ -0,0 +1,7 @@ +%CopyrightBegin% + +SPDX-License-Identifier: Apache-2.0 + +Copyright Ericsson AB 2025. All Rights Reserved. + +%CopyrightEnd% diff --git a/system/doc/README.md b/system/doc/README.md index 684a71de1e62..7ffa17570f17 100644 --- a/system/doc/README.md +++ b/system/doc/README.md @@ -44,3 +44,6 @@ to use Erlang/OTP and different aspects of working with Erlang/OTP. The guides a interoperability between Erlang and C. * [Embedded Systems User's Guide](embedded/embedded.md) - This section describes the issues that are specific for running Erlang on an embedded system. +* [VEX Statements](vex/vulnerabilities.md) - + This section describes how Erlang/OTP reports OpenVex statements and their meaning + towards third parties. diff --git a/system/doc/docs.exs b/system/doc/docs.exs index aac54c3809eb..081ccd107498 100644 --- a/system/doc/docs.exs +++ b/system/doc/docs.exs @@ -31,6 +31,7 @@ "system_principles/upgrade.md": [], "system_principles/versions.md": [], "system_principles/misc.md": [], + "vulnerabilities/vulnerabilities.md": [], "embedded/embedded.md": [], "getting_started/getting_started.md": [], "getting_started/seq_prog.md": [], diff --git a/system/doc/guides b/system/doc/guides index 784ff2ba91d3..879b977c795e 100644 --- a/system/doc/guides +++ b/system/doc/guides @@ -7,3 +7,4 @@ reference_manual:Erlang Reference Manual efficiency_guide:Efficiency Guide tutorial:Interoperability Tutorial embedded:Embedded Systems User's Guide +vulnerabilities:VEX Statements diff --git a/system/doc/guides.license b/system/doc/guides.license new file mode 100644 index 000000000000..f80cadf75c69 --- /dev/null +++ b/system/doc/guides.license @@ -0,0 +1,19 @@ +%CopyrightBegin% + +SPDX-License-Identifier: Apache-2.0 + +Copyright Ericsson AB 2024. All Rights Reserved. + +Licensed under the Apache License, Version 2.0 (the "License"); +you may not use this file except in compliance with the License. +You may obtain a copy of the License at + + http://www.apache.org/licenses/LICENSE-2.0 + +Unless required by applicable law or agreed to in writing, software +distributed under the License is distributed on an "AS IS" BASIS, +WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied. +See the License for the specific language governing permissions and +limitations under the License. + +%CopyrightEnd% diff --git a/system/doc/vulnerabilities/vulnerabilities.md b/system/doc/vulnerabilities/vulnerabilities.md new file mode 100644 index 000000000000..8011553d1523 --- /dev/null +++ b/system/doc/vulnerabilities/vulnerabilities.md @@ -0,0 +1,139 @@ + + +# Vulnerabilities + +[](){: #vulnerabilities } + +## Introduction + +This section describes how Erlang/OTP reports vulnerabilities for Erlang/OTP +CVEs and third party dependencies on which Erlang/OTP builds upon. + +Erlang/OTP reports all vulnerabilities using the [OpenVEX +specification](https://github.com/openvex/spec). This specification allows to +easily describe which CVEs affect which Erlang/OTP versions and specific OTP +applications. It also records which CVEs from third parties affect (or do not +affect) Erlang/OTP. + +Erlang/OTP releases OpenVEX statements under `vex/otp-.openvex.json` in +the [Erlang/OTP Github repository](https://github.com/erlang/otp) in the `master` branch, where +`` corresponds to the number of the Erlang/OTP release. + +## Erlang/OTP VEX Statements + +Erlang/OTP OpenVEX statements specify which Erlang/OTP versions are affected/fixed (e.g., +`pkg:otp/erlang@27.3.1`), as well as the specific Erlang/OTP application number +of all affected versions (e.g., `pkg:otp/ssh@5.2.9`). + +As an example, a snippet of the `vex/otp-27.openvex.json` contains the +vulnerability identified by `CVE-2025-32433`, following by the status of the +vulnerability (`affected`), the affected Erlang/OTP releases, namely `27.3.1` +and `27.3.2`, and the Erlang/OTP application that was vulnerable, `ssh@5.2.9`. +The affected versions are reported using the release version and the +application because it is possible to update the application independently +from the release. +In some cases, there may be an optional action statement that describes a workaround +to avoid the mentioned vulnerability. + +``` +{ + "vulnerability": { + "name": "CVE-2025-32433" + }, + "timestamp": "2025-06-18T12:18:16.661272703+02:00", + "products": [ + { "@id": "pkg:otp/erlang@27.3.1" }, + { "@id": "pkg:otp/erlang@27.3.2" }, + { "@id": "pkg:otp/ssh@5.2.9" } + ], + "status": "affected", + "action_statement": "A temporary workaround involves disabling the SSH server or to prevent access via firewall rules.", + "action_statement_timestamp": "2025-06-18T12:18:16.661272703+02:00" +}, +``` + +The fixed version will be reported in a similar fashion as follows, in the same document. +As an example, there is a new statement for `CVE-2025-32433` with status `fixed`, +that links to the versions that do not suffer from `CVE-2025-32433`, namely +`erlang@27.3.3` and `otp/ssh@5.2.10`. + +``` +{ + "vulnerability": { + "name": "CVE-2025-32433" + }, + "timestamp": "2025-06-18T12:18:16.676540081+02:00", + "products": [ + { "@id": "pkg:otp/erlang@27.3.3" }, + { "@id": "pkg:otp/ssh@5.2.10" } + ], + "status": "fixed" +}, +``` + +## Third Party VEX Statements + +Erlang/OTP generates statements for 3rd parties from which the project depends +on. It is really important to understand the scope of the third party +applications, since Erlang/OTP vendors some libraries as part of the runtime. + +Vendoring means that Erlang/OTP code contains a local copy of a library. +There are numerous use cases for why this is necessary, and we will not cover the use cases here. + +**This excludes dynamically or statically linked libraries during the Erlang/OTP build process. For instance, any security related Erlang application will rely on dynamically or statically linked version of OpenSSL cryptolib.** + +Erlang/OTP reports vulnerabilities for any source code that is vulnerable and +included in the Erlang/OTP release. + +The OpenVEX statements for our third party libraries specify the affected/fixed +version using the commit SHA1 from their respective repository. This is simply +because our third party dependencies are in C/C++ and vulnerability scanners +such as OSV report vulnerabilities in ranges. + +As an example, we mention that the OpenSSL code that Erlang/OTP vendors +is not susceptible for `CVE-2023-6129`, as follows: + +``` +{ + "vulnerability": { + "name": "CVE-2023-6129" + }, + "timestamp": "2025-06-18T12:18:16.47247833+02:00", + "products": [ + { "@id": "pkg:github/openssl/openssl@01d5e2318405362b4de5e670c90d9b40a351d053" } + ], + "status": "not_affected", + "justification": "vulnerable_code_not_present" +} +``` + +Diving into the example, this means that Erlang/OTP vendors a version of `openssl` taken from commit `01d5e2318405362b4de5e670c90d9b40a351d053` from the repository `https://github.com/openssl/openssl/commit/01d5e2318405362b4de5e670c90d9b40a351d053` (version of OpenSSL 3.1.4). The `openssl` code that Erlang/OTP vendors can be found in `./lib/erl_interface/src/openssl/` and `./erts/emulator/openssl/`. The OpenVEX statement claims that the code in those folders is not susceptible to `CVE-2023-6129`. The claim is towards **source code existing in Erlang/OTP**. + +In other words, the `not_affected` status refers to the library that Erlang/OTP vendors for OpenSSL (the library that comes +included with Erlang/OTP). If you build Erlang/OTP and link to any OpenSSL version (e.g., 3.5.2 or even 3.1.4) during the building process, +your project has now a new build and runtime dependency and may be subject to `CVE-2023-6129`. + +## Windows Binaries + +For the time being, Erlang/OTP Windows binaries are not reported in the OpenVEX +specification. diff --git a/vex/otp-26.openvex.json b/vex/otp-26.openvex.json new file mode 100644 index 000000000000..7d65656b1cc8 --- /dev/null +++ b/vex/otp-26.openvex.json @@ -0,0 +1,2760 @@ +{ + "@context": "https://openvex.dev/ns/v0.2.0", + "@id": "https://openvex.dev/docs/public/otp/vex-otp-26", + "author": "vexctl", + "timestamp": "2025-08-21T10:56:51.352964+02:00", + "last_updated": "2025-08-21T10:57:18.466086841+02:00", + "version": 39, + "statements": [ + { + "vulnerability": { + "name": "CVE-2023-45853" + }, + "timestamp": "2025-08-21T10:57:17.822976152+02:00", + "products": [ + { + "@id": "pkg:github/otp/erlang@OTP-26.0" + }, + { + "@id": "pkg:otp/erts@14.0" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.0.1" + }, + { + "@id": "pkg:otp/erts@14.0.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.0.2" + }, + { + "@id": "pkg:otp/erts@14.0.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.1.1" + }, + { + "@id": "pkg:otp/erts@14.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.1.2" + }, + { + "@id": "pkg:otp/erts@14.1.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2" + }, + { + "@id": "pkg:otp/erts@14.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.1" + }, + { + "@id": "pkg:otp/erts@14.2.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.2" + }, + { + "@id": "pkg:otp/erts@14.2.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.3" + }, + { + "@id": "pkg:otp/erts@14.2.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.4" + }, + { + "@id": "pkg:otp/erts@14.2.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5" + }, + { + "@id": "pkg:otp/erts@14.2.5" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.1" + }, + { + "@id": "pkg:otp/erts@14.2.5.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.2" + }, + { + "@id": "pkg:otp/erts@14.2.5.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.3" + }, + { + "@id": "pkg:otp/erts@14.2.5.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.5" + }, + { + "@id": "pkg:otp/erts@14.2.5.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.6" + }, + { + "@id": "pkg:otp/erts@14.2.5.5" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.7" + }, + { + "@id": "pkg:otp/erts@14.2.5.6" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.8" + }, + { + "@id": "pkg:otp/erts@14.2.5.7" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.9" + }, + { + "@id": "pkg:otp/erts@14.2.5.8" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.10" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.11" + }, + { + "@id": "pkg:otp/erts@14.2.5.9" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.12" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.13" + }, + { + "@id": "pkg:otp/erts@14.2.5.10" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.14" + }, + { + "@id": "pkg:otp/erts@14.2.5.11" + } + ], + "status": "not_affected", + "justification": "vulnerable_code_not_present" + }, + { + "vulnerability": { + "name": "CVE-2023-45853" + }, + "timestamp": "2025-08-21T10:57:17.838572327+02:00", + "products": [ + { + "@id": "pkg:github/madler/zlib@04f42ceca40f73e2978b50e93806c2a18c1281fc" + } + ], + "status": "not_affected", + "justification": "vulnerable_code_not_present" + }, + { + "vulnerability": { + "name": "CVE-2023-6129" + }, + "timestamp": "2025-08-21T10:57:17.854663547+02:00", + "products": [ + { + "@id": "pkg:github/otp/erlang@OTP-26.0" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.0.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.0.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.1.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.1.2" + }, + { + "@id": "pkg:otp/erl_interface@5.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.1" + }, + { + "@id": "pkg:otp/erl_interface@5.5" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.5" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.6" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.7" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.8" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.9" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.10" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.11" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.12" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.13" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.14" + }, + { + "@id": "pkg:otp/erl_interface@5.5.1" + }, + { + "@id": "pkg:otp/erts@14.0" + }, + { + "@id": "pkg:otp/erts@14.0.1" + }, + { + "@id": "pkg:otp/erts@14.0.2" + }, + { + "@id": "pkg:otp/erts@14.1" + }, + { + "@id": "pkg:otp/erts@14.1.1" + }, + { + "@id": "pkg:otp/erts@14.2" + }, + { + "@id": "pkg:otp/erts@14.2.1" + }, + { + "@id": "pkg:otp/erts@14.2.2" + }, + { + "@id": "pkg:otp/erts@14.2.3" + }, + { + "@id": "pkg:otp/erts@14.2.4" + }, + { + "@id": "pkg:otp/erts@14.2.5" + }, + { + "@id": "pkg:otp/erts@14.2.5.1" + }, + { + "@id": "pkg:otp/erts@14.2.5.2" + }, + { + "@id": "pkg:otp/erts@14.2.5.3" + }, + { + "@id": "pkg:otp/erts@14.2.5.4" + }, + { + "@id": "pkg:otp/erts@14.2.5.5" + }, + { + "@id": "pkg:otp/erts@14.2.5.6" + }, + { + "@id": "pkg:otp/erts@14.2.5.7" + }, + { + "@id": "pkg:otp/erts@14.2.5.8" + }, + { + "@id": "pkg:otp/erts@14.2.5.9" + }, + { + "@id": "pkg:otp/erts@14.2.5.10" + }, + { + "@id": "pkg:otp/erts@14.2.5.11" + } + ], + "status": "not_affected", + "justification": "vulnerable_code_not_present" + }, + { + "vulnerability": { + "name": "CVE-2023-6129" + }, + "timestamp": "2025-08-21T10:57:17.870865298+02:00", + "products": [ + { + "@id": "pkg:github/openssl/openssl@01d5e2318405362b4de5e670c90d9b40a351d053" + } + ], + "status": "not_affected", + "justification": "vulnerable_code_not_present" + }, + { + "vulnerability": { + "name": "CVE-2023-6237" + }, + "timestamp": "2025-08-21T10:57:17.887761585+02:00", + "products": [ + { + "@id": "pkg:github/otp/erlang@OTP-26.0" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.0.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.0.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.1.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.1.2" + }, + { + "@id": "pkg:otp/erl_interface@5.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.1" + }, + { + "@id": "pkg:otp/erl_interface@5.5" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.5" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.6" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.7" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.8" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.9" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.10" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.11" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.12" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.13" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.14" + }, + { + "@id": "pkg:otp/erl_interface@5.5.1" + }, + { + "@id": "pkg:otp/erts@14.0" + }, + { + "@id": "pkg:otp/erts@14.0.1" + }, + { + "@id": "pkg:otp/erts@14.0.2" + }, + { + "@id": "pkg:otp/erts@14.1" + }, + { + "@id": "pkg:otp/erts@14.1.1" + }, + { + "@id": "pkg:otp/erts@14.2" + }, + { + "@id": "pkg:otp/erts@14.2.1" + }, + { + "@id": "pkg:otp/erts@14.2.2" + }, + { + "@id": "pkg:otp/erts@14.2.3" + }, + { + "@id": "pkg:otp/erts@14.2.4" + }, + { + "@id": "pkg:otp/erts@14.2.5" + }, + { + "@id": "pkg:otp/erts@14.2.5.1" + }, + { + "@id": "pkg:otp/erts@14.2.5.2" + }, + { + "@id": "pkg:otp/erts@14.2.5.3" + }, + { + "@id": "pkg:otp/erts@14.2.5.4" + }, + { + "@id": "pkg:otp/erts@14.2.5.5" + }, + { + "@id": "pkg:otp/erts@14.2.5.6" + }, + { + "@id": "pkg:otp/erts@14.2.5.7" + }, + { + "@id": "pkg:otp/erts@14.2.5.8" + }, + { + "@id": "pkg:otp/erts@14.2.5.9" + }, + { + "@id": "pkg:otp/erts@14.2.5.10" + }, + { + "@id": "pkg:otp/erts@14.2.5.11" + } + ], + "status": "not_affected", + "justification": "vulnerable_code_not_present" + }, + { + "vulnerability": { + "name": "CVE-2023-6237" + }, + "timestamp": "2025-08-21T10:57:17.902536215+02:00", + "products": [ + { + "@id": "pkg:github/openssl/openssl@01d5e2318405362b4de5e670c90d9b40a351d053" + } + ], + "status": "not_affected", + "justification": "vulnerable_code_not_present" + }, + { + "vulnerability": { + "name": "CVE-2024-0727" + }, + "timestamp": "2025-08-21T10:57:17.918592468+02:00", + "products": [ + { + "@id": "pkg:github/otp/erlang@OTP-26.0" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.0.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.0.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.1.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.1.2" + }, + { + "@id": "pkg:otp/erl_interface@5.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.1" + }, + { + "@id": "pkg:otp/erl_interface@5.5" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.5" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.6" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.7" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.8" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.9" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.10" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.11" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.12" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.13" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.14" + }, + { + "@id": "pkg:otp/erl_interface@5.5.1" + }, + { + "@id": "pkg:otp/erts@14.0" + }, + { + "@id": "pkg:otp/erts@14.0.1" + }, + { + "@id": "pkg:otp/erts@14.0.2" + }, + { + "@id": "pkg:otp/erts@14.1" + }, + { + "@id": "pkg:otp/erts@14.1.1" + }, + { + "@id": "pkg:otp/erts@14.2" + }, + { + "@id": "pkg:otp/erts@14.2.1" + }, + { + "@id": "pkg:otp/erts@14.2.2" + }, + { + "@id": "pkg:otp/erts@14.2.3" + }, + { + "@id": "pkg:otp/erts@14.2.4" + }, + { + "@id": "pkg:otp/erts@14.2.5" + }, + { + "@id": "pkg:otp/erts@14.2.5.1" + }, + { + "@id": "pkg:otp/erts@14.2.5.2" + }, + { + "@id": "pkg:otp/erts@14.2.5.3" + }, + { + "@id": "pkg:otp/erts@14.2.5.4" + }, + { + "@id": "pkg:otp/erts@14.2.5.5" + }, + { + "@id": "pkg:otp/erts@14.2.5.6" + }, + { + "@id": "pkg:otp/erts@14.2.5.7" + }, + { + "@id": "pkg:otp/erts@14.2.5.8" + }, + { + "@id": "pkg:otp/erts@14.2.5.9" + }, + { + "@id": "pkg:otp/erts@14.2.5.10" + }, + { + "@id": "pkg:otp/erts@14.2.5.11" + } + ], + "status": "not_affected", + "justification": "vulnerable_code_not_present" + }, + { + "vulnerability": { + "name": "CVE-2024-0727" + }, + "timestamp": "2025-08-21T10:57:17.93416404+02:00", + "products": [ + { + "@id": "pkg:github/openssl/openssl@01d5e2318405362b4de5e670c90d9b40a351d053" + } + ], + "status": "not_affected", + "justification": "vulnerable_code_not_present" + }, + { + "vulnerability": { + "name": "CVE-2024-13176" + }, + "timestamp": "2025-08-21T10:57:17.949944484+02:00", + "products": [ + { + "@id": "pkg:github/otp/erlang@OTP-26.0" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.0.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.0.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.1.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.1.2" + }, + { + "@id": "pkg:otp/erl_interface@5.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.1" + }, + { + "@id": "pkg:otp/erl_interface@5.5" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.5" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.6" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.7" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.8" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.9" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.10" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.11" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.12" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.13" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.14" + }, + { + "@id": "pkg:otp/erl_interface@5.5.1" + }, + { + "@id": "pkg:otp/erts@14.0" + }, + { + "@id": "pkg:otp/erts@14.0.1" + }, + { + "@id": "pkg:otp/erts@14.0.2" + }, + { + "@id": "pkg:otp/erts@14.1" + }, + { + "@id": "pkg:otp/erts@14.1.1" + }, + { + "@id": "pkg:otp/erts@14.2" + }, + { + "@id": "pkg:otp/erts@14.2.1" + }, + { + "@id": "pkg:otp/erts@14.2.2" + }, + { + "@id": "pkg:otp/erts@14.2.3" + }, + { + "@id": "pkg:otp/erts@14.2.4" + }, + { + "@id": "pkg:otp/erts@14.2.5" + }, + { + "@id": "pkg:otp/erts@14.2.5.1" + }, + { + "@id": "pkg:otp/erts@14.2.5.2" + }, + { + "@id": "pkg:otp/erts@14.2.5.3" + }, + { + "@id": "pkg:otp/erts@14.2.5.4" + }, + { + "@id": "pkg:otp/erts@14.2.5.5" + }, + { + "@id": "pkg:otp/erts@14.2.5.6" + }, + { + "@id": "pkg:otp/erts@14.2.5.7" + }, + { + "@id": "pkg:otp/erts@14.2.5.8" + }, + { + "@id": "pkg:otp/erts@14.2.5.9" + }, + { + "@id": "pkg:otp/erts@14.2.5.10" + }, + { + "@id": "pkg:otp/erts@14.2.5.11" + } + ], + "status": "not_affected", + "justification": "vulnerable_code_not_present" + }, + { + "vulnerability": { + "name": "CVE-2024-13176" + }, + "timestamp": "2025-08-21T10:57:17.96533611+02:00", + "products": [ + { + "@id": "pkg:github/openssl/openssl@01d5e2318405362b4de5e670c90d9b40a351d053" + } + ], + "status": "not_affected", + "justification": "vulnerable_code_not_present" + }, + { + "vulnerability": { + "name": "CVE-2024-2511" + }, + "timestamp": "2025-08-21T10:57:17.980859866+02:00", + "products": [ + { + "@id": "pkg:github/otp/erlang@OTP-26.0" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.0.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.0.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.1.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.1.2" + }, + { + "@id": "pkg:otp/erl_interface@5.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.1" + }, + { + "@id": "pkg:otp/erl_interface@5.5" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.5" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.6" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.7" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.8" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.9" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.10" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.11" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.12" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.13" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.14" + }, + { + "@id": "pkg:otp/erl_interface@5.5.1" + }, + { + "@id": "pkg:otp/erts@14.0" + }, + { + "@id": "pkg:otp/erts@14.0.1" + }, + { + "@id": "pkg:otp/erts@14.0.2" + }, + { + "@id": "pkg:otp/erts@14.1" + }, + { + "@id": "pkg:otp/erts@14.1.1" + }, + { + "@id": "pkg:otp/erts@14.2" + }, + { + "@id": "pkg:otp/erts@14.2.1" + }, + { + "@id": "pkg:otp/erts@14.2.2" + }, + { + "@id": "pkg:otp/erts@14.2.3" + }, + { + "@id": "pkg:otp/erts@14.2.4" + }, + { + "@id": "pkg:otp/erts@14.2.5" + }, + { + "@id": "pkg:otp/erts@14.2.5.1" + }, + { + "@id": "pkg:otp/erts@14.2.5.2" + }, + { + "@id": "pkg:otp/erts@14.2.5.3" + }, + { + "@id": "pkg:otp/erts@14.2.5.4" + }, + { + "@id": "pkg:otp/erts@14.2.5.5" + }, + { + "@id": "pkg:otp/erts@14.2.5.6" + }, + { + "@id": "pkg:otp/erts@14.2.5.7" + }, + { + "@id": "pkg:otp/erts@14.2.5.8" + }, + { + "@id": "pkg:otp/erts@14.2.5.9" + }, + { + "@id": "pkg:otp/erts@14.2.5.10" + }, + { + "@id": "pkg:otp/erts@14.2.5.11" + } + ], + "status": "not_affected", + "justification": "vulnerable_code_not_present" + }, + { + "vulnerability": { + "name": "CVE-2024-2511" + }, + "timestamp": "2025-08-21T10:57:17.996629277+02:00", + "products": [ + { + "@id": "pkg:github/openssl/openssl@01d5e2318405362b4de5e670c90d9b40a351d053" + } + ], + "status": "not_affected", + "justification": "vulnerable_code_not_present" + }, + { + "vulnerability": { + "name": "CVE-2024-4603" + }, + "timestamp": "2025-08-21T10:57:18.012608222+02:00", + "products": [ + { + "@id": "pkg:github/otp/erlang@OTP-26.0" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.0.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.0.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.1.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.1.2" + }, + { + "@id": "pkg:otp/erl_interface@5.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.1" + }, + { + "@id": "pkg:otp/erl_interface@5.5" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.5" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.6" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.7" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.8" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.9" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.10" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.11" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.12" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.13" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.14" + }, + { + "@id": "pkg:otp/erl_interface@5.5.1" + }, + { + "@id": "pkg:otp/erts@14.0" + }, + { + "@id": "pkg:otp/erts@14.0.1" + }, + { + "@id": "pkg:otp/erts@14.0.2" + }, + { + "@id": "pkg:otp/erts@14.1" + }, + { + "@id": "pkg:otp/erts@14.1.1" + }, + { + "@id": "pkg:otp/erts@14.2" + }, + { + "@id": "pkg:otp/erts@14.2.1" + }, + { + "@id": "pkg:otp/erts@14.2.2" + }, + { + "@id": "pkg:otp/erts@14.2.3" + }, + { + "@id": "pkg:otp/erts@14.2.4" + }, + { + "@id": "pkg:otp/erts@14.2.5" + }, + { + "@id": "pkg:otp/erts@14.2.5.1" + }, + { + "@id": "pkg:otp/erts@14.2.5.2" + }, + { + "@id": "pkg:otp/erts@14.2.5.3" + }, + { + "@id": "pkg:otp/erts@14.2.5.4" + }, + { + "@id": "pkg:otp/erts@14.2.5.5" + }, + { + "@id": "pkg:otp/erts@14.2.5.6" + }, + { + "@id": "pkg:otp/erts@14.2.5.7" + }, + { + "@id": "pkg:otp/erts@14.2.5.8" + }, + { + "@id": "pkg:otp/erts@14.2.5.9" + }, + { + "@id": "pkg:otp/erts@14.2.5.10" + }, + { + "@id": "pkg:otp/erts@14.2.5.11" + } + ], + "status": "not_affected", + "justification": "vulnerable_code_not_present" + }, + { + "vulnerability": { + "name": "CVE-2024-4603" + }, + "timestamp": "2025-08-21T10:57:18.029498892+02:00", + "products": [ + { + "@id": "pkg:github/openssl/openssl@01d5e2318405362b4de5e670c90d9b40a351d053" + } + ], + "status": "not_affected", + "justification": "vulnerable_code_not_present" + }, + { + "vulnerability": { + "name": "CVE-2024-4741" + }, + "timestamp": "2025-08-21T10:57:18.05289133+02:00", + "products": [ + { + "@id": "pkg:github/otp/erlang@OTP-26.0" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.0.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.0.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.1.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.1.2" + }, + { + "@id": "pkg:otp/erl_interface@5.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.1" + }, + { + "@id": "pkg:otp/erl_interface@5.5" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.5" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.6" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.7" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.8" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.9" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.10" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.11" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.12" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.13" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.14" + }, + { + "@id": "pkg:otp/erl_interface@5.5.1" + }, + { + "@id": "pkg:otp/erts@14.0" + }, + { + "@id": "pkg:otp/erts@14.0.1" + }, + { + "@id": "pkg:otp/erts@14.0.2" + }, + { + "@id": "pkg:otp/erts@14.1" + }, + { + "@id": "pkg:otp/erts@14.1.1" + }, + { + "@id": "pkg:otp/erts@14.2" + }, + { + "@id": "pkg:otp/erts@14.2.1" + }, + { + "@id": "pkg:otp/erts@14.2.2" + }, + { + "@id": "pkg:otp/erts@14.2.3" + }, + { + "@id": "pkg:otp/erts@14.2.4" + }, + { + "@id": "pkg:otp/erts@14.2.5" + }, + { + "@id": "pkg:otp/erts@14.2.5.1" + }, + { + "@id": "pkg:otp/erts@14.2.5.2" + }, + { + "@id": "pkg:otp/erts@14.2.5.3" + }, + { + "@id": "pkg:otp/erts@14.2.5.4" + }, + { + "@id": "pkg:otp/erts@14.2.5.5" + }, + { + "@id": "pkg:otp/erts@14.2.5.6" + }, + { + "@id": "pkg:otp/erts@14.2.5.7" + }, + { + "@id": "pkg:otp/erts@14.2.5.8" + }, + { + "@id": "pkg:otp/erts@14.2.5.9" + }, + { + "@id": "pkg:otp/erts@14.2.5.10" + }, + { + "@id": "pkg:otp/erts@14.2.5.11" + } + ], + "status": "not_affected", + "justification": "vulnerable_code_not_present" + }, + { + "vulnerability": { + "name": "CVE-2024-4741" + }, + "timestamp": "2025-08-21T10:57:18.071457042+02:00", + "products": [ + { + "@id": "pkg:github/openssl/openssl@01d5e2318405362b4de5e670c90d9b40a351d053" + } + ], + "status": "not_affected", + "justification": "vulnerable_code_not_present" + }, + { + "vulnerability": { + "name": "CVE-2024-5535" + }, + "timestamp": "2025-08-21T10:57:18.090268971+02:00", + "products": [ + { + "@id": "pkg:github/otp/erlang@OTP-26.0" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.0.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.0.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.1.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.1.2" + }, + { + "@id": "pkg:otp/erl_interface@5.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.1" + }, + { + "@id": "pkg:otp/erl_interface@5.5" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.5" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.6" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.7" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.8" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.9" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.10" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.11" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.12" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.13" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.14" + }, + { + "@id": "pkg:otp/erl_interface@5.5.1" + }, + { + "@id": "pkg:otp/erts@14.0" + }, + { + "@id": "pkg:otp/erts@14.0.1" + }, + { + "@id": "pkg:otp/erts@14.0.2" + }, + { + "@id": "pkg:otp/erts@14.1" + }, + { + "@id": "pkg:otp/erts@14.1.1" + }, + { + "@id": "pkg:otp/erts@14.2" + }, + { + "@id": "pkg:otp/erts@14.2.1" + }, + { + "@id": "pkg:otp/erts@14.2.2" + }, + { + "@id": "pkg:otp/erts@14.2.3" + }, + { + "@id": "pkg:otp/erts@14.2.4" + }, + { + "@id": "pkg:otp/erts@14.2.5" + }, + { + "@id": "pkg:otp/erts@14.2.5.1" + }, + { + "@id": "pkg:otp/erts@14.2.5.2" + }, + { + "@id": "pkg:otp/erts@14.2.5.3" + }, + { + "@id": "pkg:otp/erts@14.2.5.4" + }, + { + "@id": "pkg:otp/erts@14.2.5.5" + }, + { + "@id": "pkg:otp/erts@14.2.5.6" + }, + { + "@id": "pkg:otp/erts@14.2.5.7" + }, + { + "@id": "pkg:otp/erts@14.2.5.8" + }, + { + "@id": "pkg:otp/erts@14.2.5.9" + }, + { + "@id": "pkg:otp/erts@14.2.5.10" + }, + { + "@id": "pkg:otp/erts@14.2.5.11" + } + ], + "status": "not_affected", + "justification": "vulnerable_code_not_present" + }, + { + "vulnerability": { + "name": "CVE-2024-5535" + }, + "timestamp": "2025-08-21T10:57:18.10914946+02:00", + "products": [ + { + "@id": "pkg:github/openssl/openssl@01d5e2318405362b4de5e670c90d9b40a351d053" + } + ], + "status": "not_affected", + "justification": "vulnerable_code_not_present" + }, + { + "vulnerability": { + "name": "CVE-2024-6119" + }, + "timestamp": "2025-08-21T10:57:18.126555717+02:00", + "products": [ + { + "@id": "pkg:github/otp/erlang@OTP-26.0" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.0.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.0.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.1.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.1.2" + }, + { + "@id": "pkg:otp/erl_interface@5.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.1" + }, + { + "@id": "pkg:otp/erl_interface@5.5" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.5" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.6" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.7" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.8" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.9" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.10" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.11" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.12" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.13" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.14" + }, + { + "@id": "pkg:otp/erl_interface@5.5.1" + }, + { + "@id": "pkg:otp/erts@14.0" + }, + { + "@id": "pkg:otp/erts@14.0.1" + }, + { + "@id": "pkg:otp/erts@14.0.2" + }, + { + "@id": "pkg:otp/erts@14.1" + }, + { + "@id": "pkg:otp/erts@14.1.1" + }, + { + "@id": "pkg:otp/erts@14.2" + }, + { + "@id": "pkg:otp/erts@14.2.1" + }, + { + "@id": "pkg:otp/erts@14.2.2" + }, + { + "@id": "pkg:otp/erts@14.2.3" + }, + { + "@id": "pkg:otp/erts@14.2.4" + }, + { + "@id": "pkg:otp/erts@14.2.5" + }, + { + "@id": "pkg:otp/erts@14.2.5.1" + }, + { + "@id": "pkg:otp/erts@14.2.5.2" + }, + { + "@id": "pkg:otp/erts@14.2.5.3" + }, + { + "@id": "pkg:otp/erts@14.2.5.4" + }, + { + "@id": "pkg:otp/erts@14.2.5.5" + }, + { + "@id": "pkg:otp/erts@14.2.5.6" + }, + { + "@id": "pkg:otp/erts@14.2.5.7" + }, + { + "@id": "pkg:otp/erts@14.2.5.8" + }, + { + "@id": "pkg:otp/erts@14.2.5.9" + }, + { + "@id": "pkg:otp/erts@14.2.5.10" + }, + { + "@id": "pkg:otp/erts@14.2.5.11" + } + ], + "status": "not_affected", + "justification": "vulnerable_code_not_present" + }, + { + "vulnerability": { + "name": "CVE-2024-6119" + }, + "timestamp": "2025-08-21T10:57:18.145001757+02:00", + "products": [ + { + "@id": "pkg:github/openssl/openssl@01d5e2318405362b4de5e670c90d9b40a351d053" + } + ], + "status": "not_affected", + "justification": "vulnerable_code_not_present" + }, + { + "vulnerability": { + "name": "CVE-2024-9143" + }, + "timestamp": "2025-08-21T10:57:18.16294088+02:00", + "products": [ + { + "@id": "pkg:github/otp/erlang@OTP-26.0" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.0.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.0.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.1.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.1.2" + }, + { + "@id": "pkg:otp/erl_interface@5.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.1" + }, + { + "@id": "pkg:otp/erl_interface@5.5" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.5" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.6" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.7" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.8" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.9" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.10" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.11" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.12" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.13" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.14" + }, + { + "@id": "pkg:otp/erl_interface@5.5.1" + }, + { + "@id": "pkg:otp/erts@14.0" + }, + { + "@id": "pkg:otp/erts@14.0.1" + }, + { + "@id": "pkg:otp/erts@14.0.2" + }, + { + "@id": "pkg:otp/erts@14.1" + }, + { + "@id": "pkg:otp/erts@14.1.1" + }, + { + "@id": "pkg:otp/erts@14.2" + }, + { + "@id": "pkg:otp/erts@14.2.1" + }, + { + "@id": "pkg:otp/erts@14.2.2" + }, + { + "@id": "pkg:otp/erts@14.2.3" + }, + { + "@id": "pkg:otp/erts@14.2.4" + }, + { + "@id": "pkg:otp/erts@14.2.5" + }, + { + "@id": "pkg:otp/erts@14.2.5.1" + }, + { + "@id": "pkg:otp/erts@14.2.5.2" + }, + { + "@id": "pkg:otp/erts@14.2.5.3" + }, + { + "@id": "pkg:otp/erts@14.2.5.4" + }, + { + "@id": "pkg:otp/erts@14.2.5.5" + }, + { + "@id": "pkg:otp/erts@14.2.5.6" + }, + { + "@id": "pkg:otp/erts@14.2.5.7" + }, + { + "@id": "pkg:otp/erts@14.2.5.8" + }, + { + "@id": "pkg:otp/erts@14.2.5.9" + }, + { + "@id": "pkg:otp/erts@14.2.5.10" + }, + { + "@id": "pkg:otp/erts@14.2.5.11" + } + ], + "status": "not_affected", + "justification": "vulnerable_code_not_present" + }, + { + "vulnerability": { + "name": "CVE-2024-9143" + }, + "timestamp": "2025-08-21T10:57:18.179983356+02:00", + "products": [ + { + "@id": "pkg:github/openssl/openssl@01d5e2318405362b4de5e670c90d9b40a351d053" + } + ], + "status": "not_affected", + "justification": "vulnerable_code_not_present" + }, + { + "vulnerability": { + "name": "CVE-2025-4575" + }, + "timestamp": "2025-08-21T10:57:18.198993543+02:00", + "products": [ + { + "@id": "pkg:github/otp/erlang@OTP-26.0" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.0.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.0.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.1.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.1.2" + }, + { + "@id": "pkg:otp/erl_interface@5.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.1" + }, + { + "@id": "pkg:otp/erl_interface@5.5" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.5" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.6" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.7" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.8" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.9" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.10" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.11" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.12" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.13" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.14" + }, + { + "@id": "pkg:otp/erl_interface@5.5.1" + }, + { + "@id": "pkg:otp/erts@14.0" + }, + { + "@id": "pkg:otp/erts@14.0.1" + }, + { + "@id": "pkg:otp/erts@14.0.2" + }, + { + "@id": "pkg:otp/erts@14.1" + }, + { + "@id": "pkg:otp/erts@14.1.1" + }, + { + "@id": "pkg:otp/erts@14.2" + }, + { + "@id": "pkg:otp/erts@14.2.1" + }, + { + "@id": "pkg:otp/erts@14.2.2" + }, + { + "@id": "pkg:otp/erts@14.2.3" + }, + { + "@id": "pkg:otp/erts@14.2.4" + }, + { + "@id": "pkg:otp/erts@14.2.5" + }, + { + "@id": "pkg:otp/erts@14.2.5.1" + }, + { + "@id": "pkg:otp/erts@14.2.5.2" + }, + { + "@id": "pkg:otp/erts@14.2.5.3" + }, + { + "@id": "pkg:otp/erts@14.2.5.4" + }, + { + "@id": "pkg:otp/erts@14.2.5.5" + }, + { + "@id": "pkg:otp/erts@14.2.5.6" + }, + { + "@id": "pkg:otp/erts@14.2.5.7" + }, + { + "@id": "pkg:otp/erts@14.2.5.8" + }, + { + "@id": "pkg:otp/erts@14.2.5.9" + }, + { + "@id": "pkg:otp/erts@14.2.5.10" + }, + { + "@id": "pkg:otp/erts@14.2.5.11" + } + ], + "status": "not_affected", + "justification": "vulnerable_code_not_present" + }, + { + "vulnerability": { + "name": "CVE-2025-4575" + }, + "timestamp": "2025-08-21T10:57:18.218784524+02:00", + "products": [ + { + "@id": "pkg:github/openssl/openssl@01d5e2318405362b4de5e670c90d9b40a351d053" + } + ], + "status": "not_affected", + "justification": "vulnerable_code_not_present" + }, + { + "vulnerability": { + "name": "CVE-2023-48795" + }, + "timestamp": "2025-08-21T10:57:18.237876861+02:00", + "products": [ + { + "@id": "pkg:github/otp/erlang@OTP-26.2" + }, + { + "@id": "pkg:otp/ssh@5.1" + } + ], + "status": "affected", + "action_statement": "Mitigation: If strict KEX availability cannot be ensured on both connection sides, affected encryption modes(CHACHA and CBC) can be disabled with standard ssh configuration. This will provide protection against vulnerability, but at a cost of affecting interoperability", + "action_statement_timestamp": "2025-08-21T10:57:18.237876861+02:00" + }, + { + "vulnerability": { + "name": "CVE-2023-48795" + }, + "timestamp": "2025-08-21T10:57:18.254933692+02:00", + "products": [ + { + "@id": "pkg:github/otp/erlang@OTP-26.2.1" + }, + { + "@id": "pkg:otp/ssh@5.1.1" + } + ], + "status": "fixed" + }, + { + "vulnerability": { + "name": "CVE-2025-26618" + }, + "timestamp": "2025-08-21T10:57:18.272581233+02:00", + "products": [ + { + "@id": "pkg:github/otp/erlang@OTP-26.0" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.0.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.0.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.1.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.1.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.5" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.6" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.7" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.8" + }, + { + "@id": "pkg:otp/ssh@5.0" + }, + { + "@id": "pkg:otp/ssh@5.0.1" + }, + { + "@id": "pkg:otp/ssh@5.1" + }, + { + "@id": "pkg:otp/ssh@5.1.1" + }, + { + "@id": "pkg:otp/ssh@5.1.2" + }, + { + "@id": "pkg:otp/ssh@5.1.3" + }, + { + "@id": "pkg:otp/ssh@5.1.4" + }, + { + "@id": "pkg:otp/ssh@5.1.4.1" + }, + { + "@id": "pkg:otp/ssh@5.1.4.2" + }, + { + "@id": "pkg:otp/ssh@5.1.4.3" + }, + { + "@id": "pkg:otp/ssh@5.1.4.4" + }, + { + "@id": "pkg:otp/ssh@5.1.4.5" + } + ], + "status": "affected", + "action_statement": "Update to the next version", + "action_statement_timestamp": "2025-08-21T10:57:18.272581233+02:00" + }, + { + "vulnerability": { + "name": "CVE-2025-26618" + }, + "timestamp": "2025-08-21T10:57:18.289408763+02:00", + "products": [ + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.9" + }, + { + "@id": "pkg:otp/ssh@5.1.4.6" + } + ], + "status": "fixed" + }, + { + "vulnerability": { + "name": "CVE-2025-32433" + }, + "timestamp": "2025-08-21T10:57:18.307530288+02:00", + "products": [ + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.10" + }, + { + "@id": "pkg:otp/ssh@5.1.4.7" + } + ], + "status": "affected", + "action_statement": "A temporary workaround involves disabling the SSH server or to prevent access via firewall rules.", + "action_statement_timestamp": "2025-08-21T10:57:18.307530288+02:00" + }, + { + "vulnerability": { + "name": "CVE-2025-32433" + }, + "timestamp": "2025-08-21T10:57:18.325700745+02:00", + "products": [ + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.11" + }, + { + "@id": "pkg:otp/ssh@5.1.4.8" + } + ], + "status": "fixed" + }, + { + "vulnerability": { + "name": "CVE-2025-46712" + }, + "timestamp": "2025-08-21T10:57:18.343313891+02:00", + "products": [ + { + "@id": "pkg:github/otp/erlang@OTP-26.2.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.5" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.6" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.7" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.8" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.9" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.10" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.11" + }, + { + "@id": "pkg:otp/ssh@5.1.1" + }, + { + "@id": "pkg:otp/ssh@5.1.2" + }, + { + "@id": "pkg:otp/ssh@5.1.3" + }, + { + "@id": "pkg:otp/ssh@5.1.4" + }, + { + "@id": "pkg:otp/ssh@5.1.4.1" + }, + { + "@id": "pkg:otp/ssh@5.1.4.2" + }, + { + "@id": "pkg:otp/ssh@5.1.4.3" + }, + { + "@id": "pkg:otp/ssh@5.1.4.4" + }, + { + "@id": "pkg:otp/ssh@5.1.4.5" + }, + { + "@id": "pkg:otp/ssh@5.1.4.6" + }, + { + "@id": "pkg:otp/ssh@5.1.4.7" + }, + { + "@id": "pkg:otp/ssh@5.1.4.8" + } + ], + "status": "affected", + "action_statement": "Update to the next version", + "action_statement_timestamp": "2025-08-21T10:57:18.343313891+02:00" + }, + { + "vulnerability": { + "name": "CVE-2025-46712" + }, + "timestamp": "2025-08-21T10:57:18.359467613+02:00", + "products": [ + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.12" + }, + { + "@id": "pkg:otp/ssh@5.1.4.9" + } + ], + "status": "fixed" + }, + { + "vulnerability": { + "name": "CVE-2025-4748" + }, + "timestamp": "2025-08-21T10:57:18.376876691+02:00", + "products": [ + { + "@id": "pkg:github/otp/erlang@OTP-26.0" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.0.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.0.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.1.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.1.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.5" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.6" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.7" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.8" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.9" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.10" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.11" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.12" + }, + { + "@id": "pkg:otp/stdlib@5.0" + }, + { + "@id": "pkg:otp/stdlib@5.0.1" + }, + { + "@id": "pkg:otp/stdlib@5.0.2" + }, + { + "@id": "pkg:otp/stdlib@5.1" + }, + { + "@id": "pkg:otp/stdlib@5.1.1" + }, + { + "@id": "pkg:otp/stdlib@5.2" + }, + { + "@id": "pkg:otp/stdlib@5.2.1" + }, + { + "@id": "pkg:otp/stdlib@5.2.2" + }, + { + "@id": "pkg:otp/stdlib@5.2.3" + }, + { + "@id": "pkg:otp/stdlib@5.2.3.1" + }, + { + "@id": "pkg:otp/stdlib@5.2.3.2" + }, + { + "@id": "pkg:otp/stdlib@5.2.3.3" + } + ], + "status": "affected", + "action_statement": "Mitigation: Update to pkg:otp/stdlib@5.2.3.4", + "action_statement_timestamp": "2025-08-21T10:57:18.376876691+02:00" + }, + { + "vulnerability": { + "name": "CVE-2025-4748" + }, + "timestamp": "2025-08-21T10:57:18.392930374+02:00", + "products": [ + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.13" + }, + { + "@id": "pkg:otp/stdlib@5.2.3.4" + } + ], + "status": "fixed" + }, + { + "vulnerability": { + "name": "CVE-2025-30211" + }, + "timestamp": "2025-08-21T10:57:18.410315436+02:00", + "products": [ + { + "@id": "pkg:github/otp/erlang@OTP-26.0" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.0.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.0.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.1.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.1.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.5" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.6" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.7" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.8" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.9" + }, + { + "@id": "pkg:otp/ssh@5.0" + }, + { + "@id": "pkg:otp/ssh@5.0.1" + }, + { + "@id": "pkg:otp/ssh@5.1" + }, + { + "@id": "pkg:otp/ssh@5.1.1" + }, + { + "@id": "pkg:otp/ssh@5.1.2" + }, + { + "@id": "pkg:otp/ssh@5.1.3" + }, + { + "@id": "pkg:otp/ssh@5.1.4" + }, + { + "@id": "pkg:otp/ssh@5.1.4.1" + }, + { + "@id": "pkg:otp/ssh@5.1.4.2" + }, + { + "@id": "pkg:otp/ssh@5.1.4.3" + }, + { + "@id": "pkg:otp/ssh@5.1.4.4" + }, + { + "@id": "pkg:otp/ssh@5.1.4.5" + }, + { + "@id": "pkg:otp/ssh@5.1.4.6" + } + ], + "status": "affected", + "action_statement": "Workaround: set option `parallel_login` to false. Reduce `max_sessions` option.", + "action_statement_timestamp": "2025-08-21T10:57:18.410315436+02:00" + }, + { + "vulnerability": { + "name": "CVE-2025-30211" + }, + "timestamp": "2025-08-21T10:57:18.427381585+02:00", + "products": [ + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.10" + }, + { + "@id": "pkg:otp/ssh@5.1.4.7" + } + ], + "status": "fixed" + }, + { + "vulnerability": { + "name": "CVE-2025-53846" + }, + "timestamp": "2025-08-21T10:57:18.445588761+02:00", + "products": [ + { + "@id": "pkg:github/otp/erlang@OTP-26.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.5" + }, + { + "@id": "pkg:otp/ssl@11.1" + }, + { + "@id": "pkg:otp/ssl@11.1.1" + }, + { + "@id": "pkg:otp/ssl@11.1.2" + }, + { + "@id": "pkg:otp/ssl@11.1.3" + }, + { + "@id": "pkg:otp/ssl@11.1.4" + }, + { + "@id": "pkg:otp/ssl@11.1.4.1" + }, + { + "@id": "pkg:otp/ssl@11.1.4.2" + }, + { + "@id": "pkg:otp/ssl@11.1.4.3" + }, + { + "@id": "pkg:otp/ssl@11.1.4.4" + }, + { + "@id": "pkg:otp/ssl@11.1.4.5" + } + ], + "status": "affected", + "action_statement": "Update to ssl@11.1.4.6", + "action_statement_timestamp": "2025-08-21T10:57:18.445588761+02:00" + }, + { + "vulnerability": { + "name": "CVE-2025-53846" + }, + "timestamp": "2025-08-21T10:57:18.46608756+02:00", + "products": [ + { + "@id": "pkg:github/otp/erlang@OTP-26.2.5.6" + }, + { + "@id": "pkg:otp/ssl@11.1.4.6" + } + ], + "status": "fixed" + } + ] +} diff --git a/vex/otp-26.openvex.json.license b/vex/otp-26.openvex.json.license new file mode 100644 index 000000000000..1ea854fee3f9 --- /dev/null +++ b/vex/otp-26.openvex.json.license @@ -0,0 +1,7 @@ +%CopyrightBegin% + +SPDX-License-Identifier: Apache-2.0 + +Copyright Ericsson AB 2025. All Rights Reserved. + +%CopyrightEnd% diff --git a/vex/otp-27.openvex.json b/vex/otp-27.openvex.json new file mode 100644 index 000000000000..977f3acd623b --- /dev/null +++ b/vex/otp-27.openvex.json @@ -0,0 +1,1969 @@ +{ + "@context": "https://openvex.dev/ns/v0.2.0", + "@id": "https://openvex.dev/docs/public/otp/vex-otp-27", + "author": "vexctl", + "timestamp": "2025-08-21T10:55:49.860147+02:00", + "last_updated": "2025-08-21T10:56:29.49388886+02:00", + "version": 37, + "statements": [ + { + "vulnerability": { + "name": "CVE-2023-45853" + }, + "timestamp": "2025-08-21T10:56:28.907257662+02:00", + "products": [ + { + "@id": "pkg:github/otp/erlang@OTP-27.0" + }, + { + "@id": "pkg:otp/erts@15.0" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.0.1" + }, + { + "@id": "pkg:otp/erts@15.0.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1" + }, + { + "@id": "pkg:otp/erts@15.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1.1" + }, + { + "@id": "pkg:otp/erts@15.1.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1.2" + }, + { + "@id": "pkg:otp/erts@15.1.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1.3" + }, + { + "@id": "pkg:otp/erts@15.1.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2" + }, + { + "@id": "pkg:otp/erts@15.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2.1" + }, + { + "@id": "pkg:otp/erts@15.2.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2.4" + }, + { + "@id": "pkg:otp/erts@15.2.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3" + }, + { + "@id": "pkg:otp/erts@15.2.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.1" + }, + { + "@id": "pkg:otp/erts@15.2.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.2" + }, + { + "@id": "pkg:otp/erts@15.2.5" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.3" + }, + { + "@id": "pkg:otp/erts@15.2.6" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.4.1" + }, + { + "@id": "pkg:otp/erts@15.2.7" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.4.2" + }, + { + "@id": "pkg:otp/erts@15.2.7.1" + } + ], + "status": "not_affected", + "justification": "vulnerable_code_not_present" + }, + { + "vulnerability": { + "name": "CVE-2023-45853" + }, + "timestamp": "2025-08-21T10:56:28.923621046+02:00", + "products": [ + { + "@id": "pkg:github/madler/zlib@04f42ceca40f73e2978b50e93806c2a18c1281fc" + } + ], + "status": "not_affected", + "justification": "vulnerable_code_not_present" + }, + { + "vulnerability": { + "name": "CVE-2023-6129" + }, + "timestamp": "2025-08-21T10:56:28.940694601+02:00", + "products": [ + { + "@id": "pkg:github/otp/erlang@OTP-27.0" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.0.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.4.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.4.2" + }, + { + "@id": "pkg:otp/erl_interface@5.5.2" + }, + { + "@id": "pkg:otp/erts@15.0" + }, + { + "@id": "pkg:otp/erts@15.0.1" + }, + { + "@id": "pkg:otp/erts@15.1" + }, + { + "@id": "pkg:otp/erts@15.1.1" + }, + { + "@id": "pkg:otp/erts@15.1.2" + }, + { + "@id": "pkg:otp/erts@15.1.3" + }, + { + "@id": "pkg:otp/erts@15.2" + }, + { + "@id": "pkg:otp/erts@15.2.1" + }, + { + "@id": "pkg:otp/erts@15.2.2" + }, + { + "@id": "pkg:otp/erts@15.2.3" + }, + { + "@id": "pkg:otp/erts@15.2.4" + }, + { + "@id": "pkg:otp/erts@15.2.5" + }, + { + "@id": "pkg:otp/erts@15.2.6" + }, + { + "@id": "pkg:otp/erts@15.2.7" + }, + { + "@id": "pkg:otp/erts@15.2.7.1" + } + ], + "status": "not_affected", + "justification": "vulnerable_code_not_present" + }, + { + "vulnerability": { + "name": "CVE-2023-6129" + }, + "timestamp": "2025-08-21T10:56:28.957097597+02:00", + "products": [ + { + "@id": "pkg:github/openssl/openssl@01d5e2318405362b4de5e670c90d9b40a351d053" + } + ], + "status": "not_affected", + "justification": "vulnerable_code_not_present" + }, + { + "vulnerability": { + "name": "CVE-2023-6237" + }, + "timestamp": "2025-08-21T10:56:28.973310063+02:00", + "products": [ + { + "@id": "pkg:github/otp/erlang@OTP-27.0" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.0.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.4.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.4.2" + }, + { + "@id": "pkg:otp/erl_interface@5.5.2" + }, + { + "@id": "pkg:otp/erts@15.0" + }, + { + "@id": "pkg:otp/erts@15.0.1" + }, + { + "@id": "pkg:otp/erts@15.1" + }, + { + "@id": "pkg:otp/erts@15.1.1" + }, + { + "@id": "pkg:otp/erts@15.1.2" + }, + { + "@id": "pkg:otp/erts@15.1.3" + }, + { + "@id": "pkg:otp/erts@15.2" + }, + { + "@id": "pkg:otp/erts@15.2.1" + }, + { + "@id": "pkg:otp/erts@15.2.2" + }, + { + "@id": "pkg:otp/erts@15.2.3" + }, + { + "@id": "pkg:otp/erts@15.2.4" + }, + { + "@id": "pkg:otp/erts@15.2.5" + }, + { + "@id": "pkg:otp/erts@15.2.6" + }, + { + "@id": "pkg:otp/erts@15.2.7" + }, + { + "@id": "pkg:otp/erts@15.2.7.1" + } + ], + "status": "not_affected", + "justification": "vulnerable_code_not_present" + }, + { + "vulnerability": { + "name": "CVE-2023-6237" + }, + "timestamp": "2025-08-21T10:56:28.988991874+02:00", + "products": [ + { + "@id": "pkg:github/openssl/openssl@01d5e2318405362b4de5e670c90d9b40a351d053" + } + ], + "status": "not_affected", + "justification": "vulnerable_code_not_present" + }, + { + "vulnerability": { + "name": "CVE-2024-0727" + }, + "timestamp": "2025-08-21T10:56:29.006143754+02:00", + "products": [ + { + "@id": "pkg:github/otp/erlang@OTP-27.0" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.0.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.4.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.4.2" + }, + { + "@id": "pkg:otp/erl_interface@5.5.2" + }, + { + "@id": "pkg:otp/erts@15.0" + }, + { + "@id": "pkg:otp/erts@15.0.1" + }, + { + "@id": "pkg:otp/erts@15.1" + }, + { + "@id": "pkg:otp/erts@15.1.1" + }, + { + "@id": "pkg:otp/erts@15.1.2" + }, + { + "@id": "pkg:otp/erts@15.1.3" + }, + { + "@id": "pkg:otp/erts@15.2" + }, + { + "@id": "pkg:otp/erts@15.2.1" + }, + { + "@id": "pkg:otp/erts@15.2.2" + }, + { + "@id": "pkg:otp/erts@15.2.3" + }, + { + "@id": "pkg:otp/erts@15.2.4" + }, + { + "@id": "pkg:otp/erts@15.2.5" + }, + { + "@id": "pkg:otp/erts@15.2.6" + }, + { + "@id": "pkg:otp/erts@15.2.7" + }, + { + "@id": "pkg:otp/erts@15.2.7.1" + } + ], + "status": "not_affected", + "justification": "vulnerable_code_not_present" + }, + { + "vulnerability": { + "name": "CVE-2024-0727" + }, + "timestamp": "2025-08-21T10:56:29.023424181+02:00", + "products": [ + { + "@id": "pkg:github/openssl/openssl@01d5e2318405362b4de5e670c90d9b40a351d053" + } + ], + "status": "not_affected", + "justification": "vulnerable_code_not_present" + }, + { + "vulnerability": { + "name": "CVE-2024-13176" + }, + "timestamp": "2025-08-21T10:56:29.039936554+02:00", + "products": [ + { + "@id": "pkg:github/otp/erlang@OTP-27.0" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.0.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.4.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.4.2" + }, + { + "@id": "pkg:otp/erl_interface@5.5.2" + }, + { + "@id": "pkg:otp/erts@15.0" + }, + { + "@id": "pkg:otp/erts@15.0.1" + }, + { + "@id": "pkg:otp/erts@15.1" + }, + { + "@id": "pkg:otp/erts@15.1.1" + }, + { + "@id": "pkg:otp/erts@15.1.2" + }, + { + "@id": "pkg:otp/erts@15.1.3" + }, + { + "@id": "pkg:otp/erts@15.2" + }, + { + "@id": "pkg:otp/erts@15.2.1" + }, + { + "@id": "pkg:otp/erts@15.2.2" + }, + { + "@id": "pkg:otp/erts@15.2.3" + }, + { + "@id": "pkg:otp/erts@15.2.4" + }, + { + "@id": "pkg:otp/erts@15.2.5" + }, + { + "@id": "pkg:otp/erts@15.2.6" + }, + { + "@id": "pkg:otp/erts@15.2.7" + }, + { + "@id": "pkg:otp/erts@15.2.7.1" + } + ], + "status": "not_affected", + "justification": "vulnerable_code_not_present" + }, + { + "vulnerability": { + "name": "CVE-2024-13176" + }, + "timestamp": "2025-08-21T10:56:29.055627893+02:00", + "products": [ + { + "@id": "pkg:github/openssl/openssl@01d5e2318405362b4de5e670c90d9b40a351d053" + } + ], + "status": "not_affected", + "justification": "vulnerable_code_not_present" + }, + { + "vulnerability": { + "name": "CVE-2024-2511" + }, + "timestamp": "2025-08-21T10:56:29.072843347+02:00", + "products": [ + { + "@id": "pkg:github/otp/erlang@OTP-27.0" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.0.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.4.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.4.2" + }, + { + "@id": "pkg:otp/erl_interface@5.5.2" + }, + { + "@id": "pkg:otp/erts@15.0" + }, + { + "@id": "pkg:otp/erts@15.0.1" + }, + { + "@id": "pkg:otp/erts@15.1" + }, + { + "@id": "pkg:otp/erts@15.1.1" + }, + { + "@id": "pkg:otp/erts@15.1.2" + }, + { + "@id": "pkg:otp/erts@15.1.3" + }, + { + "@id": "pkg:otp/erts@15.2" + }, + { + "@id": "pkg:otp/erts@15.2.1" + }, + { + "@id": "pkg:otp/erts@15.2.2" + }, + { + "@id": "pkg:otp/erts@15.2.3" + }, + { + "@id": "pkg:otp/erts@15.2.4" + }, + { + "@id": "pkg:otp/erts@15.2.5" + }, + { + "@id": "pkg:otp/erts@15.2.6" + }, + { + "@id": "pkg:otp/erts@15.2.7" + }, + { + "@id": "pkg:otp/erts@15.2.7.1" + } + ], + "status": "not_affected", + "justification": "vulnerable_code_not_present" + }, + { + "vulnerability": { + "name": "CVE-2024-2511" + }, + "timestamp": "2025-08-21T10:56:29.088478654+02:00", + "products": [ + { + "@id": "pkg:github/openssl/openssl@01d5e2318405362b4de5e670c90d9b40a351d053" + } + ], + "status": "not_affected", + "justification": "vulnerable_code_not_present" + }, + { + "vulnerability": { + "name": "CVE-2024-4603" + }, + "timestamp": "2025-08-21T10:56:29.104822021+02:00", + "products": [ + { + "@id": "pkg:github/otp/erlang@OTP-27.0" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.0.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.4.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.4.2" + }, + { + "@id": "pkg:otp/erl_interface@5.5.2" + }, + { + "@id": "pkg:otp/erts@15.0" + }, + { + "@id": "pkg:otp/erts@15.0.1" + }, + { + "@id": "pkg:otp/erts@15.1" + }, + { + "@id": "pkg:otp/erts@15.1.1" + }, + { + "@id": "pkg:otp/erts@15.1.2" + }, + { + "@id": "pkg:otp/erts@15.1.3" + }, + { + "@id": "pkg:otp/erts@15.2" + }, + { + "@id": "pkg:otp/erts@15.2.1" + }, + { + "@id": "pkg:otp/erts@15.2.2" + }, + { + "@id": "pkg:otp/erts@15.2.3" + }, + { + "@id": "pkg:otp/erts@15.2.4" + }, + { + "@id": "pkg:otp/erts@15.2.5" + }, + { + "@id": "pkg:otp/erts@15.2.6" + }, + { + "@id": "pkg:otp/erts@15.2.7" + }, + { + "@id": "pkg:otp/erts@15.2.7.1" + } + ], + "status": "not_affected", + "justification": "vulnerable_code_not_present" + }, + { + "vulnerability": { + "name": "CVE-2024-4603" + }, + "timestamp": "2025-08-21T10:56:29.120157609+02:00", + "products": [ + { + "@id": "pkg:github/openssl/openssl@01d5e2318405362b4de5e670c90d9b40a351d053" + } + ], + "status": "not_affected", + "justification": "vulnerable_code_not_present" + }, + { + "vulnerability": { + "name": "CVE-2024-4741" + }, + "timestamp": "2025-08-21T10:56:29.136387324+02:00", + "products": [ + { + "@id": "pkg:github/otp/erlang@OTP-27.0" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.0.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.4.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.4.2" + }, + { + "@id": "pkg:otp/erl_interface@5.5.2" + }, + { + "@id": "pkg:otp/erts@15.0" + }, + { + "@id": "pkg:otp/erts@15.0.1" + }, + { + "@id": "pkg:otp/erts@15.1" + }, + { + "@id": "pkg:otp/erts@15.1.1" + }, + { + "@id": "pkg:otp/erts@15.1.2" + }, + { + "@id": "pkg:otp/erts@15.1.3" + }, + { + "@id": "pkg:otp/erts@15.2" + }, + { + "@id": "pkg:otp/erts@15.2.1" + }, + { + "@id": "pkg:otp/erts@15.2.2" + }, + { + "@id": "pkg:otp/erts@15.2.3" + }, + { + "@id": "pkg:otp/erts@15.2.4" + }, + { + "@id": "pkg:otp/erts@15.2.5" + }, + { + "@id": "pkg:otp/erts@15.2.6" + }, + { + "@id": "pkg:otp/erts@15.2.7" + }, + { + "@id": "pkg:otp/erts@15.2.7.1" + } + ], + "status": "not_affected", + "justification": "vulnerable_code_not_present" + }, + { + "vulnerability": { + "name": "CVE-2024-4741" + }, + "timestamp": "2025-08-21T10:56:29.151633049+02:00", + "products": [ + { + "@id": "pkg:github/openssl/openssl@01d5e2318405362b4de5e670c90d9b40a351d053" + } + ], + "status": "not_affected", + "justification": "vulnerable_code_not_present" + }, + { + "vulnerability": { + "name": "CVE-2024-5535" + }, + "timestamp": "2025-08-21T10:56:29.168668453+02:00", + "products": [ + { + "@id": "pkg:github/otp/erlang@OTP-27.0" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.0.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.4.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.4.2" + }, + { + "@id": "pkg:otp/erl_interface@5.5.2" + }, + { + "@id": "pkg:otp/erts@15.0" + }, + { + "@id": "pkg:otp/erts@15.0.1" + }, + { + "@id": "pkg:otp/erts@15.1" + }, + { + "@id": "pkg:otp/erts@15.1.1" + }, + { + "@id": "pkg:otp/erts@15.1.2" + }, + { + "@id": "pkg:otp/erts@15.1.3" + }, + { + "@id": "pkg:otp/erts@15.2" + }, + { + "@id": "pkg:otp/erts@15.2.1" + }, + { + "@id": "pkg:otp/erts@15.2.2" + }, + { + "@id": "pkg:otp/erts@15.2.3" + }, + { + "@id": "pkg:otp/erts@15.2.4" + }, + { + "@id": "pkg:otp/erts@15.2.5" + }, + { + "@id": "pkg:otp/erts@15.2.6" + }, + { + "@id": "pkg:otp/erts@15.2.7" + }, + { + "@id": "pkg:otp/erts@15.2.7.1" + } + ], + "status": "not_affected", + "justification": "vulnerable_code_not_present" + }, + { + "vulnerability": { + "name": "CVE-2024-5535" + }, + "timestamp": "2025-08-21T10:56:29.186156112+02:00", + "products": [ + { + "@id": "pkg:github/openssl/openssl@01d5e2318405362b4de5e670c90d9b40a351d053" + } + ], + "status": "not_affected", + "justification": "vulnerable_code_not_present" + }, + { + "vulnerability": { + "name": "CVE-2024-6119" + }, + "timestamp": "2025-08-21T10:56:29.202601178+02:00", + "products": [ + { + "@id": "pkg:github/otp/erlang@OTP-27.0" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.0.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.4.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.4.2" + }, + { + "@id": "pkg:otp/erl_interface@5.5.2" + }, + { + "@id": "pkg:otp/erts@15.0" + }, + { + "@id": "pkg:otp/erts@15.0.1" + }, + { + "@id": "pkg:otp/erts@15.1" + }, + { + "@id": "pkg:otp/erts@15.1.1" + }, + { + "@id": "pkg:otp/erts@15.1.2" + }, + { + "@id": "pkg:otp/erts@15.1.3" + }, + { + "@id": "pkg:otp/erts@15.2" + }, + { + "@id": "pkg:otp/erts@15.2.1" + }, + { + "@id": "pkg:otp/erts@15.2.2" + }, + { + "@id": "pkg:otp/erts@15.2.3" + }, + { + "@id": "pkg:otp/erts@15.2.4" + }, + { + "@id": "pkg:otp/erts@15.2.5" + }, + { + "@id": "pkg:otp/erts@15.2.6" + }, + { + "@id": "pkg:otp/erts@15.2.7" + }, + { + "@id": "pkg:otp/erts@15.2.7.1" + } + ], + "status": "not_affected", + "justification": "vulnerable_code_not_present" + }, + { + "vulnerability": { + "name": "CVE-2024-6119" + }, + "timestamp": "2025-08-21T10:56:29.218287926+02:00", + "products": [ + { + "@id": "pkg:github/openssl/openssl@01d5e2318405362b4de5e670c90d9b40a351d053" + } + ], + "status": "not_affected", + "justification": "vulnerable_code_not_present" + }, + { + "vulnerability": { + "name": "CVE-2024-9143" + }, + "timestamp": "2025-08-21T10:56:29.23619712+02:00", + "products": [ + { + "@id": "pkg:github/otp/erlang@OTP-27.0" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.0.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.4.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.4.2" + }, + { + "@id": "pkg:otp/erl_interface@5.5.2" + }, + { + "@id": "pkg:otp/erts@15.0" + }, + { + "@id": "pkg:otp/erts@15.0.1" + }, + { + "@id": "pkg:otp/erts@15.1" + }, + { + "@id": "pkg:otp/erts@15.1.1" + }, + { + "@id": "pkg:otp/erts@15.1.2" + }, + { + "@id": "pkg:otp/erts@15.1.3" + }, + { + "@id": "pkg:otp/erts@15.2" + }, + { + "@id": "pkg:otp/erts@15.2.1" + }, + { + "@id": "pkg:otp/erts@15.2.2" + }, + { + "@id": "pkg:otp/erts@15.2.3" + }, + { + "@id": "pkg:otp/erts@15.2.4" + }, + { + "@id": "pkg:otp/erts@15.2.5" + }, + { + "@id": "pkg:otp/erts@15.2.6" + }, + { + "@id": "pkg:otp/erts@15.2.7" + }, + { + "@id": "pkg:otp/erts@15.2.7.1" + } + ], + "status": "not_affected", + "justification": "vulnerable_code_not_present" + }, + { + "vulnerability": { + "name": "CVE-2024-9143" + }, + "timestamp": "2025-08-21T10:56:29.254516893+02:00", + "products": [ + { + "@id": "pkg:github/openssl/openssl@01d5e2318405362b4de5e670c90d9b40a351d053" + } + ], + "status": "not_affected", + "justification": "vulnerable_code_not_present" + }, + { + "vulnerability": { + "name": "CVE-2025-4575" + }, + "timestamp": "2025-08-21T10:56:29.274864577+02:00", + "products": [ + { + "@id": "pkg:github/otp/erlang@OTP-27.0" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.0.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.4.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.4.2" + }, + { + "@id": "pkg:otp/erl_interface@5.5.2" + }, + { + "@id": "pkg:otp/erts@15.0" + }, + { + "@id": "pkg:otp/erts@15.0.1" + }, + { + "@id": "pkg:otp/erts@15.1" + }, + { + "@id": "pkg:otp/erts@15.1.1" + }, + { + "@id": "pkg:otp/erts@15.1.2" + }, + { + "@id": "pkg:otp/erts@15.1.3" + }, + { + "@id": "pkg:otp/erts@15.2" + }, + { + "@id": "pkg:otp/erts@15.2.1" + }, + { + "@id": "pkg:otp/erts@15.2.2" + }, + { + "@id": "pkg:otp/erts@15.2.3" + }, + { + "@id": "pkg:otp/erts@15.2.4" + }, + { + "@id": "pkg:otp/erts@15.2.5" + }, + { + "@id": "pkg:otp/erts@15.2.6" + }, + { + "@id": "pkg:otp/erts@15.2.7" + }, + { + "@id": "pkg:otp/erts@15.2.7.1" + } + ], + "status": "not_affected", + "justification": "vulnerable_code_not_present" + }, + { + "vulnerability": { + "name": "CVE-2025-4575" + }, + "timestamp": "2025-08-21T10:56:29.292568488+02:00", + "products": [ + { + "@id": "pkg:github/openssl/openssl@01d5e2318405362b4de5e670c90d9b40a351d053" + } + ], + "status": "not_affected", + "justification": "vulnerable_code_not_present" + }, + { + "vulnerability": { + "name": "CVE-2025-26618" + }, + "timestamp": "2025-08-21T10:56:29.309033999+02:00", + "products": [ + { + "@id": "pkg:github/otp/erlang@OTP-27.0" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.0.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2.3" + }, + { + "@id": "pkg:otp/ssh@5.2" + }, + { + "@id": "pkg:otp/ssh@5.2.1" + }, + { + "@id": "pkg:otp/ssh@5.2.2" + }, + { + "@id": "pkg:otp/ssh@5.2.3" + }, + { + "@id": "pkg:otp/ssh@5.2.4" + }, + { + "@id": "pkg:otp/ssh@5.2.5" + }, + { + "@id": "pkg:otp/ssh@5.2.6" + } + ], + "status": "affected", + "action_statement": "Update to the next version", + "action_statement_timestamp": "2025-08-21T10:56:29.309033999+02:00" + }, + { + "vulnerability": { + "name": "CVE-2025-26618" + }, + "timestamp": "2025-08-21T10:56:29.32552649+02:00", + "products": [ + { + "@id": "pkg:github/otp/erlang@OTP-27.2.4" + }, + { + "@id": "pkg:otp/ssh@5.2.7" + } + ], + "status": "fixed" + }, + { + "vulnerability": { + "name": "CVE-2025-32433" + }, + "timestamp": "2025-08-21T10:56:29.341333268+02:00", + "products": [ + { + "@id": "pkg:github/otp/erlang@OTP-27.3.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.2" + }, + { + "@id": "pkg:otp/ssh@5.2.9" + } + ], + "status": "affected", + "action_statement": "A temporary workaround involves disabling the SSH server or to prevent access via firewall rules.", + "action_statement_timestamp": "2025-08-21T10:56:29.341333268+02:00" + }, + { + "vulnerability": { + "name": "CVE-2025-32433" + }, + "timestamp": "2025-08-21T10:56:29.358118726+02:00", + "products": [ + { + "@id": "pkg:github/otp/erlang@OTP-27.3.3" + }, + { + "@id": "pkg:otp/ssh@5.2.10" + } + ], + "status": "fixed" + }, + { + "vulnerability": { + "name": "CVE-2025-46712" + }, + "timestamp": "2025-08-21T10:56:29.374406582+02:00", + "products": [ + { + "@id": "pkg:github/otp/erlang@OTP-27.0" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.0.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.3" + }, + { + "@id": "pkg:otp/ssh@5.2" + }, + { + "@id": "pkg:otp/ssh@5.2.1" + }, + { + "@id": "pkg:otp/ssh@5.2.2" + }, + { + "@id": "pkg:otp/ssh@5.2.3" + }, + { + "@id": "pkg:otp/ssh@5.2.4" + }, + { + "@id": "pkg:otp/ssh@5.2.5" + }, + { + "@id": "pkg:otp/ssh@5.2.6" + }, + { + "@id": "pkg:otp/ssh@5.2.7" + }, + { + "@id": "pkg:otp/ssh@5.2.8" + }, + { + "@id": "pkg:otp/ssh@5.2.9" + }, + { + "@id": "pkg:otp/ssh@5.2.10" + } + ], + "status": "affected", + "action_statement": "Update to ssh@5.2.11", + "action_statement_timestamp": "2025-08-21T10:56:29.374406582+02:00" + }, + { + "vulnerability": { + "name": "CVE-2025-46712" + }, + "timestamp": "2025-08-21T10:56:29.391627434+02:00", + "products": [ + { + "@id": "pkg:github/otp/erlang@OTP-27.3.4" + }, + { + "@id": "pkg:otp/ssh@5.2.11" + } + ], + "status": "fixed" + }, + { + "vulnerability": { + "name": "CVE-2025-4748" + }, + "timestamp": "2025-08-21T10:56:29.40933803+02:00", + "products": [ + { + "@id": "pkg:github/otp/erlang@OTP-27.0" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.0.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.4" + }, + { + "@id": "pkg:otp/stdlib@6.0" + }, + { + "@id": "pkg:otp/stdlib@6.0.1" + }, + { + "@id": "pkg:otp/stdlib@6.1" + }, + { + "@id": "pkg:otp/stdlib@6.1.1" + }, + { + "@id": "pkg:otp/stdlib@6.1.2" + }, + { + "@id": "pkg:otp/stdlib@6.2" + }, + { + "@id": "pkg:otp/stdlib@6.2.1" + }, + { + "@id": "pkg:otp/stdlib@6.2.2" + } + ], + "status": "affected", + "action_statement": "Mitigation: Update to pkg:otp/stdlib@6.2.2.1", + "action_statement_timestamp": "2025-08-21T10:56:29.40933803+02:00" + }, + { + "vulnerability": { + "name": "CVE-2025-4748" + }, + "timestamp": "2025-08-21T10:56:29.426231469+02:00", + "products": [ + { + "@id": "pkg:github/otp/erlang@OTP-27.3.4.1" + }, + { + "@id": "pkg:otp/stdlib@6.2.2.1" + } + ], + "status": "fixed" + }, + { + "vulnerability": { + "name": "CVE-2025-30211" + }, + "timestamp": "2025-08-21T10:56:29.444026411+02:00", + "products": [ + { + "@id": "pkg:github/otp/erlang@OTP-27.0" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.0.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2.3" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.2.4" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3" + }, + { + "@id": "pkg:otp/ssh@5.2" + }, + { + "@id": "pkg:otp/ssh@5.2.1" + }, + { + "@id": "pkg:otp/ssh@5.2.2" + }, + { + "@id": "pkg:otp/ssh@5.2.3" + }, + { + "@id": "pkg:otp/ssh@5.2.4" + }, + { + "@id": "pkg:otp/ssh@5.2.5" + }, + { + "@id": "pkg:otp/ssh@5.2.6" + }, + { + "@id": "pkg:otp/ssh@5.2.7" + }, + { + "@id": "pkg:otp/ssh@5.2.8" + } + ], + "status": "affected", + "action_statement": "Workaround: set option `parallel_login` to false. Reduce `max_sessions` option.", + "action_statement_timestamp": "2025-08-21T10:56:29.444026411+02:00" + }, + { + "vulnerability": { + "name": "CVE-2025-30211" + }, + "timestamp": "2025-08-21T10:56:29.460006476+02:00", + "products": [ + { + "@id": "pkg:github/otp/erlang@OTP-27.3.2" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.3.1" + }, + { + "@id": "pkg:otp/ssh@5.2.9" + } + ], + "status": "fixed" + }, + { + "vulnerability": { + "name": "CVE-2025-53846" + }, + "timestamp": "2025-08-21T10:56:29.477131167+02:00", + "products": [ + { + "@id": "pkg:github/otp/erlang@OTP-27.0" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.0.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-27.1.2" + }, + { + "@id": "pkg:otp/ssl@11.2" + }, + { + "@id": "pkg:otp/ssl@11.2.1" + }, + { + "@id": "pkg:otp/ssl@11.2.2" + }, + { + "@id": "pkg:otp/ssl@11.2.3" + }, + { + "@id": "pkg:otp/ssl@11.2.4" + } + ], + "status": "affected", + "action_statement": "Update to ssl@11.2.5", + "action_statement_timestamp": "2025-08-21T10:56:29.477131167+02:00" + }, + { + "vulnerability": { + "name": "CVE-2025-53846" + }, + "timestamp": "2025-08-21T10:56:29.493892991+02:00", + "products": [ + { + "@id": "pkg:github/otp/erlang@OTP-27.1.3" + }, + { + "@id": "pkg:otp/ssl@11.2.5" + } + ], + "status": "fixed" + } + ] +} diff --git a/vex/otp-27.openvex.json.license b/vex/otp-27.openvex.json.license new file mode 100644 index 000000000000..1ea854fee3f9 --- /dev/null +++ b/vex/otp-27.openvex.json.license @@ -0,0 +1,7 @@ +%CopyrightBegin% + +SPDX-License-Identifier: Apache-2.0 + +Copyright Ericsson AB 2025. All Rights Reserved. + +%CopyrightEnd% diff --git a/vex/otp-28.openvex.json b/vex/otp-28.openvex.json new file mode 100644 index 000000000000..9636348acb38 --- /dev/null +++ b/vex/otp-28.openvex.json @@ -0,0 +1,140 @@ +{ + "@context": "https://openvex.dev/ns/v0.2.0", + "@id": "https://openvex.dev/docs/public/otp/vex-otp-28", + "author": "vexctl", + "timestamp": "2025-08-21T10:55:45.714759+02:00", + "last_updated": "2025-08-21T10:55:46.021839073+02:00", + "version": 8, + "statements": [ + { + "vulnerability": { + "name": "OSV-2025-300" + }, + "timestamp": "2025-08-21T10:55:45.929417984+02:00", + "products": [ + { + "@id": "pkg:github/otp/erlang@OTP-28.0" + }, + { + "@id": "pkg:otp/erts@16.0" + }, + { + "@id": "pkg:github/otp/erlang@OTP-28.0.1" + }, + { + "@id": "pkg:otp/erts@16.0.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-28.0.2" + }, + { + "@id": "pkg:otp/erts@16.0.2" + } + ], + "status": "not_affected", + "justification": "vulnerable_code_not_present" + }, + { + "vulnerability": { + "name": "OSV-2025-300" + }, + "timestamp": "2025-08-21T10:55:45.944352157+02:00", + "products": [ + { + "@id": "pkg:github/PCRE2Project/pcre2@2dce7761b1831fd3f82a9c2bd5476259d945da4d" + } + ], + "status": "not_affected", + "justification": "vulnerable_code_not_present" + }, + { + "vulnerability": { + "name": "CVE-2023-45853" + }, + "timestamp": "2025-08-21T10:55:45.958540114+02:00", + "products": [ + { + "@id": "pkg:github/madler/zlib@1a8db63788c34a50e39e273d39b7e1033208aea2" + } + ], + "status": "not_affected", + "justification": "vulnerable_code_not_present" + }, + { + "vulnerability": { + "name": "CVE-2025-4748" + }, + "timestamp": "2025-08-21T10:55:45.97513015+02:00", + "products": [ + { + "@id": "pkg:github/otp/erlang@OTP-28.0" + }, + { + "@id": "pkg:otp/stdlib@7.0" + } + ], + "status": "affected", + "action_statement": "Mitigation: Update to pkg:otp/stdlib@7.0.1", + "action_statement_timestamp": "2025-08-21T10:55:45.97513015+02:00" + }, + { + "vulnerability": { + "name": "CVE-2025-4748" + }, + "timestamp": "2025-08-21T10:55:45.990630892+02:00", + "products": [ + { + "@id": "pkg:github/otp/erlang@OTP-28.0.1" + }, + { + "@id": "pkg:otp/stdlib@7.0.1" + } + ], + "status": "fixed" + }, + { + "vulnerability": { + "name": "CVE-2025-4575" + }, + "timestamp": "2025-08-21T10:55:46.006302174+02:00", + "products": [ + { + "@id": "pkg:github/otp/erlang@OTP-28.0" + }, + { + "@id": "pkg:github/otp/erlang@OTP-28.0.1" + }, + { + "@id": "pkg:github/otp/erlang@OTP-28.0.2" + }, + { + "@id": "pkg:otp/erl_interface@5.6" + }, + { + "@id": "pkg:otp/erts@16.0" + }, + { + "@id": "pkg:otp/erts@16.0.1" + }, + { + "@id": "pkg:otp/erts@16.0.2" + } + ], + "status": "not_affected", + "justification": "vulnerable_code_not_present" + }, + { + "vulnerability": { + "name": "CVE-2025-4575" + }, + "timestamp": "2025-08-21T10:55:46.021839572+02:00", + "products": [ + { + "@id": "pkg:github/openssl/openssl@01d5e2318405362b4de5e670c90d9b40a351d053" + } + ], + "status": "not_affected", + "justification": "vulnerable_code_not_present" + } + ] +} diff --git a/vex/otp-28.openvex.json.license b/vex/otp-28.openvex.json.license new file mode 100644 index 000000000000..1ea854fee3f9 --- /dev/null +++ b/vex/otp-28.openvex.json.license @@ -0,0 +1,7 @@ +%CopyrightBegin% + +SPDX-License-Identifier: Apache-2.0 + +Copyright Ericsson AB 2025. All Rights Reserved. + +%CopyrightEnd%