diff --git a/.github/scripts/ort-scanner.es b/.github/scripts/ort-scanner.es index 3e1afeb2f3e2..863c7a489e6e 100755 --- a/.github/scripts/ort-scanner.es +++ b/.github/scripts/ort-scanner.es @@ -487,8 +487,8 @@ format_scan_results(ScanResult) -> end end)). -sort_arrays(JSon) -> - sort_arrays(JSon, fun(_) -> true end). +% sort_arrays(JSon) -> +% sort_arrays(JSon, fun(_) -> true end). sort_arrays(JSon, KeyFun) -> sort_arrays(JSon, KeyFun, true). sort_arrays(Map, KeyFun, _Sort) when is_map(Map) -> diff --git a/.github/scripts/otp-compliance.es b/.github/scripts/otp-compliance.es index f2f0f76a7373..ae6ba165dbae 100755 --- a/.github/scripts/otp-compliance.es +++ b/.github/scripts/otp-compliance.es @@ -53,7 +53,7 @@ test_package_ids/1, test_verificationCode/1, test_supplier_Ericsson/1, 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_snippets/1, + test_package_relations/1, test_has_extracted_licenses/1, test_vendor_packages/1]). -define(default_classified_result, "scan-result-classified.json"). @@ -365,10 +365,7 @@ sbom_otp(#{sbom_file := SbomFile, write_to_file := Write, input_file := Input}) improve_sbom_with_info(Sbom, ScanResults) -> {Licenses, Copyrights} = fetch_license_copyrights(ScanResults), - Spdx = generate_spdx_fixes(Sbom, Licenses, Copyrights), - generate_snippet_fixes(Spdx, ScanResults). - %% Spdx. - + generate_spdx_fixes(Sbom, Licenses, Copyrights). fetch_license_copyrights(Input) -> {path_to_license(Input), path_to_copyright(Input)}. @@ -379,68 +376,6 @@ generate_spdx_fixes(Input, Licenses, Copyrights) -> Spdx = lists:foldl(fun ({Fun, Data}, Acc) -> Fun(Data, Acc) end, Input, FixFuns), package_by_app(Spdx). -%% this function has a hard dependency to ScanResults. -%% ScanResults has license results on a per line found basis. -%% Spdx result builds using ScanResult and loses this information. -generate_snippet_fixes(Spdx, ScanResults) -> - Licenses = licenses(scan_results(ScanResults)), - %% We identify the known copied snippet - [Snippet] = lists:filter(fun(#{~"location" := #{~"path" := Path}, ~"license" := License}) -> - case {License, Path} of - {~"Apache-2.0 WITH LLVM-exception AND BSL-1.0", ~"erts/emulator/ryu/d2s.c"} -> - true; - _ -> - false - end - end, Licenses), - Snippets = generate_snippet(Spdx, [Snippet]), - Spdx#{ ~"snippets" => Snippets }. - -%% we are doing the assumption that we only have one known snippet. -generate_snippet(#{~"files" := Files}=_Spdx, [#{~"location" := #{~"path" := ~"erts/emulator/ryu/d2s.c"=Path}, ~"license" := License}]) -> - [#{~"SPDXID" := SpdxId}=SpdxFile] = lists:filter(fun (#{~"fileName" := FileName}) -> FileName == Path end, Files), - - %% read file to find snippet byte range and lines - {ok, Content} = file:read_file(Path), - #{~"begin_byte" := StartOffsetBytes, ~"end_byte" := EndOffsetBytes, - ~"start_line" := StartLine, ~"end_line" := EndLine} = get_snippet_range(Content), - - [#{ ~"SPDXID" => ~"SPDXRef-Snippet-STL", - ~"comment" => ~""" - vendor package. - This is inspired from the MS STL Charconv, under Apache with LLVM exception licence see https://github.com/microsoft/STL/blob/main/LICENSE.txt - The inspiration is at https://github.com/microsoft/STL/blob/e745bad3b1d05b5b19ec652d68abb37865ffa454/stl/inc/xcharconv_ryu.h#L1926 - Changes are described in the file. - """, - ~"copyrightText" => maps:get(~"copyrightText", SpdxFile), - ~"licenseConcluded" => ~"Apache-2.0 WITH LLVM-exception AND BSL-1.0", - ~"licenseInfoInSnippets" => split_licenses_in_individual_parts([License]), - ~"name" => ~"stl", - ~"ranges" => [ #{~"endPointer" => #{ ~"lineNumber" => EndLine, ~"reference" => SpdxId}, - ~"startPointer" => #{ ~"lineNumber" => StartLine, ~"reference" => SpdxId}}, - #{~"endPointer" => #{ ~"offset" => EndOffsetBytes, ~"reference" => SpdxId}, - ~"startPointer" => #{ ~"offset" => StartOffsetBytes, ~"reference" => SpdxId}} ], - ~"snippetFromFile" => SpdxId - }]. - -%% assumes that there is only one snippet in the whole file. --spec get_snippet_range(Content :: binary()) -> map(). -get_snippet_range(Content) -> - get_snippet_range(Content, {<<>>, 1}). -get_snippet_range(<<"\n", Rest/binary>>, {Acc, Lines}) -> - get_snippet_range(Rest, {<<"\n", Acc/binary>>, Lines+1}); -get_snippet_range(<<"// SPDX-SnippetBegin", Rest/binary>>, {Content, Line}) -> - {BeginContent, StartLine} = {Content, Line}, - {EndContent, EndLine} = get_snippet_range(Rest, {<<"// SPDX-SnippetBegin", Content/binary>>, Line+1}), - #{~"begin_byte" => byte_size(BeginContent), - ~"end_byte" => byte_size(EndContent), - ~"start_line" => StartLine, - ~"end_line" => EndLine}; -get_snippet_range(<<"// SPDX-SnippetEnd", _Rest/binary>>, {Content, Line}) -> - {Content, Line}; -get_snippet_range(<>, {Content, Line}) -> - get_snippet_range(Rest, {<>, Line}). - sbom_fixing_functions(Licenses, Copyrights) -> [{fun fix_project_name/2, ?spdxref_project_name}, {fun fix_name/2, ?spdx_project_name}, @@ -580,14 +515,6 @@ fix_beam_licenses(LicensesAndCopyrights, %% follows from otp/lib/stdlib/uc_spec/README-UPDATE.txt files_have_no_license(SPDX#{~"licenseConcluded" := ~"Unicode-3.0 AND Apache-2.0"}); - #{~"fileName" := <<"erts/emulator/internal_doc/",Filename/binary>>} -> - case binary:split(Filename, ~".md") of - [_File, _Ext] -> - SPDX#{~"licenseConcluded" := ~"Apache-2.0"}; - _ -> - SPDX - end; - #{~"fileName" := Filename} -> case bootstrap_mappings(Filename) of {error, not_beam_file} -> @@ -858,7 +785,7 @@ decode_without_spdx_license(Filename) -> %% remove comments Lines = string:split(Bin, "\n", all), - Lines1 = lists:map(fun (Line) -> re:replace(Line, "%.*", "", [global]) end, Lines), + Lines1 = lists:map(fun (Line) -> re:replace(Line, "^//.*", "", [global]) end, Lines), Bin1 = erlang:iolist_to_binary(Lines1), json:decode(Bin1). @@ -1141,8 +1068,7 @@ get_otp_apps_from_table() -> end. find_vendor_src_files(Folder) -> - S = os:cmd("find "++ Folder ++ " -name vendor.info"), - lists:map(fun erlang:list_to_binary/1, string:split(S, "\n", all)). + string:split(string:trim(os:cmd("find "++ Folder ++ " -name vendor.info")), "\n", all). -spec generate_spdx_mappings(Path :: [binary()]) -> Result when Result :: #{AppName :: binary() => {AppPath :: binary(), AppInfo :: app_info()}}. @@ -1152,21 +1078,10 @@ generate_spdx_mappings(AppSrcPath) -> maps:merge(Acc, DetectedPackages) end, #{}, AppSrcPath). --spec generate_vendor_info_package(VendorSrcPath :: [binary()]) -> map(). -generate_vendor_info_package(VendorSrcPath) -> - lists:foldl(fun vendor_info_to_map/2, [], VendorSrcPath). - - %% Read Path file and generate Json (map) following vendor.info specification -vendor_info_to_map(<<>>, Acc) -> - Acc; -vendor_info_to_map(Path, Acc) -> - case decode_without_spdx_license(Path) of - Json when is_list(Json) -> - Json ++ Acc; - Json when is_map(Json) -> - [Json | Acc] - end. +-spec generate_vendor_info_package(VendorSrcPath :: [file:name()]) -> map(). +generate_vendor_info_package(VendorSrcPath) -> + lists:flatmap(fun decode_without_spdx_license/1, VendorSrcPath). -spec generate_spdx_vendor_packages(VendorInfoPackage :: map(), map()) -> map(). generate_spdx_vendor_packages(VendorInfoPackages, #{~"files" := SpdxFiles}=_SPDX) -> @@ -1174,9 +1089,7 @@ generate_spdx_vendor_packages(VendorInfoPackages, #{~"files" := SpdxFiles}=_SPDX (#{~"ID" := Id, ~"path" := [_ | _]=ExplicitFiles}=Package) when is_list(ExplicitFiles) -> %% Deals with the cases of creating a package out of specific files Paths = lists:map(fun cleanup_path/1, ExplicitFiles), - Package0 = maps:remove(~"purl", Package), - Package1 = maps:remove(~"ID", Package0), - Package2 = maps:remove(~"path", Package1), + Package1 = maps:without([~"purl", ~"ID", ~"path", ~"update"], Package), %% place files in SPDX in the corresponding package Files = lists:filter(fun (#{~"fileName" := Filename}) -> @@ -1190,7 +1103,7 @@ generate_spdx_vendor_packages(VendorInfoPackages, #{~"files" := SpdxFiles}=_SPDX PackageVerificationCodeValue = generate_verification_code_value(Files), ExternalRefs = generate_vendor_purl(Package), - Package2#{ + Package1#{ ~"SPDXID" => generate_spdxid_name(Id), ~"filesAnalyzed" => true, ~"hasFiles" => lists:map(fun (#{~"SPDXID":=Id0}) -> Id0 end, Files), @@ -1203,9 +1116,7 @@ generate_spdx_vendor_packages(VendorInfoPackages, #{~"files" := SpdxFiles}=_SPDX (#{~"ID" := Id, ~"path" := DirtyPath}=Package) when is_binary(DirtyPath) -> %% Deals with the case of creating a package out of a path Path = cleanup_path(DirtyPath), - Package0 = maps:remove(~"purl", Package), - Package1 = maps:remove(~"ID", Package0), - Package2 = maps:remove(~"path", Package1), + Package1 = maps:without([~"purl", ~"ID", ~"path", ~"update"], Package), %% place files in SPDX in the corresponding package Files = lists:filter(fun (#{~"fileName" := Filename}) -> @@ -1221,7 +1132,7 @@ generate_spdx_vendor_packages(VendorInfoPackages, #{~"files" := SpdxFiles}=_SPDX PackageVerificationCodeValue = generate_verification_code_value(Files), ExternalRefs = generate_vendor_purl(Package), - Package2#{ + Package1#{ ~"SPDXID" => generate_spdxid_name(Id), ~"filesAnalyzed" => true, ~"hasFiles" => lists:map(fun (#{~"SPDXID":=Id0}) -> Id0 end, Files), @@ -1523,7 +1434,6 @@ package_generator(Sbom) -> test_download_location, test_package_relations, test_has_extracted_licenses, - test_snippets, test_vendor_packages], true = ?CALL_TEST_FUNCTIONS(Tests, Sbom), ok. @@ -1587,7 +1497,7 @@ root_vendor_packages() -> minimum_vendor_packages() -> %% self-contained root_vendor_packages() ++ - [~"tcl", ~"json-test-suite", ~"openssl", ~"Autoconf", ~"wx", ~"jquery", ~"jquery-tablesorter"]. + [~"tcl", ~"ryu_to_chars", ~"json-test-suite", ~"openssl", ~"Autoconf", ~"wx", ~"jquery", ~"jquery-tablesorter"]. test_copyright_not_empty(#{~"packages" := Packages}) -> true = lists:all(fun (#{~"copyrightText" := Copyright}) -> Copyright =/= ~"" end, Packages), @@ -1602,7 +1512,7 @@ test_hasFiles_not_empty(#{~"packages" := Packages}) -> true = lists:all(fun (#{~"hasFiles" := Files}) -> length(Files) > 0 end, Packages) catch _:_:_ -> - lists:map(fun (#{~"hasFiles" := Files, ~"SPDXID":=Id}) -> + lists:foreach(fun (#{~"hasFiles" := Files, ~"SPDXID":=Id}) -> io:format("~p: length: ~p~n", [Id, length(Files)]) end, Packages), error(?FUNCTION_NAME) @@ -1705,7 +1615,13 @@ test_download_location(#{~"packages" := Packages}) -> test_package_hasFiles(#{~"packages" := Packages}) -> %% test files are not repeated AllFiles = lists:foldl(fun (#{~"hasFiles" := FileIds}, Acc) -> FileIds ++ Acc end, [], Packages), - true = length(AllFiles) == length(lists:uniq(AllFiles)), + + try + true = length(AllFiles) == length(lists:uniq(AllFiles)) + catch _:_:_ -> + io:format("~p~n",[AllFiles -- lists:uniq(AllFiles)]), + error(?FUNCTION_NAME) + end, %% Test all files contain at least one file true = lists:all(fun (#{~"hasFiles" := Files}) -> erlang:length(Files) > 0 end, Packages), @@ -1764,25 +1680,6 @@ test_has_extracted_licenses(#{~"hasExtractedLicensingInfos" := LicensesInfo, true = lists:all(fun (#{~"licenseId" := LicenseId}) -> lists:member(LicenseId, LicenseRefsInProject) end, LicensesInfo), ok. -test_snippets(#{~"snippets" := Snippets, ~"files" := Files}=_Spdx) -> - true = lists:all(fun (#{ ~"SPDXID" := _Id, - ~"copyrightText" := _Copyright, - ~"licenseConcluded" := License, - ~"licenseInfoInSnippets" := Licenses, - ~"name" := _Name, - ~"ranges" := [ #{~"endPointer" := #{ ~"lineNumber" := EndLine, ~"reference" := SpdxId}, - ~"startPointer" := #{ ~"lineNumber" := StartLine, ~"reference" := SpdxId}}, - #{~"endPointer" := #{ ~"offset" := EndOffsetBytes, ~"reference" := SpdxId}, - ~"startPointer" := #{ ~"offset" := StartOffsetBytes, ~"reference" := SpdxId}} ], - ~"snippetFromFile" := SpdxId}) -> - EndLine >= StartLine andalso - EndOffsetBytes >= StartOffsetBytes andalso - lists:all(fun (L) -> lists:member(L, Licenses) end, split_licenses_in_individual_parts([License])) andalso - length(lists:filter(fun (#{~"SPDXID" := Id}) -> SpdxId == Id end, Files)) == 1 - end, Snippets), - ok. - - %% Adds LicenseRef licenses where the text is missing. extracted_license_info() -> [begin diff --git a/.github/workflows/main.yaml b/.github/workflows/main.yaml index fcfc72ff0632..fde864c7eb67 100644 --- a/.github/workflows/main.yaml +++ b/.github/workflows/main.yaml @@ -62,6 +62,7 @@ jobs: pack: name: Build Erlang/OTP (64-bit) runs-on: ubuntu-latest + if: github.repository == 'erlang/otp' || github.event_name != 'scheduled' outputs: changes: ${{ steps.changes.outputs.changes }} build-c-code: ${{ steps.c-code-changes.outputs.changes != '[]' || env.FULL_BUILD_AND_CHECK == 'true' }} diff --git a/.ort.yml b/.ort.yml index 048ea0ec891c..11d18d82700d 100644 --- a/.ort.yml +++ b/.ort.yml @@ -38,12 +38,6 @@ excludes: # Curations are used to fix wrongly detected licenses curations: license_findings: - - path: "**/vendor.info" - reason: "DATA_OF" - comment: >- - License of vendor library confuses the scanner - concluded_license: "Apache-2.0" - - path: "lib/wx/src/gen/**/wx*.erl" reason: "INCORRECT" comment: >- @@ -51,24 +45,6 @@ curations: detected_license: "Apache-2.0" concluded_license: "Apache-2.0 AND LicenseRef-scancode-wxwindows-free-doc-3" - - path: "lib/edoc/doc/guides/chapter.md" - reason: "INCORRECT" - comment: >- - License mistaken by Scancode - concluded_license: "Apache-2.0 OR LGPL-2.0-or-later" - - - path: "lib/eunit/doc/guides/chapter.md" - reason: "INCORRECT" - comment: >- - License mistaken by Scancode - concluded_license: "Apache-2.0 OR LGPL-2.0-or-later" - - - path: "lib/syntax_tools/doc/guides/chapter.md" - reason: "INCORRECT" - comment: >- - License mistaken by Scancode - concluded_license: "Apache-2.0 OR LGPL-2.0-or-later" - - path: "lib/compiler/test/beam_ssa_check_SUITE_data/phis.erl" reason: "INCORRECT" comment: >- @@ -131,13 +107,6 @@ curations: Update license to its actual license concluded_license: "Unicode-3.0" - - path: "lib/stdlib/test/shell_docs_SUITE_data/**/*" - detected_license: "NONE" - reason: "DATA_OF" - comment: >- - License not included in data files - concluded_license: "Apache-2.0" - - path: "bootstrap/bin/no_dot_erlang.boot" reason: "NOT_DETECTED" comment: >- @@ -174,20 +143,6 @@ curations: This file does not admit comments to add a license. concluded_license: "Apache-2.0" - - path: ".github/scripts/ort-scanner.es" - reason: "CODE" - comment: >- - The script contains licenses names in source code, and the - scanner considers them as its license. - concluded_license: "Apache-2.0" - - - path: "CONTRIBUTING.md" - reason: "DOCUMENTATION_OF" - comment: >- - This file contains a written Developer Certificate of Origin license - in writing, and the scanner considers it its license - concluded_license: "Apache-2.0" - - path: "lib/stdlib/test/json_SUITE_data/**/*" reason: "NOT_DETECTED" comment: >- @@ -207,19 +162,6 @@ curations: The minified version does not contain its license in writing. concluded_license: "MIT OR GPL-2.0-only" - - path: ".ort.yml" - reason: "CODE" - comment: >- - The file mentions licenses and confuses the scanner. - concluded_license: "Unlicense" - - - path: "erts/doc/notes.md" - reason: "DOCUMENTATION_OF" - comment: >- - The scanner incorrectly categorises the file with a - NOASSERTION OR Apache-2.0 when only the latter applies. - concluded_license: "Apache-2.0" - - path: "erts/autoconf/config.guess" reason: "CODE" comment: >- @@ -298,30 +240,6 @@ curations: The scanner incorrectly categorises the license concluded_license: "Zlib" - - path: "lib/megaco/test/megaco_test_msg_v3_lib.erl" - reason: "CODE" - comment: >- - The file contains variables that resemble license names - concluded_license: "Apache-2.0" - - - path: "lib/megaco/test/megaco_test_msg_v2_lib.erl" - reason: "CODE" - comment: >- - The file contains variables that resemble license names - concluded_license: "Apache-2.0" - - - path: "lib/megaco/test/megaco_test_msg_v1_lib.erl" - reason: "CODE" - comment: >- - The file contains variables that resemble license names - concluded_license: "Apache-2.0" - - - path: "lib/megaco/test/megaco_codec_v3_SUITE.erl" - reason: "CODE" - comment: >- - The file contains variables that resemble license names - concluded_license: "Apache-2.0" - - path: "erts/emulator/pcre/LICENCE" reason: "INCORRECT" comment: >- @@ -370,382 +288,11 @@ curations: The scanner incorrectly categorises this license concluded_license: "MIT" - - path: "lib/dialyzer/doc/notes.md" - reason: "DOCUMENTATION_OF" - comment: >- - The scanner incorrectly categorises this license - concluded_license: "Apache-2.0" - - - path: "lib/tools/emacs/internal_doc/emacs.sgml" - reason: "DOCUMENTATION_OF" - comment: >- - The scanner incorrectly categorises this license - concluded_license: "Apache-2.0" - - - path: "lib/edoc/include/edoc_doclet.hrl" - reason: "INCORRECT" - comment: >- - The scanner incorrectly categorises a dual license - concluded_license: "Apache-2.0 OR LGPL-2.1-or-later" - - - path: "lib/edoc/src/edoc.erl" - reason: "INCORRECT" - comment: >- - The scanner incorrectly categorises a dual license - concluded_license: "Apache-2.0 OR LGPL-2.1-or-later" - - - path: "lib/edoc/src/edoc.hrl" - reason: "INCORRECT" - comment: >- - The scanner incorrectly categorises a dual license - concluded_license: "Apache-2.0 OR LGPL-2.1-or-later" - - - path: "lib/edoc/src/edoc_data.erl" - reason: "INCORRECT" - comment: >- - The scanner incorrectly categorises a dual license - concluded_license: "Apache-2.0 OR LGPL-2.1-or-later" - - - path: "lib/edoc/src/edoc_doclet.erl" - reason: "INCORRECT" - comment: >- - The scanner incorrectly categorises a dual license - concluded_license: "Apache-2.0 OR LGPL-2.1-or-later" - - - path: "lib/edoc/src/edoc_doclet_chunks.erl" - reason: "INCORRECT" - comment: >- - The scanner incorrectly categorises a dual license - concluded_license: "Apache-2.0 OR LGPL-2.1-or-later" - - - path: "lib/edoc/src/edoc_extract.erl" - reason: "INCORRECT" - comment: >- - The scanner incorrectly categorises a dual license - concluded_license: "Apache-2.0 OR LGPL-2.1-or-later" - - - path: "lib/edoc/src/edoc_layout.erl" - reason: "INCORRECT" - comment: >- - The scanner incorrectly categorises a dual license - concluded_license: "Apache-2.0 OR LGPL-2.1-or-later" - - - path: "lib/edoc/src/edoc_layout_chunks.erl" - reason: "INCORRECT" - comment: >- - The scanner incorrectly categorises a dual license - concluded_license: "Apache-2.0 OR LGPL-2.1-or-later" - - - path: "lib/edoc/src/edoc_lib.erl" - reason: "INCORRECT" - comment: >- - The scanner incorrectly categorises a dual license - concluded_license: "Apache-2.0 OR LGPL-2.1-or-later" - - - path: "lib/edoc/src/edoc_macros.erl" - reason: "INCORRECT" - comment: >- - The scanner incorrectly categorises a dual license - concluded_license: "Apache-2.0 OR LGPL-2.1-or-later" - - - path: "lib/edoc/src/edoc_parser.yrl" - reason: "INCORRECT" - comment: >- - The scanner incorrectly categorises a dual license - concluded_license: "Apache-2.0 OR LGPL-2.1-or-later" - - - path: "lib/edoc/src/edoc_refs.erl" - reason: "INCORRECT" - comment: >- - The scanner incorrectly categorises a dual license - concluded_license: "Apache-2.0 OR LGPL-2.1-or-later" - - - path: "lib/edoc/src/edoc_report.erl" - reason: "INCORRECT" - comment: >- - The scanner incorrectly categorises a dual license - concluded_license: "Apache-2.0 OR LGPL-2.1-or-later" - - - path: "lib/edoc/src/edoc_run.erl" - reason: "INCORRECT" - comment: >- - The scanner incorrectly categorises a dual license - concluded_license: "Apache-2.0 OR LGPL-2.1-or-later" - - - path: "lib/edoc/src/edoc_tags.erl" - reason: "INCORRECT" - comment: >- - The scanner incorrectly categorises a dual license - concluded_license: "Apache-2.0 OR LGPL-2.1-or-later" - - - path: "lib/edoc/src/edoc_types.erl" - reason: "INCORRECT" - comment: >- - The scanner incorrectly categorises a dual license - concluded_license: "Apache-2.0 OR LGPL-2.1-or-later" - - - path: "lib/edoc/src/edoc_types.hrl" - reason: "INCORRECT" - comment: >- - The scanner incorrectly categorises a dual license - concluded_license: "Apache-2.0 OR LGPL-2.1-or-later" - - - path: "lib/edoc/src/edoc_wiki.erl" - reason: "INCORRECT" - comment: >- - The scanner incorrectly categorises a dual license - concluded_license: "Apache-2.0 OR LGPL-2.1-or-later" - - - path: "lib/eunit/include/eunit.hrl" - reason: "INCORRECT" - comment: >- - The scanner incorrectly categorises a dual license - concluded_license: "Apache-2.0 OR LGPL-2.1-or-later" - - - path: "lib/eunit/src/eunit.erl" - reason: "INCORRECT" - comment: >- - The scanner incorrectly categorises a dual license - concluded_license: "Apache-2.0 OR LGPL-2.1-or-later" - - - path: "lib/eunit/src/eunit_autoexport.erl" - reason: "INCORRECT" - comment: >- - The scanner incorrectly categorises a dual license - concluded_license: "Apache-2.0 OR LGPL-2.1-or-later" - - - path: "lib/eunit/src/eunit_data.erl" - reason: "INCORRECT" - comment: >- - The scanner incorrectly categorises a dual license - concluded_license: "Apache-2.0 OR LGPL-2.1-or-later" - - - path: "lib/eunit/src/eunit_internal.hrl" - reason: "INCORRECT" - comment: >- - The scanner incorrectly categorises a dual license - concluded_license: "Apache-2.0 OR LGPL-2.1-or-later" - - - path: "lib/eunit/src/eunit_lib.erl" - reason: "INCORRECT" - comment: >- - The scanner incorrectly categorises a dual license - concluded_license: "Apache-2.0 OR LGPL-2.1-or-later" - - - path: "lib/eunit/src/eunit_listener.erl" - reason: "INCORRECT" - comment: >- - The scanner incorrectly categorises a dual license - concluded_license: "Apache-2.0 OR LGPL-2.1-or-later" - - - path: "lib/eunit/src/eunit_proc.erl" - reason: "INCORRECT" - comment: >- - The scanner incorrectly categorises a dual license - concluded_license: "Apache-2.0 OR LGPL-2.1-or-later" - - - path: "lib/eunit/src/eunit_serial.erl" - reason: "INCORRECT" - comment: >- - The scanner incorrectly categorises a dual license - concluded_license: "Apache-2.0 OR LGPL-2.1-or-later" - - - path: "lib/eunit/src/eunit_server.erl" - reason: "INCORRECT" - comment: >- - The scanner incorrectly categorises a dual license - concluded_license: "Apache-2.0 OR LGPL-2.1-or-later" - - - path: "lib/eunit/src/eunit_striptests.erl" - reason: "INCORRECT" - comment: >- - The scanner incorrectly categorises a dual license - concluded_license: "Apache-2.0 OR LGPL-2.1-or-later" - - - path: "lib/eunit/src/eunit_surefire.erl" - reason: "INCORRECT" - comment: >- - The scanner incorrectly categorises a dual license - concluded_license: "Apache-2.0 OR LGPL-2.1-or-later" - - - path: "lib/eunit/src/eunit_test.erl" - reason: "INCORRECT" - comment: >- - The scanner incorrectly categorises a dual license - concluded_license: "Apache-2.0 OR LGPL-2.1-or-later" - - - path: "lib/eunit/src/eunit_tests.erl" - reason: "INCORRECT" - comment: >- - The scanner incorrectly categorises a dual license - concluded_license: "Apache-2.0 OR LGPL-2.1-or-later" - - - path: "lib/eunit/src/eunit_tty.erl" - reason: "INCORRECT" - comment: >- - The scanner incorrectly categorises a dual license - concluded_license: "Apache-2.0 OR LGPL-2.1-or-later" - - - path: "lib/eunit/test/eunit_test_listener.erl" - reason: "INCORRECT" - comment: >- - The scanner incorrectly categorises a dual license - concluded_license: "Apache-2.0 OR LGPL-2.1-or-later" - - - path: "lib/syntax_tools/src/epp_dodger.erl" - reason: "INCORRECT" - comment: >- - The scanner incorrectly categorises a dual license - concluded_license: "Apache-2.0 OR LGPL-2.1-or-later" - - - path: "lib/syntax_tools/src/erl_comment_scan.erl" - reason: "INCORRECT" - comment: >- - The scanner incorrectly categorises a dual license - concluded_license: "Apache-2.0 OR LGPL-2.1-or-later" - - - path: "lib/syntax_tools/src/erl_prettypr.erl" - reason: "INCORRECT" - comment: >- - The scanner incorrectly categorises a dual license - concluded_license: "Apache-2.0 OR LGPL-2.1-or-later" - - - path: "lib/syntax_tools/src/erl_recomment.erl" - reason: "INCORRECT" - comment: >- - The scanner incorrectly categorises a dual license - concluded_license: "Apache-2.0 OR LGPL-2.1-or-later" - - - path: "lib/syntax_tools/src/erl_syntax.erl" - reason: "INCORRECT" - comment: >- - The scanner incorrectly categorises a dual license - concluded_license: "Apache-2.0 OR LGPL-2.1-or-later" - - - path: "lib/syntax_tools/src/erl_syntax_lib.erl" - reason: "INCORRECT" - comment: >- - The scanner incorrectly categorises a dual license - concluded_license: "Apache-2.0 OR LGPL-2.1-or-later" - - - path: "lib/syntax_tools/src/merl.erl" - reason: "INCORRECT" - comment: >- - The scanner incorrectly categorises a dual license - concluded_license: "Apache-2.0 OR LGPL-2.1-or-later" - - - path: "lib/syntax_tools/src/merl_tests.erl" - reason: "INCORRECT" - comment: >- - The scanner incorrectly categorises a dual license - concluded_license: "Apache-2.0 OR LGPL-2.1-or-later" - - - path: "lib/syntax_tools/src/merl_transform.erl" - reason: "INCORRECT" - comment: >- - The scanner incorrectly categorises a dual license - concluded_license: "Apache-2.0 OR LGPL-2.1-or-later" - - - path: "lib/syntax_tools/src/prettypr.erl" - reason: "INCORRECT" - comment: >- - The scanner incorrectly categorises a dual license - concluded_license: "Apache-2.0 OR LGPL-2.1-or-later" - - - path: "lib/diameter/doc/notes.md" - reason: "NOT_DETECTED" - comment: >- - The scanner categorises as NOASSERTION when it is Apache-2.0 - concluded_license: "Apache-2.0" - - - path: "lib/ftp/doc/notes.md" - reason: "NOT_DETECTED" - comment: >- - The scanner categorises as NOASSERTION when it is Apache-2.0 - concluded_license: "Apache-2.0" - - - path: "lib/inets/doc/notes.md" - reason: "NOT_DETECTED" - comment: >- - The scanner categorises as NOASSERTION when it is Apache-2.0 - concluded_license: "Apache-2.0" - - - path: "lib/kernel/doc/notes.md" - reason: "NOT_DETECTED" - comment: >- - The scanner categorises as NOASSERTION when it is Apache-2.0 - concluded_license: "Apache-2.0" - - path: "lib/kernel/test/zlib_SUITE_data/zipdoc" reason: "INCORRECT" comment: "We do not know this license" concluded_license: "NOASSERTION" - - path: "lib/snmp/mibs/OTP-REG.mib" - reason: "NOT_DETECTED" - comment: >- - The scanner categorises as NOASSERTION when it is Apache-2.0 - concluded_license: "Apache-2.0" - - - path: "lib/snmp/mibs/OTP-SNMPEA-MIB.mib" - reason: "NOT_DETECTED" - comment: >- - The scanner categorises as NOASSERTION when it is Apache-2.0 - concluded_license: "Apache-2.0" - - - path: "lib/snmp/mibs/OTP-TC.mib" - reason: "NOT_DETECTED" - comment: >- - The scanner categorises as NOASSERTION when it is Apache-2.0 - concluded_license: "Apache-2.0" - - - path: "lib/ssh/doc/notes.md" - reason: "NOT_DETECTED" - comment: >- - The scanner categorises as NOASSERTION when it is Apache-2.0 - concluded_license: "Apache-2.0" - - - path: "lib/ssl/doc/notes.md" - reason: "NOT_DETECTED" - comment: >- - The scanner categorises as NOASSERTION when it is Apache-2.0 - concluded_license: "Apache-2.0" - - - path: "lib/stdlib/doc/notes.md" - reason: "NOT_DETECTED" - comment: >- - The scanner categorises as NOASSERTION when it is Apache-2.0 - concluded_license: "Apache-2.0" - - - path: "lib/tftp/doc/notes.md" - reason: "NOT_DETECTED" - comment: >- - The scanner categorises as NOASSERTION when it is Apache-2.0 - concluded_license: "Apache-2.0" - - - path: "lib/wx/api_gen/wx_gen_doc.erl" - reason: "NOT_DETECTED" - comment: >- - The scanner categorises as NOASSERTION when it is Apache-2.0 - concluded_license: "Apache-2.0" - - - path: "erts/emulator/test/hello_SUITE_data/hello.erl" - reason: "CODE" - comment: >- - There are variables that resemble license names - concluded_license: "Apache-2.0" - - # - # - # COPYRIGHT - # - # - - path: "system/COPYRIGHT" - reason: "DOCUMENTATION_OF" - comment: >- - The scanner mixes licenses written in text with its actual license - concluded_license: "Apache-2.0" - # # # ryu is dual license OR @@ -761,7 +308,7 @@ curations: reason: "INCORRECT" comment: >- The scanner incorrectly categorises the license - concluded_license: "(Apache-2.0 WITH LLVM-exception AND BSL-1.0) AND (Apache-2.0 OR BSL-1.0)" + concluded_license: "Apache-2.0 OR BSL-1.0" - path: "erts/emulator/ryu/d2s_full_table.h" reason: "INCORRECT" @@ -787,30 +334,12 @@ curations: The scanner incorrectly categorises the license concluded_license: "Apache-2.0 OR BSL-1.0" - - path: "erts/emulator/test/estone_SUITE.erl" - reason: "INCORRECT" - comment: >- - The scanner incorrectly categorises the license - concluded_license: "Apache-2.0" - - path: "erts/emulator/pcre/LICENCE" reason: "DOCUMENTATION_OF" comment: >- The scanner incorrectly reads the license concluded_license: "BSD-3-Clause" - - path: "erts/emulator/pcre/README.pcre_update.md" - reason: "DOCUMENTATION_OF" - comment: >- - The scanner incorrectly categorises the license - concluded_license: "BSD-3-Clause" - - - path: "lib/snmp/mibs/SNMP-USM-HMAC-SHA2-MIB.mib" - reason: "INCORRECT" - comment: >- - The scanner incorrectly categorises the license - concluded_license: "BSD-2-Clause" - - path: "erts/lib_src/yielding_c_fun/test/examples/sha256_erlang_nif/c_src/sha-2/README.md" reason: "DOCUMENTATION_OF" comment: >- @@ -877,25 +406,3 @@ curations: The scanner mixes up the copyright and license notice concluded_license: "Apache-2.0" - - path: ".github/scripts/otp-compliance.es" - reason: "CODE" - comment: >- - The scanner mixes up the copyright and license notice - concluded_license: "Apache-2.0" - - - path: "HOWTO/SBOM.md" - reason: "DOCUMENTATION_OF" - comment: >- - This file contains an example of copyright text - concluded_license: "Apache-2.0" - - # - # - # Image files - # - # - - path: "system/doc/reference_manual/assets/prio-msg-recv.png" - reason: "DOCUMENTATION_OF" - comment: >- - The scanner cannot detect this license - concluded_license: "Apache-2.0" diff --git a/HOWTO/SBOM.md b/HOWTO/SBOM.md index 7ce3db94b79d..f4a7980cebf1 100644 --- a/HOWTO/SBOM.md +++ b/HOWTO/SBOM.md @@ -170,22 +170,24 @@ Vendor packages are identified by a JSON `vendor.info` file that contains fields Each `vendor.info` file will implicitly generate a [SPDX](https://spdx.dev/) Package (within the source SBOM) to separate vendor libraries from Erlang/OTP applications. -This file may be a JSON object or a list of JSON objects. For simplicity, we document the fields using a JSON object. +This file may be a list of JSON objects. For simplicity, we document the fields using a JSON object. ```json -{ - "ID": "erts-asmjit", - "description": "Asmjit library", - "copyrightText": "Copyright (c) 2008-2023 The AsmJit Authors", - "downloadLocation": "https://github.com/asmjit/asmjit", - "homepage": "https://github.com/asmjit/asmjit", - "licenseDeclared": "Zlib", - "name": "asmjit", - "versionInfo": "a465fe71ab3d0e224b2b4bd0fac69ae68ab9239d", - "path": "./erts/emulator/asmjit", - "supplier": "Person: Petr Kobalicek", - "purl": "pkg:github/asmjit/asmjit" -} +[ + { + "ID": "erts-asmjit", + "description": "Asmjit library", + "copyrightText": "Copyright (c) 2008-2023 The AsmJit Authors", + "downloadLocation": "https://github.com/asmjit/asmjit", + "homepage": "https://github.com/asmjit/asmjit", + "licenseDeclared": "Zlib", + "name": "asmjit", + "versionInfo": "a465fe71ab3d0e224b2b4bd0fac69ae68ab9239d", + "path": "./erts/emulator/asmjit", + "supplier": "Person: Petr Kobalicek", + "purl": "pkg:github/asmjit/asmjit" + } +] ``` Fields summary: diff --git a/erts/autoconf/vendor.info b/erts/autoconf/vendor.info index b3aef0c5a8d9..428da4e848c0 100644 --- a/erts/autoconf/vendor.info +++ b/erts/autoconf/vendor.info @@ -1,10 +1,10 @@ -%% %CopyrightBegin% -%% -%% SPDX-License-Identifier: Apache-2.0 -%% -%% Copyright Ericsson AB 2025. All Rights Reserved. -%% -%% %CopyrightEnd% +// %CopyrightBegin% +// +// SPDX-License-Identifier: Apache-2.0 +// +// Copyright Ericsson AB 2025. All Rights Reserved. +// +// %CopyrightEnd% [ { "ID": "erts-config", @@ -28,7 +28,7 @@ "licenseDeclared": "MIT", "name": "Autoconf", "versionInfo": "2.71", - "path": "./erts/autoconf/install-sh", + "path": ["./erts/autoconf/install-sh"], "supplier": "Organization: Free Software Foundation", "purl": "pkg:generic/autoconf" } diff --git a/erts/emulator/asmjit/vendor.info b/erts/emulator/asmjit/vendor.info index 500d68392494..5ef8ef22d572 100644 --- a/erts/emulator/asmjit/vendor.info +++ b/erts/emulator/asmjit/vendor.info @@ -1,20 +1,22 @@ -%% %CopyrightBegin% -%% -%% SPDX-License-Identifier: Apache-2.0 -%% -%% Copyright Ericsson AB 2025. All Rights Reserved. -%% -%% %CopyrightEnd% -{ - "ID": "erts-asmjit", - "description": "Asmjit library", - "copyrightText": "Copyright (c) 2008-2023 The AsmJit Authors", - "downloadLocation": "https://github.com/asmjit/asmjit", - "homepage": "https://github.com/asmjit/asmjit", - "licenseDeclared": "Zlib", - "name": "asmjit", - "versionInfo": "a465fe71ab3d0e224b2b4bd0fac69ae68ab9239d", - "path": "./erts/emulator/asmjit", - "supplier": "Person: Petr Kobalicek", - "purl": "pkg:github/asmjit/asmjit" -} +// %CopyrightBegin% +// +// SPDX-License-Identifier: Apache-2.0 +// +// Copyright Ericsson AB 2025. All Rights Reserved. +// +// %CopyrightEnd% +[ + { + "ID": "erts-asmjit", + "description": "Asmjit library", + "copyrightText": "Copyright (c) 2008-2023 The AsmJit Authors", + "downloadLocation": "https://github.com/asmjit/asmjit", + "homepage": "https://github.com/asmjit/asmjit", + "licenseDeclared": "Zlib", + "name": "asmjit", + "versionInfo": "a465fe71ab3d0e224b2b4bd0fac69ae68ab9239d", + "path": "./erts/emulator/asmjit", + "supplier": "Person: Petr Kobalicek", + "purl": "pkg:github/asmjit/asmjit" + } +] diff --git a/erts/emulator/beam/vendor.info b/erts/emulator/beam/vendor.info index 9727e970df6f..5c0f88bfa1fc 100644 --- a/erts/emulator/beam/vendor.info +++ b/erts/emulator/beam/vendor.info @@ -1,21 +1,21 @@ -%% %CopyrightBegin% -%% -%% SPDX-License-Identifier: Apache-2.0 -%% -%% Copyright Ericsson AB 2025. All Rights Reserved. -%% -%% %CopyrightEnd% +// %CopyrightBegin% +// +// SPDX-License-Identifier: Apache-2.0 +// +// Copyright Ericsson AB 2025. All Rights Reserved. +// +// %CopyrightEnd% [ { "ID": "erts-fp16", "description": "fp16 library", - "copyrightText": "Copyright (c) 2017 Facebook Inc./nCopyright (c) 2017 Georgia Institute of Technology/nCopyright 2019 Google LLC", + "copyrightText": "Copyright (c) 2017 Facebook Inc.\nCopyright (c) 2017 Georgia Institute of Technology\nCopyright 2019 Google LLC", "downloadLocation": "https://github.com/Maratyszcza/FP16", "homepage": "https://github.com/Maratyszcza/FP16", "licenseDeclared": "MIT", "name": "fp16", "versionInfo": "0a92994d729ff76a58f692d3028ca1b64b145d91", - "path": "./erts/emulator/beam/erl_bits_f16.h", + "path": ["./erts/emulator/beam/erl_bits_f16.h"], "supplier": "Person: Marat Dukhan", "purl": "pkg:github/maratyszcza/fp16" }, @@ -28,7 +28,7 @@ "licenseDeclared": "TCL", "name": "tcl", "versionInfo": "7.6", - "path": "./erts/emulator/beam/erl_posix_str.c", + "path": ["./erts/emulator/beam/erl_posix_str.c"], "supplier": "Organization: Tcl Core Team", "purl": "pkg:generic/tcl" } diff --git a/erts/emulator/internal_doc/assets/Makefile b/erts/emulator/internal_doc/assets/Makefile index 111cb393fb7f..30c3a1f13457 100644 --- a/erts/emulator/internal_doc/assets/Makefile +++ b/erts/emulator/internal_doc/assets/Makefile @@ -1,3 +1,22 @@ +# %CopyrightBegin% +# +# SPDX-License-Identifier: Apache-2.0 +# +# +# 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% + # In order to update the figures you have to have both dia # and imagemagick installed. diff --git a/erts/emulator/internal_doc/assets/beamasm-perf-annotate.png.license b/erts/emulator/internal_doc/assets/beamasm-perf-annotate.png.license new file mode 100644 index 000000000000..52a6180f341a --- /dev/null +++ b/erts/emulator/internal_doc/assets/beamasm-perf-annotate.png.license @@ -0,0 +1,6 @@ +%CopyrightBegin% + +SPDX-License-Identifier: Apache-2.0 + + +%CopyrightEnd% diff --git a/erts/emulator/internal_doc/assets/gc-heap-scan1.dia.license b/erts/emulator/internal_doc/assets/gc-heap-scan1.dia.license new file mode 100644 index 000000000000..52a6180f341a --- /dev/null +++ b/erts/emulator/internal_doc/assets/gc-heap-scan1.dia.license @@ -0,0 +1,6 @@ +%CopyrightBegin% + +SPDX-License-Identifier: Apache-2.0 + + +%CopyrightEnd% diff --git a/erts/emulator/internal_doc/assets/gc-heap-scan1.png.license b/erts/emulator/internal_doc/assets/gc-heap-scan1.png.license new file mode 100644 index 000000000000..52a6180f341a --- /dev/null +++ b/erts/emulator/internal_doc/assets/gc-heap-scan1.png.license @@ -0,0 +1,6 @@ +%CopyrightBegin% + +SPDX-License-Identifier: Apache-2.0 + + +%CopyrightEnd% diff --git a/erts/emulator/internal_doc/assets/gc-heap-stop.dia.license b/erts/emulator/internal_doc/assets/gc-heap-stop.dia.license new file mode 100644 index 000000000000..52a6180f341a --- /dev/null +++ b/erts/emulator/internal_doc/assets/gc-heap-stop.dia.license @@ -0,0 +1,6 @@ +%CopyrightBegin% + +SPDX-License-Identifier: Apache-2.0 + + +%CopyrightEnd% diff --git a/erts/emulator/internal_doc/assets/gc-heap-stop.png.license b/erts/emulator/internal_doc/assets/gc-heap-stop.png.license new file mode 100644 index 000000000000..52a6180f341a --- /dev/null +++ b/erts/emulator/internal_doc/assets/gc-heap-stop.png.license @@ -0,0 +1,6 @@ +%CopyrightBegin% + +SPDX-License-Identifier: Apache-2.0 + + +%CopyrightEnd% diff --git a/erts/emulator/internal_doc/assets/gc-rootset-scan.dia.license b/erts/emulator/internal_doc/assets/gc-rootset-scan.dia.license new file mode 100644 index 000000000000..52a6180f341a --- /dev/null +++ b/erts/emulator/internal_doc/assets/gc-rootset-scan.dia.license @@ -0,0 +1,6 @@ +%CopyrightBegin% + +SPDX-License-Identifier: Apache-2.0 + + +%CopyrightEnd% diff --git a/erts/emulator/internal_doc/assets/gc-rootset-scan.png.license b/erts/emulator/internal_doc/assets/gc-rootset-scan.png.license new file mode 100644 index 000000000000..52a6180f341a --- /dev/null +++ b/erts/emulator/internal_doc/assets/gc-rootset-scan.png.license @@ -0,0 +1,6 @@ +%CopyrightBegin% + +SPDX-License-Identifier: Apache-2.0 + + +%CopyrightEnd% diff --git a/erts/emulator/internal_doc/assets/gc-start.dia.license b/erts/emulator/internal_doc/assets/gc-start.dia.license new file mode 100644 index 000000000000..52a6180f341a --- /dev/null +++ b/erts/emulator/internal_doc/assets/gc-start.dia.license @@ -0,0 +1,6 @@ +%CopyrightBegin% + +SPDX-License-Identifier: Apache-2.0 + + +%CopyrightEnd% diff --git a/erts/emulator/internal_doc/assets/gc-start.png.license b/erts/emulator/internal_doc/assets/gc-start.png.license new file mode 100644 index 000000000000..52a6180f341a --- /dev/null +++ b/erts/emulator/internal_doc/assets/gc-start.png.license @@ -0,0 +1,6 @@ +%CopyrightBegin% + +SPDX-License-Identifier: Apache-2.0 + + +%CopyrightEnd% diff --git a/erts/emulator/internal_doc/assets/gc-watermark-2.dia.license b/erts/emulator/internal_doc/assets/gc-watermark-2.dia.license new file mode 100644 index 000000000000..52a6180f341a --- /dev/null +++ b/erts/emulator/internal_doc/assets/gc-watermark-2.dia.license @@ -0,0 +1,6 @@ +%CopyrightBegin% + +SPDX-License-Identifier: Apache-2.0 + + +%CopyrightEnd% diff --git a/erts/emulator/internal_doc/assets/gc-watermark-2.png.license b/erts/emulator/internal_doc/assets/gc-watermark-2.png.license new file mode 100644 index 000000000000..52a6180f341a --- /dev/null +++ b/erts/emulator/internal_doc/assets/gc-watermark-2.png.license @@ -0,0 +1,6 @@ +%CopyrightBegin% + +SPDX-License-Identifier: Apache-2.0 + + +%CopyrightEnd% diff --git a/erts/emulator/internal_doc/assets/gc-watermark.dia.license b/erts/emulator/internal_doc/assets/gc-watermark.dia.license new file mode 100644 index 000000000000..52a6180f341a --- /dev/null +++ b/erts/emulator/internal_doc/assets/gc-watermark.dia.license @@ -0,0 +1,6 @@ +%CopyrightBegin% + +SPDX-License-Identifier: Apache-2.0 + + +%CopyrightEnd% diff --git a/erts/emulator/internal_doc/assets/gc-watermark.png.license b/erts/emulator/internal_doc/assets/gc-watermark.png.license new file mode 100644 index 000000000000..52a6180f341a --- /dev/null +++ b/erts/emulator/internal_doc/assets/gc-watermark.png.license @@ -0,0 +1,6 @@ +%CopyrightBegin% + +SPDX-License-Identifier: Apache-2.0 + + +%CopyrightEnd% diff --git a/erts/emulator/internal_doc/assets/perf-beamasm-merged.svg b/erts/emulator/internal_doc/assets/perf-beamasm-merged.svg index ea56070144d7..c6e747eabafc 100644 --- a/erts/emulator/internal_doc/assets/perf-beamasm-merged.svg +++ b/erts/emulator/internal_doc/assets/perf-beamasm-merged.svg @@ -1,4 +1,24 @@ + diff --git a/erts/emulator/internal_doc/assets/perf-beamasm.png.license b/erts/emulator/internal_doc/assets/perf-beamasm.png.license new file mode 100644 index 000000000000..52a6180f341a --- /dev/null +++ b/erts/emulator/internal_doc/assets/perf-beamasm.png.license @@ -0,0 +1,6 @@ +%CopyrightBegin% + +SPDX-License-Identifier: Apache-2.0 + + +%CopyrightEnd% diff --git a/erts/emulator/internal_doc/assets/perf-beamasm.svg b/erts/emulator/internal_doc/assets/perf-beamasm.svg index 59b4c5cdf1e7..2d3c23869958 100644 --- a/erts/emulator/internal_doc/assets/perf-beamasm.svg +++ b/erts/emulator/internal_doc/assets/perf-beamasm.svg @@ -1,4 +1,24 @@ + diff --git a/erts/emulator/internal_doc/dec.dat.license b/erts/emulator/internal_doc/dec.dat.license new file mode 100644 index 000000000000..52a6180f341a --- /dev/null +++ b/erts/emulator/internal_doc/dec.dat.license @@ -0,0 +1,6 @@ +%CopyrightBegin% + +SPDX-License-Identifier: Apache-2.0 + + +%CopyrightEnd% diff --git a/erts/emulator/openssl/vendor.info b/erts/emulator/openssl/vendor.info index f3c4233b35d8..3b709f40587b 100644 --- a/erts/emulator/openssl/vendor.info +++ b/erts/emulator/openssl/vendor.info @@ -1,20 +1,22 @@ -%% %CopyrightBegin% -%% -%% SPDX-License-Identifier: Apache-2.0 -%% -%% Copyright Ericsson AB 2025. All Rights Reserved. -%% -%% %CopyrightEnd% -{ - "ID": "erts-openssl", - "description": "Openssl MD5 implementation in ERTS", - "copyrightText": "Copyright 1995-2022 The OpenSSL Project Authors. All Rights Reserved.", - "downloadLocation": "https://github.com/openssl/openssl", - "homepage": "https://www.openssl.org/", - "licenseDeclared": "Apache-2.0", - "name": "openssl", - "versionInfo": "3.1.4", - "path": "./erts/emulator/openssl", - "supplier": "Organization: OpenSSL Mission", - "purl": "pkg:generic/openssl" -} +// %CopyrightBegin% +// +// SPDX-License-Identifier: Apache-2.0 +// +// Copyright Ericsson AB 2025. All Rights Reserved. +// +// %CopyrightEnd% +[ + { + "ID": "erts-openssl", + "description": "Openssl MD5 implementation in ERTS", + "copyrightText": "Copyright 1995-2022 The OpenSSL Project Authors. All Rights Reserved.", + "downloadLocation": "https://github.com/openssl/openssl", + "homepage": "https://www.openssl.org/", + "licenseDeclared": "Apache-2.0", + "name": "openssl", + "versionInfo": "3.1.4", + "path": "./erts/emulator/openssl", + "supplier": "Organization: OpenSSL Mission", + "purl": "pkg:generic/openssl" + } +] diff --git a/erts/emulator/pcre/.gitignore b/erts/emulator/pcre/.gitignore new file mode 100644 index 000000000000..1ad207f3adeb --- /dev/null +++ b/erts/emulator/pcre/.gitignore @@ -0,0 +1 @@ +*.gen.h diff --git a/erts/emulator/pcre/vendor.info b/erts/emulator/pcre/vendor.info index c8275efa9b08..c655601e0a99 100644 --- a/erts/emulator/pcre/vendor.info +++ b/erts/emulator/pcre/vendor.info @@ -1,20 +1,22 @@ -%% %CopyrightBegin% -%% -%% SPDX-License-Identifier: Apache-2.0 -%% -%% Copyright Ericsson AB 2025. All Rights Reserved. -%% -%% %CopyrightEnd% -{ - "ID": "erts-pcre", - "description": "PCRE2 library", - "copyrightText": "NOASSERTION", - "downloadLocation": "git+https://github.com/PCRE2Project/pcre2.git", - "homepage": "https://pcre2project.github.io/pcre2/", - "licenseDeclared": "BSD-3-Clause", - "name": "pcre2", - "versionInfo": "10.44", - "path": "./erts/emulator/pcre", - "supplier": "Person: Philip Hazel", - "purl": "pkg:generic/pcre2" -} +// %CopyrightBegin% +// +// SPDX-License-Identifier: Apache-2.0 +// +// Copyright Ericsson AB 2025. All Rights Reserved. +// +// %CopyrightEnd% +[ + { + "ID": "erts-pcre", + "description": "PCRE2 library", + "copyrightText": "NOASSERTION", + "downloadLocation": "git+https://github.com/PCRE2Project/pcre2.git", + "homepage": "https://pcre2project.github.io/pcre2/", + "licenseDeclared": "BSD-3-Clause", + "name": "pcre2", + "versionInfo": "10.44", + "path": "./erts/emulator/pcre", + "supplier": "Person: Philip Hazel", + "purl": "pkg:generic/pcre2" + } +] diff --git a/erts/emulator/ryu/LICENSE-Apache2 b/erts/emulator/ryu/LICENSE-Apache2 new file mode 100644 index 000000000000..261eeb9e9f8b --- /dev/null +++ b/erts/emulator/ryu/LICENSE-Apache2 @@ -0,0 +1,201 @@ + Apache License + Version 2.0, January 2004 + http://www.apache.org/licenses/ + + TERMS AND CONDITIONS FOR USE, REPRODUCTION, AND DISTRIBUTION + + 1. Definitions. + + "License" shall mean the terms and conditions for use, reproduction, + and distribution as defined by Sections 1 through 9 of this document. + + "Licensor" shall mean the copyright owner or entity authorized by + the copyright owner that is granting the License. + + "Legal Entity" shall mean the union of the acting entity and all + other entities that control, are controlled by, or are under common + control with that entity. For the purposes of this definition, + "control" means (i) the power, direct or indirect, to cause the + direction or management of such entity, whether by contract or + otherwise, or (ii) ownership of fifty percent (50%) or more of the + outstanding shares, or (iii) beneficial ownership of such entity. + + "You" (or "Your") shall mean an individual or Legal Entity + exercising permissions granted by this License. + + "Source" form shall mean the preferred form for making modifications, + including but not limited to software source code, documentation + source, and configuration files. + + "Object" form shall mean any form resulting from mechanical + transformation or translation of a Source form, including but + not limited to compiled object code, generated documentation, + and conversions to other media types. + + "Work" shall mean the work of authorship, whether in Source or + Object form, made available under the License, as indicated by a + copyright notice that is included in or attached to the work + (an example is provided in the Appendix below). + + "Derivative Works" shall mean any work, whether in Source or Object + form, that is based on (or derived from) the Work and for which the + editorial revisions, annotations, elaborations, or other modifications + represent, as a whole, an original work of authorship. For the purposes + of this License, Derivative Works shall not include works that remain + separable from, or merely link (or bind by name) to the interfaces of, + the Work and Derivative Works thereof. + + "Contribution" shall mean any work of authorship, including + the original version of the Work and any modifications or additions + to that Work or Derivative Works thereof, that is intentionally + submitted to Licensor for inclusion in the Work by the copyright owner + or by an individual or Legal Entity authorized to submit on behalf of + the copyright owner. For the purposes of this definition, "submitted" + means any form of electronic, verbal, or written communication sent + to the Licensor or its representatives, including but not limited to + communication on electronic mailing lists, source code control systems, + and issue tracking systems that are managed by, or on behalf of, the + Licensor for the purpose of discussing and improving the Work, but + excluding communication that is conspicuously marked or otherwise + designated in writing by the copyright owner as "Not a Contribution." + + "Contributor" shall mean Licensor and any individual or Legal Entity + on behalf of whom a Contribution has been received by Licensor and + subsequently incorporated within the Work. + + 2. Grant of Copyright License. Subject to the terms and conditions of + this License, each Contributor hereby grants to You a perpetual, + worldwide, non-exclusive, no-charge, royalty-free, irrevocable + copyright license to reproduce, prepare Derivative Works of, + publicly display, publicly perform, sublicense, and distribute the + Work and such Derivative Works in Source or Object form. + + 3. Grant of Patent License. Subject to the terms and conditions of + this License, each Contributor hereby grants to You a perpetual, + worldwide, non-exclusive, no-charge, royalty-free, irrevocable + (except as stated in this section) patent license to make, have made, + use, offer to sell, sell, import, and otherwise transfer the Work, + where such license applies only to those patent claims licensable + by such Contributor that are necessarily infringed by their + Contribution(s) alone or by combination of their Contribution(s) + with the Work to which such Contribution(s) was submitted. If You + institute patent litigation against any entity (including a + cross-claim or counterclaim in a lawsuit) alleging that the Work + or a Contribution incorporated within the Work constitutes direct + or contributory patent infringement, then any patent licenses + granted to You under this License for that Work shall terminate + as of the date such litigation is filed. + + 4. Redistribution. You may reproduce and distribute copies of the + Work or Derivative Works thereof in any medium, with or without + modifications, and in Source or Object form, provided that You + meet the following conditions: + + (a) You must give any other recipients of the Work or + Derivative Works a copy of this License; and + + (b) You must cause any modified files to carry prominent notices + stating that You changed the files; and + + (c) You must retain, in the Source form of any Derivative Works + that You distribute, all copyright, patent, trademark, and + attribution notices from the Source form of the Work, + excluding those notices that do not pertain to any part of + the Derivative Works; and + + (d) If the Work includes a "NOTICE" text file as part of its + distribution, then any Derivative Works that You distribute must + include a readable copy of the attribution notices contained + within such NOTICE file, excluding those notices that do not + pertain to any part of the Derivative Works, in at least one + of the following places: within a NOTICE text file distributed + as part of the Derivative Works; within the Source form or + documentation, if provided along with the Derivative Works; or, + within a display generated by the Derivative Works, if and + wherever such third-party notices normally appear. The contents + of the NOTICE file are for informational purposes only and + do not modify the License. You may add Your own attribution + notices within Derivative Works that You distribute, alongside + or as an addendum to the NOTICE text from the Work, provided + that such additional attribution notices cannot be construed + as modifying the License. + + You may add Your own copyright statement to Your modifications and + may provide additional or different license terms and conditions + for use, reproduction, or distribution of Your modifications, or + for any such Derivative Works as a whole, provided Your use, + reproduction, and distribution of the Work otherwise complies with + the conditions stated in this License. + + 5. Submission of Contributions. Unless You explicitly state otherwise, + any Contribution intentionally submitted for inclusion in the Work + by You to the Licensor shall be under the terms and conditions of + this License, without any additional terms or conditions. + Notwithstanding the above, nothing herein shall supersede or modify + the terms of any separate license agreement you may have executed + with Licensor regarding such Contributions. + + 6. Trademarks. This License does not grant permission to use the trade + names, trademarks, service marks, or product names of the Licensor, + except as required for reasonable and customary use in describing the + origin of the Work and reproducing the content of the NOTICE file. + + 7. Disclaimer of Warranty. Unless required by applicable law or + agreed to in writing, Licensor provides the Work (and each + Contributor provides its Contributions) on an "AS IS" BASIS, + WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or + implied, including, without limitation, any warranties or conditions + of TITLE, NON-INFRINGEMENT, MERCHANTABILITY, or FITNESS FOR A + PARTICULAR PURPOSE. You are solely responsible for determining the + appropriateness of using or redistributing the Work and assume any + risks associated with Your exercise of permissions under this License. + + 8. Limitation of Liability. In no event and under no legal theory, + whether in tort (including negligence), contract, or otherwise, + unless required by applicable law (such as deliberate and grossly + negligent acts) or agreed to in writing, shall any Contributor be + liable to You for damages, including any direct, indirect, special, + incidental, or consequential damages of any character arising as a + result of this License or out of the use or inability to use the + Work (including but not limited to damages for loss of goodwill, + work stoppage, computer failure or malfunction, or any and all + other commercial damages or losses), even if such Contributor + has been advised of the possibility of such damages. + + 9. Accepting Warranty or Additional Liability. While redistributing + the Work or Derivative Works thereof, You may choose to offer, + and charge a fee for, acceptance of support, warranty, indemnity, + or other liability obligations and/or rights consistent with this + License. However, in accepting such obligations, You may act only + on Your own behalf and on Your sole responsibility, not on behalf + of any other Contributor, and only if You agree to indemnify, + defend, and hold each Contributor harmless for any liability + incurred by, or claims asserted against, such Contributor by reason + of your accepting any such warranty or additional liability. + + END OF TERMS AND CONDITIONS + + APPENDIX: How to apply the Apache License to your work. + + To apply the Apache License to your work, attach the following + boilerplate notice, with the fields enclosed by brackets "[]" + replaced with your own identifying information. (Don't include + the brackets!) The text should be enclosed in the appropriate + comment syntax for the file format. We also recommend that a + file or class name and description of purpose be included on the + same "printed page" as the copyright notice for easier + identification within third-party archives. + + Copyright [yyyy] [name of copyright owner] + + 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. diff --git a/erts/emulator/ryu/LICENSE-Boost b/erts/emulator/ryu/LICENSE-Boost new file mode 100644 index 000000000000..36b7cd93cdfb --- /dev/null +++ b/erts/emulator/ryu/LICENSE-Boost @@ -0,0 +1,23 @@ +Boost Software License - Version 1.0 - August 17th, 2003 + +Permission is hereby granted, free of charge, to any person or organization +obtaining a copy of the software and accompanying documentation covered by +this license (the "Software") to use, reproduce, display, distribute, +execute, and transmit the Software, and to prepare derivative works of the +Software, and to permit third-parties to whom the Software is furnished to +do so, all subject to the following: + +The copyright notices in the Software and this entire statement, including +the above license grant, this restriction and the following disclaimer, +must be included in all copies of the Software, in whole or in part, and +all derivative works of the Software, unless such copies or derivative +works are solely in the form of machine-executable object code generated by +a source language processor. + +THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR +IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, +FITNESS FOR A PARTICULAR PURPOSE, TITLE AND NON-INFRINGEMENT. IN NO EVENT +SHALL THE COPYRIGHT HOLDERS OR ANYONE DISTRIBUTING THE SOFTWARE BE LIABLE +FOR ANY DAMAGES OR OTHER LIABILITY, WHETHER IN CONTRACT, TORT OR OTHERWISE, +ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER +DEALINGS IN THE SOFTWARE. diff --git a/erts/emulator/ryu/README.md b/erts/emulator/ryu/README.md new file mode 100644 index 000000000000..c3b16dfb5c4d --- /dev/null +++ b/erts/emulator/ryu/README.md @@ -0,0 +1,49 @@ + + +# Erlang RYU + +To work with the Erlang VM, Ryu has been changed in three important ways. These +changes have been marked with a `//CHANGE_FOR_ERLANG` comment explaining them in +the code. + +1. We only kept the bare minimum files needed to generate a double to string with the shortest algorithm, with the widest lookup table +2. We deleted the code producing the final string, this is handled using a modified version of to_chars from the MS STL. +3. All other unneeded code has been deleted + +This is build with our own makefile. + +Some of the more minor difference: + +- the Zero case in common.h is changed to correspond to erlang fixed point version +- the MS STL pointer check are not here. Erlang generate a 256 bytes buffer, we only need 30 maximum. Beware what this mean when refactoring. + +# How to update the Ryu version used by Erlang + +To update run the `update.sh` script in this folder. It uses + as a base and tries to merge + into it. If there are no merge conflicts it then +checks that the STL file we use had changed. If it has changed you need to manually +check if there are any changes in the `__to_chars` function and if so see if they +need to be uplifted. + +The update script will also bump the versions in vendor.info so that the SBOM +contains the latest versions. \ No newline at end of file diff --git a/erts/emulator/ryu/README.ryu_update.md b/erts/emulator/ryu/README.ryu_update.md deleted file mode 100644 index cc60ea169003..000000000000 --- a/erts/emulator/ryu/README.ryu_update.md +++ /dev/null @@ -1,20 +0,0 @@ -# How to update the Ryu version used by Erlang - -Last commit taken : 844864ac213bdbf1fb57e6f51c653b3d90af0937 - -## The basic changes to the Ryu library - -To work with the Erlang VM, Ryu has been changed in three important ways. These -changes have been marked with a `//CHANGE_FOR_ERLANG` comment explaining them in -the code. - -1. We only kept the bare minimum files needed to generate a double to string with the shortest algorithm, with the widest lookup table -2. We deleted the code producing the final string, this is handled using a modified version of to_chars from the MS STL. -3. All other unneeded code has been deleted - -This is build with our own makefile. - -Some of the more minor difference: - -- the Zero case in common.h is changed to correspond to erlang fixed point version -- the MS STL pointer check are not here. Erlang generate a 256 bytes buffer, we only need 30 maximum. Beware what this mean when refactoring. diff --git a/erts/emulator/ryu/d2s.c b/erts/emulator/ryu/d2s.c index f3ac78306a73..f4a997a1ff02 100644 --- a/erts/emulator/ryu/d2s.c +++ b/erts/emulator/ryu/d2s.c @@ -84,6 +84,10 @@ typedef struct floating_decimal_64 { int32_t exponent; } floating_decimal_64; +// CHANGE_FOR_ERLANG include STL to_chars function +#include "to_chars.h" +// END CHANGE_FOR_ERLANG + static inline floating_decimal_64 d2d(const uint64_t ieeeMantissa, const uint32_t ieeeExponent) { int32_t e2; uint64_t m2; @@ -295,352 +299,6 @@ static inline floating_decimal_64 d2d(const uint64_t ieeeMantissa, const uint32_ return fd; } -//CHANGE_FOR_ERLANG: This format is new, it is here to handle the different format switch used in the STL code -enum chars_format { - FMT_SCIENTIFIC, - FMT_FIXED, - FMT_GENERAL -}; - -// SPDX-SnippetBegin -// SPDX-SnippetCopyrightText: Copyright (c) Microsoft Corporation. -// SPDX-SnippetCopyrightText: Copyright 2018 Ulf Adams -// SPDX-SnippetCopyrightText: Copyright (c) Microsoft Corporation. All rights reserved. -// SPDX-License-Identifier: (Apache-2.0 WITH LLVM-exception) AND BSL-1.0 -// -// The license information in the original file is not -// clear on whether it should be AND or OR between -// "Apache 2.0 with LLVM-exception" and "Boost Software License 1.0". -// Therefore, just to be safe, an AND was chosen in the SPDX license -// identifier expression above. -// Library: STL -// Git repository: https://github.com/microsoft/STL -// Commit: e745bad3b1d05b5b19ec652d68abb37865ffa454 -// Original function: https://github.com/microsoft/STL/blob/e745bad3b1d05b5b19ec652d68abb37865ffa454/stl/inc/xcharconv_ryu.h#L1926 - - -// This is inspired from the MS STL Charconv, under Apache with LLVM exception licence -// see https://github.com/microsoft/STL/blob/main/LICENSE.txt -// The inspiration is at https://github.com/microsoft/STL/blob/e745bad3b1d05b5b19ec652d68abb37865ffa454/stl/inc/xcharconv_ryu.h#L1926 -// CHANGE_FOR_ERLANG all the types and typecast have been adapted to C types from Cpp. -// I have also kept the Ryu original function head as it allows to not impact the rest of the code -// __v and __mantissa and __exponent have lost their double underscore over the whole function -// all the test on the lenght of the buffer have been dropped too. This could need change, but -// we always pass a 256 bytes buffer when we only need 26 bytes maximum. -static inline int to_chars(const floating_decimal_64 v, const bool sign, char* const result) { - // Step 5: Print the decimal representation. - uint64_t __output = v.mantissa; - int32_t _Ryu_exponent = v.exponent; - const uint32_t __olength = decimalLength17(__output); - int32_t _Scientific_exponent = _Ryu_exponent + ((int32_t) __olength) - 1; - - // CHANGE_FOR_ERLANG: we use our chars_format instead of the STL one - enum chars_format _Fmt; - - int32_t _Lower; - int32_t _Upper; - - if (__olength == 1) { - // CHANGE_FOR_ERLANG the format and examples have been adapted to the erlang format - // as the original would have not shown a change in format - // (erlang always add ".0" to scientific format) and omit the + in the exponent - // Value | Fixed | Scientific - // 1e-4 | "0.0001" | "1.0e-4" - // 1e2 | "100.0" | "1.0e2" - // CHANGE_FOR_ERLANG the values for a switch, as seen in the example above, for erlang - // are different than for STL format. - _Lower = -4; - _Upper = 2; - } else if (_Scientific_exponent >= 10) { - // CHANGE_FOR_ERLANG This case does not exist for the STL and is due to the - // negative sign in the exponent. - // Value | Fixed | Scientific - // 123456789e1 | "1234567890.0" | "1.23456789e9" - // 123456789e2 | "12345678900.0" | "1.23456789e10" - - _Lower = - (int32_t) (__olength + 2); - _Upper = 2; - } else { - // CHANGE_FOR_ERLANG the format and examples have been adapted to the erlang format - // as the original would have not shown a change in format - // (erlang always add ".0" to scientific format) and omit the + in the exponent - // Value | Fixed | Scientific - // 1234e-6 | "0.001234" | "1.234e-4" - // 1234e1 | "12340.0" | "1.234e4" - // CHANGE_FOR_ERLANG the values for a switch, as seen in the example above, for erlang - // are different than for STL format. - _Lower = - (int32_t) (__olength + 2); - _Upper = 1; - } - - if (_Lower <= _Ryu_exponent && _Ryu_exponent <= _Upper) { - // CHANGE_FOR_ERLANG this is added to handle the -2**53, 2**53 range special case - // These are edge cases not captured above, all the other are naturally handled - // by _Lower nad _Upper - if ((__output >= (1ull << 53) && _Ryu_exponent == 0) - || (__output > ((1ull << 52) / 5) && _Ryu_exponent == 1) - || (__output > ((1ull << 51) / 25) && _Ryu_exponent == 2)) { - _Fmt = FMT_SCIENTIFIC; - } else { - _Fmt = FMT_FIXED; - } - } else { - // CHANGE_FOR_ERLANG we do not need to handle the %g case here. - _Fmt = FMT_SCIENTIFIC; - } - - // CHANGE_FOR_ERLANG we handle the sign here as it is handled outside of this in the STL case - // and we need it to compute the start of the buffer for the characters after - if (sign) { - result[0] = '-'; - } - - // CHANGE_FOR_ERLANG we compute the start of the usable buffer. It is done here - // in order to be fixed for both branches of formatting. - char* const __result = result + sign; - - if (_Fmt == FMT_FIXED) { - // CHANGE_FOR_ERLANG this whole table has been adapted to erlang examples to help - // debug and evolve the edge cases - // Example: __output == 1729, __olength == 4 - - // _Ryu_exponent | Printed | _Whole_digits | _Total_fixed_length | Notes - // --------------|----------|---------------|----------------------|--------------------------------------- - // 1 | 17290.0 | 5 | _Whole_digits + 2 | Unified length cases. - // 0 | 1729.0 | 4 | | - // --------------|----------|---------------|----------------------|--------------------------------------- - // -1 | 172.9 | 3 | __olength + 1 | This case can't happen for - // -2 | 17.29 | 2 | | __olength == 1, but no additional - // -3 | 1.729 | 1 | | code is needed to avoid it. - // --------------|----------|---------------|----------------------|--------------------------------------- - // -4 | 0.1729 | 0 | 2 - _Ryu_exponent | If the decimal point appears, we need - // -5 | 0.01729 | -1 | | to put the "0" in front - // -6 | 0.001729 | -2 | | - - const int32_t _Whole_digits = (int32_t) (__olength) + _Ryu_exponent; - - uint32_t _Total_fixed_length; - if (_Ryu_exponent >= 0) { - // CHANGE_FOR_ERLANG the examples and values have been adapted to erlang format one - // CHANGE_FOR_ERLANG we also dropped the whole adjustement, as it is only of value - // for %f which we do not handle - // cases "17290.0" and "1729.0" - _Total_fixed_length = (uint32_t) (_Whole_digits) + 2; - } else if (_Whole_digits > 0) { // case "17.29" - _Total_fixed_length = __olength + 1; - } else { // case "0.001729" - _Total_fixed_length = (uint32_t) (2 - _Ryu_exponent); - } - - char* _Mid; - if (_Ryu_exponent >= 0) { // case "172900.0" - // CHANGE_FOR_ERLANG we do not need the can_use_ryu, as we are not doing %f - // but always shortest round_trip. The whole complexity here is dropped - // Print the decimal digits, left-aligned within [result, result + _Total_fixed_length). - _Mid = __result + __olength; - } else { // cases "1729.0", "17.29", and "0.001729" - // Print the decimal digits, right-aligned within [result, result + _Total_fixed_length). - _Mid = __result + _Total_fixed_length; - } - - // We prefer 32-bit operations, even on 64-bit platforms. - // We have at most 17 digits, and uint32_t can store 9 digits. - // If __output doesn't fit into uint32_t, we cut off 8 digits, - // so the rest will fit into uint32_t. - // CHANGE_FOR_ERLANG we consider in this whole thing that memcopy use the same - // char has defined in the DIGIT_TABLE - // CHANGE_FOR_ERLANG __DIGIT_TABLE became DIGIT_TABLE - if ((__output >> 32) != 0) { - // Expensive 64-bit division. - const uint64_t __q = div1e8(__output); - uint32_t __output2 = (uint32_t) (__output - 100000000 * __q); - __output = __q; - - const uint32_t __c = __output2 % 10000; - __output2 /= 10000; - const uint32_t __d = __output2 % 10000; - const uint32_t __c0 = (__c % 100) << 1; - const uint32_t __c1 = (__c / 100) << 1; - const uint32_t __d0 = (__d % 100) << 1; - const uint32_t __d1 = (__d / 100) << 1; - - memcpy(_Mid -= 2, DIGIT_TABLE + __c0, 2); - memcpy(_Mid -= 2, DIGIT_TABLE + __c1, 2); - memcpy(_Mid -= 2, DIGIT_TABLE + __d0, 2); - memcpy(_Mid -= 2, DIGIT_TABLE + __d1, 2); - } - uint32_t __output2 = (uint32_t) __output; - while (__output2 >= 10000) { -#ifdef __clang__ // TRANSITION, LLVM-38217 - const uint32_t __c = __output2 - 10000 * (__output2 / 10000); -#else - const uint32_t __c = __output2 % 10000; -#endif - __output2 /= 10000; - const uint32_t __c0 = (__c % 100) << 1; - const uint32_t __c1 = (__c / 100) << 1; - memcpy(_Mid -= 2, DIGIT_TABLE + __c0, 2); - memcpy(_Mid -= 2, DIGIT_TABLE + __c1, 2); - } - if (__output2 >= 100) { - const uint32_t __c = (__output2 % 100) << 1; - __output2 /= 100; - memcpy(_Mid -= 2, DIGIT_TABLE + __c, 2); - } - if (__output2 >= 10) { - const uint32_t __c = __output2 << 1; - memcpy(_Mid -= 2, DIGIT_TABLE + __c, 2); - } else { - *--_Mid = (char) ('0' + __output2); - } - - if (_Ryu_exponent > 0) { // case "172900.0" - // Performance note: it might be more efficient to do this immediately after setting _Mid. - // CHANGE_FOR_ERLANG we have different case here, so we have to add the ".0" here - // we use memset as we do not have access to fill_n - memset(__result + __olength, '0', (size_t) _Ryu_exponent); - __result[__olength + (size_t) _Ryu_exponent] = '.'; - __result[__olength + (size_t) _Ryu_exponent + 1] = '0'; - } else if (_Ryu_exponent == 0) { // case "1729.0" - // CHANGE_FOR_ERLANG we have different case here, so we have to add the ".0" here - __result[__olength] = '.'; - __result[__olength + 1] = '0'; - } else if (_Whole_digits > 0) { // case "17.29" - // Performance note: moving digits might not be optimal. - memmove(__result, __result + 1, (size_t) _Whole_digits); - __result[_Whole_digits] = '.'; - } else { // case "0.001729" - // CHANGE_FOR_ERLANG we use the memset here as we do not have access to fill_n - // Performance note: a larger memset() followed by overwriting '.' might be more efficient. - __result[0] = '0'; - __result[1] = '.'; - memset(__result + 2, '0', (size_t) (-_Whole_digits)); - } - - // CHANGE_FOR_ERLANG we do not need the errc and we are only interested in - // returning the length, as it is what Ryu and erlang expect. We do add the - // sign as we did it here instead of adding it by default as in the STL - return _Total_fixed_length + sign; - } - - uint32_t _Scientific_exponent_length; - // CHANGE_FOR_ERLANG we have to do a little bit more complex logic here because we do not always - // print the exponent sign, only if it is negative - if (_Scientific_exponent <= -100) { // "e-100" - _Scientific_exponent_length = 5; - } else if (_Scientific_exponent <= -10 || _Scientific_exponent >= 100) { // "e-10" or "e100" - _Scientific_exponent_length = 4; - } else if ((_Scientific_exponent > -10 && _Scientific_exponent < 0) || _Scientific_exponent >= 10) { // "e-9" or "e10" - _Scientific_exponent_length = 3; - } else { // "e1" - _Scientific_exponent_length = 2; - } - - // CHANGE_FOR_ERLANG we do not need the ternary as we did all the logic above - const uint32_t _Total_scientific_length = __olength + 1 +(__olength == 1) // digits + decimal point + possible 0 after decimal point - + _Scientific_exponent_length; // + scientific exponent - - // Print the decimal digits. - uint32_t __i = 0; - // We prefer 32-bit operations, even on 64-bit platforms. - // We have at most 17 digits, and uint32_t can store 9 digits. - // If __output doesn't fit into uint32_t, we cut off 8 digits, - // so the rest will fit into uint32_t. - // CHANGE_FOR_ERLANG we consider in this whole thing that memcopy use the same - // char has defined in the DIGIT_TABLE - // CHANGE_FOR_ERLANG __DIGIT_TABLE became DIGIT_TABLE - if ((__output >> 32) != 0) { - // Expensive 64-bit division. - const uint64_t __q = div1e8(__output); - uint32_t __output2 = (uint32_t) (__output) - 100000000 * (uint32_t) (__q); - __output = __q; - - const uint32_t __c = __output2 % 10000; - __output2 /= 10000; - const uint32_t __d = __output2 % 10000; - const uint32_t __c0 = (__c % 100) << 1; - const uint32_t __c1 = (__c / 100) << 1; - const uint32_t __d0 = (__d % 100) << 1; - const uint32_t __d1 = (__d / 100) << 1; - memcpy(__result + __olength - __i - 1, DIGIT_TABLE + __c0, 2); - memcpy(__result + __olength - __i - 3, DIGIT_TABLE + __c1, 2); - memcpy(__result + __olength - __i - 5, DIGIT_TABLE + __d0, 2); - memcpy(__result + __olength - __i - 7, DIGIT_TABLE + __d1, 2); - __i += 8; - } - uint32_t __output2 = (uint32_t) (__output); - while (__output2 >= 10000) { -#ifdef __clang__ // TRANSITION, LLVM-38217 - const uint32_t __c = __output2 - 10000 * (__output2 / 10000); -#else - const uint32_t __c = __output2 % 10000; -#endif - __output2 /= 10000; - const uint32_t __c0 = (__c % 100) << 1; - const uint32_t __c1 = (__c / 100) << 1; - memcpy(__result + __olength - __i - 1, DIGIT_TABLE + __c0, 2); - memcpy(__result + __olength - __i - 3, DIGIT_TABLE + __c1, 2); - __i += 4; - } - if (__output2 >= 100) { - const uint32_t __c = (__output2 % 100) << 1; - __output2 /= 100; - memcpy(__result + __olength - __i - 1, DIGIT_TABLE + __c, 2); - __i += 2; - } - if (__output2 >= 10) { - const uint32_t __c = __output2 << 1; - // We can't use memcpy here: the decimal dot goes between these two digits. - __result[2] = DIGIT_TABLE[__c + 1]; - __result[0] = DIGIT_TABLE[__c]; - } else { - __result[0] = (char) ('0' + __output2); - } - - // Print decimal point if needed. - uint32_t __index; - if (__olength > 1) { - __result[1] = '.'; - __index = __olength + 1; - } else { - // In erlang we _have_ to print the ".0" in the case this is an integer - __result[1] = '.'; - __result[2] = '0'; - __index = __olength + 2; - } - - // Print the exponent. - __result[__index++] = 'e'; - if (_Scientific_exponent < 0) { - __result[__index++] = '-'; - _Scientific_exponent = -_Scientific_exponent; - } - // CHANGE_FOR_ERLANG no else, as we do not print the positive sign on the exponent - - if (_Scientific_exponent >= 100) { - const int32_t __c = _Scientific_exponent % 10; - memcpy(__result + __index, DIGIT_TABLE + 2 * (_Scientific_exponent / 10), 2); - __result[__index + 2] = (char) ('0' + __c); - __index += 3; - } else if (_Scientific_exponent >= 10) { - // CHANGE_FOR_ERLANG we have to do this only if the exponent is larger than 10 - memcpy(__result + __index, DIGIT_TABLE + 2 * _Scientific_exponent, 2); - __index += 2; - } else { - // CHANGE_FOR_ERLANG we can have an exponent under 10, which is not handled by the table - // so we handle it here - __result[__index++] = (char) ('0' + _Scientific_exponent); - } - - // CHANGE_FOR_ERLANG we do not need the errc and we are only interested in - // returning the length, as it is what Ryu and erlang expect. We do add the - // sign as we did it here instead of adding it by default as in the STL - return _Total_scientific_length + sign; -} -// end of STL code, back to ryu -// SPDX-SnippetEnd - - static inline bool d2d_small_int(const uint64_t ieeeMantissa, const uint32_t ieeeExponent, floating_decimal_64* const v) { const uint64_t m2 = (1ull << DOUBLE_MANTISSA_BITS) | ieeeMantissa; diff --git a/erts/emulator/ryu/d2s_intrinsics.h b/erts/emulator/ryu/d2s_intrinsics.h index 77388b308821..3d53ed3b3b81 100644 --- a/erts/emulator/ryu/d2s_intrinsics.h +++ b/erts/emulator/ryu/d2s_intrinsics.h @@ -189,15 +189,14 @@ static inline uint32_t mod1e9(const uint64_t x) { #endif // defined(RYU_32_BIT_PLATFORM) static inline uint32_t pow5Factor(uint64_t value) { + const uint64_t m_inv_5 = 14757395258967641293u; // 5 * m_inv_5 = 1 (mod 2^64) + const uint64_t n_div_5 = 3689348814741910323u; // #{ n | n = 0 (mod 2^64) } = 2^64 / 5 uint32_t count = 0; for (;;) { assert(value != 0); - const uint64_t q = div5(value); - const uint32_t r = ((uint32_t) value) - 5 * ((uint32_t) q); - if (r != 0) { + value *= m_inv_5; + if (value > n_div_5) break; - } - value = q; ++count; } return count; diff --git a/erts/emulator/ryu/to_chars.h b/erts/emulator/ryu/to_chars.h new file mode 100644 index 000000000000..1d41d3ea9883 --- /dev/null +++ b/erts/emulator/ryu/to_chars.h @@ -0,0 +1,340 @@ +// SPDX-CopyrightText: Copyright (c) Microsoft Corporation. +// SPDX-CopyrightText: Copyright 2018 Ulf Adams +// SPDX-License-Identifier: Apache-2.0 WITH LLVM-exception AND BSL-1.0 +//h +// The license information in the original file is not super clear. +// Microsoft seems to have changed it from Apache-2.0 to Apache-2.0 WITH LLVM-exception +// which they most likely are not allowed to do as the LLVM exception is less +// restrictive than Apache-2.0 plain. There is not much we can do about that +// though so we use their license. +// +// Library: STL +// Git repository: https://github.com/microsoft/STL +// Commit: e745bad3b1d05b5b19ec652d68abb37865ffa454 +// Original function: https://github.com/microsoft/STL/blob/e745bad3b1d05b5b19ec652d68abb37865ffa454/stl/inc/xcharconv_ryu.h#L1926 + +//CHANGE_FOR_ERLANG: This format is new, it is here to handle the different format switch used in the STL code +enum chars_format { + FMT_SCIENTIFIC, + FMT_FIXED, + FMT_GENERAL +}; + +// This is inspired from the MS STL Charconv, under Apache with LLVM exception licence +// see https://github.com/microsoft/STL/blob/main/LICENSE.txt +// The inspiration is at https://github.com/microsoft/STL/blob/e745bad3b1d05b5b19ec652d68abb37865ffa454/stl/inc/xcharconv_ryu.h#L1926 +// CHANGE_FOR_ERLANG all the types and typecast have been adapted to C types from Cpp. +// I have also kept the Ryu original function head as it allows to not impact the rest of the code +// __v and __mantissa and __exponent have lost their double underscore over the whole function +// all the test on the lenght of the buffer have been dropped too. This could need change, but +// we always pass a 256 bytes buffer when we only need 26 bytes maximum. +static inline int to_chars(const floating_decimal_64 v, const bool sign, char* const result) { + // Step 5: Print the decimal representation. + uint64_t __output = v.mantissa; + int32_t _Ryu_exponent = v.exponent; + const uint32_t __olength = decimalLength17(__output); + int32_t _Scientific_exponent = _Ryu_exponent + ((int32_t) __olength) - 1; + + // CHANGE_FOR_ERLANG: we use our chars_format instead of the STL one + enum chars_format _Fmt; + + int32_t _Lower; + int32_t _Upper; + + if (__olength == 1) { + // CHANGE_FOR_ERLANG the format and examples have been adapted to the erlang format + // as the original would have not shown a change in format + // (erlang always add ".0" to scientific format) and omit the + in the exponent + // Value | Fixed | Scientific + // 1e-4 | "0.0001" | "1.0e-4" + // 1e2 | "100.0" | "1.0e2" + // CHANGE_FOR_ERLANG the values for a switch, as seen in the example above, for erlang + // are different than for STL format. + _Lower = -4; + _Upper = 2; + } else if (_Scientific_exponent >= 10) { + // CHANGE_FOR_ERLANG This case does not exist for the STL and is due to the + // negative sign in the exponent. + // Value | Fixed | Scientific + // 123456789e1 | "1234567890.0" | "1.23456789e9" + // 123456789e2 | "12345678900.0" | "1.23456789e10" + + _Lower = - (int32_t) (__olength + 2); + _Upper = 2; + } else { + // CHANGE_FOR_ERLANG the format and examples have been adapted to the erlang format + // as the original would have not shown a change in format + // (erlang always add ".0" to scientific format) and omit the + in the exponent + // Value | Fixed | Scientific + // 1234e-6 | "0.001234" | "1.234e-4" + // 1234e1 | "12340.0" | "1.234e4" + // CHANGE_FOR_ERLANG the values for a switch, as seen in the example above, for erlang + // are different than for STL format. + _Lower = - (int32_t) (__olength + 2); + _Upper = 1; + } + + if (_Lower <= _Ryu_exponent && _Ryu_exponent <= _Upper) { + // CHANGE_FOR_ERLANG this is added to handle the -2**53, 2**53 range special case + // These are edge cases not captured above, all the other are naturally handled + // by _Lower nad _Upper + if ((__output >= (1ull << 53) && _Ryu_exponent == 0) + || (__output > ((1ull << 52) / 5) && _Ryu_exponent == 1) + || (__output > ((1ull << 51) / 25) && _Ryu_exponent == 2)) { + _Fmt = FMT_SCIENTIFIC; + } else { + _Fmt = FMT_FIXED; + } + } else { + // CHANGE_FOR_ERLANG we do not need to handle the %g case here. + _Fmt = FMT_SCIENTIFIC; + } + + // CHANGE_FOR_ERLANG we handle the sign here as it is handled outside of this in the STL case + // and we need it to compute the start of the buffer for the characters after + if (sign) { + result[0] = '-'; + } + + // CHANGE_FOR_ERLANG we compute the start of the usable buffer. It is done here + // in order to be fixed for both branches of formatting. + char* const __result = result + sign; + + if (_Fmt == FMT_FIXED) { + // CHANGE_FOR_ERLANG this whole table has been adapted to erlang examples to help + // debug and evolve the edge cases + // Example: __output == 1729, __olength == 4 + + // _Ryu_exponent | Printed | _Whole_digits | _Total_fixed_length | Notes + // --------------|----------|---------------|----------------------|--------------------------------------- + // 1 | 17290.0 | 5 | _Whole_digits + 2 | Unified length cases. + // 0 | 1729.0 | 4 | | + // --------------|----------|---------------|----------------------|--------------------------------------- + // -1 | 172.9 | 3 | __olength + 1 | This case can't happen for + // -2 | 17.29 | 2 | | __olength == 1, but no additional + // -3 | 1.729 | 1 | | code is needed to avoid it. + // --------------|----------|---------------|----------------------|--------------------------------------- + // -4 | 0.1729 | 0 | 2 - _Ryu_exponent | If the decimal point appears, we need + // -5 | 0.01729 | -1 | | to put the "0" in front + // -6 | 0.001729 | -2 | | + + const int32_t _Whole_digits = (int32_t) (__olength) + _Ryu_exponent; + + uint32_t _Total_fixed_length; + if (_Ryu_exponent >= 0) { + // CHANGE_FOR_ERLANG the examples and values have been adapted to erlang format one + // CHANGE_FOR_ERLANG we also dropped the whole adjustement, as it is only of value + // for %f which we do not handle + // cases "17290.0" and "1729.0" + _Total_fixed_length = (uint32_t) (_Whole_digits) + 2; + } else if (_Whole_digits > 0) { // case "17.29" + _Total_fixed_length = __olength + 1; + } else { // case "0.001729" + _Total_fixed_length = (uint32_t) (2 - _Ryu_exponent); + } + + char* _Mid; + if (_Ryu_exponent >= 0) { // case "172900.0" + // CHANGE_FOR_ERLANG we do not need the can_use_ryu, as we are not doing %f + // but always shortest round_trip. The whole complexity here is dropped + // Print the decimal digits, left-aligned within [result, result + _Total_fixed_length). + _Mid = __result + __olength; + } else { // cases "1729.0", "17.29", and "0.001729" + // Print the decimal digits, right-aligned within [result, result + _Total_fixed_length). + _Mid = __result + _Total_fixed_length; + } + + // We prefer 32-bit operations, even on 64-bit platforms. + // We have at most 17 digits, and uint32_t can store 9 digits. + // If __output doesn't fit into uint32_t, we cut off 8 digits, + // so the rest will fit into uint32_t. + // CHANGE_FOR_ERLANG we consider in this whole thing that memcopy use the same + // char has defined in the DIGIT_TABLE + // CHANGE_FOR_ERLANG __DIGIT_TABLE became DIGIT_TABLE + if ((__output >> 32) != 0) { + // Expensive 64-bit division. + const uint64_t __q = div1e8(__output); + uint32_t __output2 = (uint32_t) (__output - 100000000 * __q); + __output = __q; + + const uint32_t __c = __output2 % 10000; + __output2 /= 10000; + const uint32_t __d = __output2 % 10000; + const uint32_t __c0 = (__c % 100) << 1; + const uint32_t __c1 = (__c / 100) << 1; + const uint32_t __d0 = (__d % 100) << 1; + const uint32_t __d1 = (__d / 100) << 1; + + memcpy(_Mid -= 2, DIGIT_TABLE + __c0, 2); + memcpy(_Mid -= 2, DIGIT_TABLE + __c1, 2); + memcpy(_Mid -= 2, DIGIT_TABLE + __d0, 2); + memcpy(_Mid -= 2, DIGIT_TABLE + __d1, 2); + } + uint32_t __output2 = (uint32_t) __output; + while (__output2 >= 10000) { +#ifdef __clang__ // TRANSITION, LLVM-38217 + const uint32_t __c = __output2 - 10000 * (__output2 / 10000); +#else + const uint32_t __c = __output2 % 10000; +#endif + __output2 /= 10000; + const uint32_t __c0 = (__c % 100) << 1; + const uint32_t __c1 = (__c / 100) << 1; + memcpy(_Mid -= 2, DIGIT_TABLE + __c0, 2); + memcpy(_Mid -= 2, DIGIT_TABLE + __c1, 2); + } + if (__output2 >= 100) { + const uint32_t __c = (__output2 % 100) << 1; + __output2 /= 100; + memcpy(_Mid -= 2, DIGIT_TABLE + __c, 2); + } + if (__output2 >= 10) { + const uint32_t __c = __output2 << 1; + memcpy(_Mid -= 2, DIGIT_TABLE + __c, 2); + } else { + *--_Mid = (char) ('0' + __output2); + } + + if (_Ryu_exponent > 0) { // case "172900.0" + // Performance note: it might be more efficient to do this immediately after setting _Mid. + // CHANGE_FOR_ERLANG we have different case here, so we have to add the ".0" here + // we use memset as we do not have access to fill_n + memset(__result + __olength, '0', (size_t) _Ryu_exponent); + __result[__olength + (size_t) _Ryu_exponent] = '.'; + __result[__olength + (size_t) _Ryu_exponent + 1] = '0'; + } else if (_Ryu_exponent == 0) { // case "1729.0" + // CHANGE_FOR_ERLANG we have different case here, so we have to add the ".0" here + __result[__olength] = '.'; + __result[__olength + 1] = '0'; + } else if (_Whole_digits > 0) { // case "17.29" + // Performance note: moving digits might not be optimal. + memmove(__result, __result + 1, (size_t) _Whole_digits); + __result[_Whole_digits] = '.'; + } else { // case "0.001729" + // CHANGE_FOR_ERLANG we use the memset here as we do not have access to fill_n + // Performance note: a larger memset() followed by overwriting '.' might be more efficient. + __result[0] = '0'; + __result[1] = '.'; + memset(__result + 2, '0', (size_t) (-_Whole_digits)); + } + + // CHANGE_FOR_ERLANG we do not need the errc and we are only interested in + // returning the length, as it is what Ryu and erlang expect. We do add the + // sign as we did it here instead of adding it by default as in the STL + return _Total_fixed_length + sign; + } + + uint32_t _Scientific_exponent_length; + // CHANGE_FOR_ERLANG we have to do a little bit more complex logic here because we do not always + // print the exponent sign, only if it is negative + if (_Scientific_exponent <= -100) { // "e-100" + _Scientific_exponent_length = 5; + } else if (_Scientific_exponent <= -10 || _Scientific_exponent >= 100) { // "e-10" or "e100" + _Scientific_exponent_length = 4; + } else if ((_Scientific_exponent > -10 && _Scientific_exponent < 0) || _Scientific_exponent >= 10) { // "e-9" or "e10" + _Scientific_exponent_length = 3; + } else { // "e1" + _Scientific_exponent_length = 2; + } + + // CHANGE_FOR_ERLANG we do not need the ternary as we did all the logic above + const uint32_t _Total_scientific_length = __olength + 1 +(__olength == 1) // digits + decimal point + possible 0 after decimal point + + _Scientific_exponent_length; // + scientific exponent + + // Print the decimal digits. + uint32_t __i = 0; + // We prefer 32-bit operations, even on 64-bit platforms. + // We have at most 17 digits, and uint32_t can store 9 digits. + // If __output doesn't fit into uint32_t, we cut off 8 digits, + // so the rest will fit into uint32_t. + // CHANGE_FOR_ERLANG we consider in this whole thing that memcopy use the same + // char has defined in the DIGIT_TABLE + // CHANGE_FOR_ERLANG __DIGIT_TABLE became DIGIT_TABLE + if ((__output >> 32) != 0) { + // Expensive 64-bit division. + const uint64_t __q = div1e8(__output); + uint32_t __output2 = (uint32_t) (__output) - 100000000 * (uint32_t) (__q); + __output = __q; + + const uint32_t __c = __output2 % 10000; + __output2 /= 10000; + const uint32_t __d = __output2 % 10000; + const uint32_t __c0 = (__c % 100) << 1; + const uint32_t __c1 = (__c / 100) << 1; + const uint32_t __d0 = (__d % 100) << 1; + const uint32_t __d1 = (__d / 100) << 1; + memcpy(__result + __olength - __i - 1, DIGIT_TABLE + __c0, 2); + memcpy(__result + __olength - __i - 3, DIGIT_TABLE + __c1, 2); + memcpy(__result + __olength - __i - 5, DIGIT_TABLE + __d0, 2); + memcpy(__result + __olength - __i - 7, DIGIT_TABLE + __d1, 2); + __i += 8; + } + uint32_t __output2 = (uint32_t) (__output); + while (__output2 >= 10000) { +#ifdef __clang__ // TRANSITION, LLVM-38217 + const uint32_t __c = __output2 - 10000 * (__output2 / 10000); +#else + const uint32_t __c = __output2 % 10000; +#endif + __output2 /= 10000; + const uint32_t __c0 = (__c % 100) << 1; + const uint32_t __c1 = (__c / 100) << 1; + memcpy(__result + __olength - __i - 1, DIGIT_TABLE + __c0, 2); + memcpy(__result + __olength - __i - 3, DIGIT_TABLE + __c1, 2); + __i += 4; + } + if (__output2 >= 100) { + const uint32_t __c = (__output2 % 100) << 1; + __output2 /= 100; + memcpy(__result + __olength - __i - 1, DIGIT_TABLE + __c, 2); + __i += 2; + } + if (__output2 >= 10) { + const uint32_t __c = __output2 << 1; + // We can't use memcpy here: the decimal dot goes between these two digits. + __result[2] = DIGIT_TABLE[__c + 1]; + __result[0] = DIGIT_TABLE[__c]; + } else { + __result[0] = (char) ('0' + __output2); + } + + // Print decimal point if needed. + uint32_t __index; + if (__olength > 1) { + __result[1] = '.'; + __index = __olength + 1; + } else { + // In erlang we _have_ to print the ".0" in the case this is an integer + __result[1] = '.'; + __result[2] = '0'; + __index = __olength + 2; + } + + // Print the exponent. + __result[__index++] = 'e'; + if (_Scientific_exponent < 0) { + __result[__index++] = '-'; + _Scientific_exponent = -_Scientific_exponent; + } + // CHANGE_FOR_ERLANG no else, as we do not print the positive sign on the exponent + + if (_Scientific_exponent >= 100) { + const int32_t __c = _Scientific_exponent % 10; + memcpy(__result + __index, DIGIT_TABLE + 2 * (_Scientific_exponent / 10), 2); + __result[__index + 2] = (char) ('0' + __c); + __index += 3; + } else if (_Scientific_exponent >= 10) { + // CHANGE_FOR_ERLANG we have to do this only if the exponent is larger than 10 + memcpy(__result + __index, DIGIT_TABLE + 2 * _Scientific_exponent, 2); + __index += 2; + } else { + // CHANGE_FOR_ERLANG we can have an exponent under 10, which is not handled by the table + // so we handle it here + __result[__index++] = (char) ('0' + _Scientific_exponent); + } + + // CHANGE_FOR_ERLANG we do not need the errc and we are only interested in + // returning the length, as it is what Ryu and erlang expect. We do add the + // sign as we did it here instead of adding it by default as in the STL + return _Total_scientific_length + sign; +} diff --git a/erts/emulator/ryu/update.sh b/erts/emulator/ryu/update.sh new file mode 100755 index 000000000000..cceb97c506bb --- /dev/null +++ b/erts/emulator/ryu/update.sh @@ -0,0 +1,105 @@ +#!/bin/bash +# +# %CopyrightBegin% +# +# SPDX-License-Identifier: Apache-2.0 +# +# Copyright Ericsson AB 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% + +ORIGIN_REPO="https://github.com/erlang/ryu" +UPSTREAM_REPO="https://github.com/ulfjack/ryu" + +cd $ERL_TOP/erts/emulator/ryu + +set -exo pipefail + +## Clone reference +git clone ${ORIGIN_REPO} ryu-copy + +## into ryu-copy +cd ryu-copy +git remote add upstream ${UPSTREAM_REPO} +git fetch upstream + +SHA=$(git rev-parse --verify upstream/master) +SHORT_SHA=$(git rev-parse --verify --short upstream/master) + +if ! git merge upstream/master; then + git status --short | grep "^D" | awk '{print $2}' | xargs git rm -rf + git status --short | grep "^A" | awk '{print $2}' | xargs git rm -rf + if ! git commit; then + cat < ${ERL_TOP}/erts/emulator/ryu/xcharconv_ryu.h.sha + +EOF + +fi + +## Remove old files +shopt -s extglob +git rm -rf $(ls -d !(update.sh|vendor.info|ryu.mk|obj|README.ryu_update.md|ryu-copy|STL|xcharconv_ryu.h.sha)) +shopt -u extglob + +cp -r ryu-copy/* . +rm -rf ryu-copy STL + +## Update vendor info +COMMENTS=$(cat vendor.info | grep "^//") +NEW_VENDOR_INFO=$(cat vendor.info | grep -v "^//" | jq "map(if .ID == \"erts-ryu\" then .versionInfo = \"${SHA}\" | .sha = \"${SHA}\" else . end)") +NEW_VENDOR_INFO=$(echo "${NEW_VENDOR_INFO}" | jq "map(if .ID == \"erts-ryu-to_chars\" then .versionInfo = \"${STL_VSN}\" | .sha = \"${STL_SHA}\" else . end)") + +cat < vendor.info +${COMMENTS} +${NEW_VENDOR_INFO} +EOF + +git add . + +git commit -m "erts: Update ryu version to ${SHA}" \ No newline at end of file diff --git a/erts/emulator/ryu/vendor.info b/erts/emulator/ryu/vendor.info index dcd4a2e535e1..372863235c9f 100644 --- a/erts/emulator/ryu/vendor.info +++ b/erts/emulator/ryu/vendor.info @@ -1,20 +1,52 @@ -%% %CopyrightBegin% -%% -%% SPDX-License-Identifier: Apache-2.0 -%% -%% Copyright Ericsson AB 2025. All Rights Reserved. -%% -%% %CopyrightEnd% -{ - "ID": "erts-ryu", - "description": "ryu library", - "copyrightText": "Copyright 2018 Ulf Adams", - "downloadLocation": "https://github.com/ulfjack/ryu", - "homepage": "https://github.com/ulfjack/ryu", - "licenseDeclared": "Apache-2.0 OR BSL-1.0", - "name": "ryu", - "versionInfo": "844864ac213bdbf1fb57e6f51c653b3d90af0937", - "path": "./erts/emulator/ryu", - "supplier": "Person: Ulf Adams", - "purl": "pkg:github/ulfjack/ryu" -} +// %CopyrightBegin% +// +// SPDX-License-Identifier: Apache-2.0 +// +// Copyright Ericsson AB 2025. All Rights Reserved. +// +// %CopyrightEnd% +[ + { + "ID": "erts-ryu", + "description": "ryu library", + "copyrightText": "Copyright 2018 Ulf Adams", + "downloadLocation": "https://github.com/ulfjack/ryu", + "homepage": "https://github.com/ulfjack/ryu", + "licenseDeclared": "Apache-2.0", + "name": "ryu", + "versionInfo": "1264a946ba66eab320e927bfd2362e0c8580c42f", + "path": ["./erts/emulator/ryu/common.h", + "./erts/emulator/ryu/d2s.c", + "./erts/emulator/ryu/d2s_full_table.h", + "./erts/emulator/ryu/d2s_intrinsics.h", + "./erts/emulator/ryu/digit_table.h", + "./erts/emulator/ryu/ryu.h", + "./erts/emulator/ryu/ryu.mk", + "./erts/emulator/ryu/README.md", + "./erts/emulator/ryu/LICENSE-Apache2", + "./erts/emulator/ryu/LICENSE-Boost" + ], + "supplier": "Person: Ulf Adams", + "purl": "pkg:github/ulfjack/ryu#ryu", + "update": "./erts/emulator/ryu/update.sh", + "sha": "1264a946ba66eab320e927bfd2362e0c8580c42f" + }, + { + "ID": "ryu-to_chars", + "description": "to_chars from STL ryu", + "copyrightText": "Copyright 2018 Ulf Adams\nCopyright (c) Microsoft Corporation.", + "downloadLocation": "https://github.com/microsoft/STL", + "homepage": "https://github.com/microsoft/STL", + "licenseDeclared": "Apache-2.0 WITH LLVM-exception AND BSL-1.0", + "name": "ryu_to_chars", + "versionInfo": "vs-2022-17.13", + "path": [ + "./erts/emulator/ryu/to_chars.h", + "./erts/emulator/ryu/xcharconv_ryu.h.sha" + ], + "supplier": "Organization: Microsoft Corporation", + "purl": "pkg:github/microsoft/STL#stl/inc/xcharconv_ryu.h", + "update": "./erts/emulator/ryu/update.sh", + "sha": "442029c6fa37f1b6f9203357de09672d5704077c" + } +] diff --git a/erts/emulator/ryu/xcharconv_ryu.h.sha b/erts/emulator/ryu/xcharconv_ryu.h.sha new file mode 100644 index 000000000000..a3c589e489f7 --- /dev/null +++ b/erts/emulator/ryu/xcharconv_ryu.h.sha @@ -0,0 +1 @@ +c12089e489c7b6a3896f5043ed545ac8d1870590 diff --git a/erts/emulator/zlib/vendor.info b/erts/emulator/zlib/vendor.info index 8e9474a75b91..4c78ed4dd788 100644 --- a/erts/emulator/zlib/vendor.info +++ b/erts/emulator/zlib/vendor.info @@ -1,20 +1,22 @@ -%% %CopyrightBegin% -%% -%% SPDX-License-Identifier: Apache-2.0 -%% -%% Copyright Ericsson AB 2025. All Rights Reserved. -%% -%% %CopyrightEnd% -{ - "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/", - "homepage": "https://zlib.net/", - "licenseDeclared": "Zlib", - "name": "zlib", - "versionInfo": "1.3.1", - "path": "./erts/emulator/zlib", - "supplier": "Person: Mark Adler (zlib@gzip.org)", - "purl": "pkg:generic/zlib" -} +// %CopyrightBegin% +// +// SPDX-License-Identifier: Apache-2.0 +// +// Copyright Ericsson AB 2025. All Rights Reserved. +// +// %CopyrightEnd% +[ + { + "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/", + "homepage": "https://zlib.net/", + "licenseDeclared": "Zlib", + "name": "zlib", + "versionInfo": "1.3.1", + "path": "./erts/emulator/zlib", + "supplier": "Person: Mark Adler (zlib@gzip.org)", + "purl": "pkg:generic/zlib" + } +] diff --git a/erts/emulator/zstd/update.sh b/erts/emulator/zstd/update.sh index 79d3a5772ab2..faa935cf6947 100755 --- a/erts/emulator/zstd/update.sh +++ b/erts/emulator/zstd/update.sh @@ -22,20 +22,21 @@ cd $ERL_TOP/erts/emulator/zstd +set -eo pipefail + +## Remove old files +shopt -s extglob +git rm -rf $(ls -d !(update.sh|vendor.info|zstd.mk|obj)) +shopt -u extglob + ## Fetch latest version of zstd from github VSN=$(curl -sL -H "Authorization: Bearer $(cat ~/.githubtoken)" -H "Accept: application/vnd.github+json" -H "X-GitHub-Api-Version: 2022-11-28" https://api.github.com/repos/facebook/zstd/releases/latest | jq ".tag_name" | sed 's/"//g') ## Clone it -git clone git@github.com:facebook/zstd -b $VSN zstd-copy +git clone https://github.com/facebook/zstd -b $VSN zstd-copy ## Save sha version for book keeping SHA=$(cd zstd-copy && git rev-parse --verify HEAD) -echo "// SPDX-License-Identifier: Apache-2.0 -// SPDX-FileCopyrightText: 2025 Ericsson and the Erlang/OTP contributors -${SHA}" > zstd.version - -## Remove old files -rm -rf common compress decompress ezstd.h LICENSE ## Copy new files cp -r zstd-copy/lib/{common,compress,decompress} ./ @@ -52,27 +53,16 @@ done rm -rf zstd-copy -git add common compress decompress ./erl_*.h COPYING LICENSE zstd.version - -LICENSE=$(cat LICENSE) -COPYING=$(cat COPYING) -read -r -d '' SYSTEM_COPYRIGHT << EOM -[zstd] - -* Info: - * SPDX-License-Identifier: BSD-3-Clause OR GPL-2.0-only - * Tool: zstd - * Git Repository: https://github.com/facebook/zstd - * Version: ${VSN} - * Commit: ${SHA} - * OTP Location: ./erts/emulator/zstd - -${LICENSE} +## Update vendor info +COMMENTS=$(cat vendor.info | grep "^//") +NEW_VENDOR_INFO=$(cat vendor.info | grep -v "^//" | jq "map(if .ID == \"erts-zstd\" then .versionInfo = \"${VSN}\" | .sha = \"${SHA}\" else . end)") -${COPYING} +cat < vendor.info +${COMMENTS} +${NEW_VENDOR_INFO} +EOF -EOM -SYSTEM_COPYRIGHT=$(echo "${SYSTEM_COPYRIGHT}" | sed 's@/@\\/@g') +## Add and commit everything +git add common compress decompress ./erl_*.h COPYING LICENSE vendor.info -perl -0777 -i -pe 's/\[zstd\](.|\n)*(\n------*)/'"${SYSTEM_COPYRIGHT}"'\n$2/is' \ - "$ERL_TOP/system/COPYRIGHT" +git commit -m "erts: Update zstd version to ${VSN}" \ No newline at end of file diff --git a/erts/emulator/zstd/vendor.info b/erts/emulator/zstd/vendor.info index 7c0a2ba7a378..41101c977e4c 100644 --- a/erts/emulator/zstd/vendor.info +++ b/erts/emulator/zstd/vendor.info @@ -1,21 +1,24 @@ -%% %CopyrightBegin% -%% -%% SPDX-License-Identifier: Apache-2.0 -%% -%% Copyright Ericsson AB 2025. All Rights Reserved. -%% -%% %CopyrightEnd% -{ - "ID": "erts-zstd", - "description": "zstd", - "copyrightText": "Copyright (c) Meta Platforms, Inc. and affiliates. All rights reserved.", - "downloadLocation": "https://github.com/facebook/zstd", - "homepage": "https://github.com/facebook/zstd", - "license": "BSD-3-Clause OR GPL-2.0-only", - "licenseDeclared": "BSD-3-Clause OR GPL-2.0-only", - "name": "zstd", - "versionInfo": "v1.5.7", - "path": "./erts/emulator/zstd", - "supplier": "Organization: Meta", - "purl": "pkg:github/facebook/zstd" -} +// %CopyrightBegin% +// +// SPDX-License-Identifier: Apache-2.0 +// +// Copyright Ericsson AB 2025. All Rights Reserved. +// +// %CopyrightEnd% +[ + { + "ID": "erts-zstd", + "description": "zstd", + "copyrightText": "Copyright (c) Meta Platforms, Inc. and affiliates. All rights reserved.", + "downloadLocation": "https://github.com/facebook/zstd", + "homepage": "https://github.com/facebook/zstd", + "license": "BSD-3-Clause OR GPL-2.0-only", + "licenseDeclared": "BSD-3-Clause OR GPL-2.0-only", + "name": "zstd", + "versionInfo": "v1.5.7", + "path": "./erts/emulator/zstd", + "supplier": "Organization: Meta", + "purl": "pkg:github/facebook/zstd", + "update": "./erts/emulator/zstd/update.sh" + } +] diff --git a/lib/common_test/priv/vendor.info b/lib/common_test/priv/vendor.info index 9f636237fe53..2526eed77092 100644 --- a/lib/common_test/priv/vendor.info +++ b/lib/common_test/priv/vendor.info @@ -1,10 +1,10 @@ -%% %CopyrightBegin% -%% -%% SPDX-License-Identifier: Apache-2.0 -%% -%% Copyright Ericsson AB 2025. All Rights Reserved. -%% -%% %CopyrightEnd% +// %CopyrightBegin% +// +// SPDX-License-Identifier: Apache-2.0 +// +// Copyright Ericsson AB 2025. All Rights Reserved. +// +// %CopyrightEnd% [ { "ID": "common_test-jquery", @@ -15,7 +15,7 @@ "licenseDeclared": "MIT", "name": "jquery", "versionInfo": "3.7.1", - "path": "./lib/common_test/priv/jquery-latest.js", + "path": ["./lib/common_test/priv/jquery-latest.js"], "supplier": "Organization: The jQuery Team", "purl": "pkg:github/jquery/jquery" }, @@ -28,7 +28,7 @@ "licenseDeclared": "BSD-3-Clause OR GPL-2.0-only", "name": "jquery-tablesorter", "versionInfo": "2.32", - "path": "./lib/common_test/priv/jquery.tablesorter.min.js", + "path": ["./lib/common_test/priv/jquery.tablesorter.min.js"], "supplier": "Person: Christian Bach", "purl": "pkg:github/mottie/tablesorter" } diff --git a/lib/common_test/test_server/vendor.info b/lib/common_test/test_server/vendor.info index 852adfd75da8..ae498455b334 100644 --- a/lib/common_test/test_server/vendor.info +++ b/lib/common_test/test_server/vendor.info @@ -1,10 +1,10 @@ -%% %CopyrightBegin% -%% -%% SPDX-License-Identifier: Apache-2.0 -%% -%% Copyright Ericsson AB 2025. All Rights Reserved. -%% -%% %CopyrightEnd% +// %CopyrightBegin% +// +// SPDX-License-Identifier: Apache-2.0 +// +// Copyright Ericsson AB 2025. All Rights Reserved. +// +// %CopyrightEnd% [ { "ID": "common_test-config", @@ -28,7 +28,7 @@ "licenseDeclared": "MIT", "name": "Autoconf", "versionInfo": "2.71", - "path": "./lib/common_test/test_server/install-sh", + "path": ["./lib/common_test/test_server/install-sh"], "supplier": "Organization: Free Software Foundation", "purl": "pkg:generic/autoconf" } diff --git a/lib/erl_interface/src/openssl/vendor.info b/lib/erl_interface/src/openssl/vendor.info index cabd64afc120..f288b30a49cb 100644 --- a/lib/erl_interface/src/openssl/vendor.info +++ b/lib/erl_interface/src/openssl/vendor.info @@ -1,20 +1,22 @@ -%% %CopyrightBegin% -%% -%% SPDX-License-Identifier: Apache-2.0 -%% -%% Copyright Ericsson AB 2025. All Rights Reserved. -%% -%% %CopyrightEnd% -{ - "ID": "erl_interface-openssl", - "description": "Openssl MD5 implementation in erl_interface", - "copyrightText": "Copyright 1995-2022 The OpenSSL Project Authors. All Rights Reserved.", - "downloadLocation": "https://github.com/openssl/openssl", - "homepage": "https://www.openssl.org/", - "licenseDeclared": "Apache-2.0", - "name": "openssl", - "versionInfo": "3.1.4", - "path": "./lib/erl_interface/src/openssl", - "supplier": "Organization: OpenSSL Mission", - "purl": "pkg:generic/openssl" -} +// %CopyrightBegin% +// +// SPDX-License-Identifier: Apache-2.0 +// +// Copyright Ericsson AB 2025. All Rights Reserved. +// +// %CopyrightEnd% +[ + { + "ID": "erl_interface-openssl", + "description": "Openssl MD5 implementation in erl_interface", + "copyrightText": "Copyright 1995-2022 The OpenSSL Project Authors. All Rights Reserved.", + "downloadLocation": "https://github.com/openssl/openssl", + "homepage": "https://www.openssl.org/", + "licenseDeclared": "Apache-2.0", + "name": "openssl", + "versionInfo": "3.1.4", + "path": "./lib/erl_interface/src/openssl", + "supplier": "Organization: OpenSSL Mission", + "purl": "pkg:generic/openssl" + } +] diff --git a/lib/kernel/internal_doc/distribution_handshake.txt b/lib/kernel/internal_doc/distribution_handshake.txt deleted file mode 100644 index d00c4ceb022a..000000000000 --- a/lib/kernel/internal_doc/distribution_handshake.txt +++ /dev/null @@ -1 +0,0 @@ -This information has been moved to the "Distribution Protocol" chapter of "ERTS User's Guide". diff --git a/lib/observer/priv/erlang_observer.png.license b/lib/observer/priv/erlang_observer.png.license index f358620e4037..8ca64c7f91ca 100644 --- a/lib/observer/priv/erlang_observer.png.license +++ b/lib/observer/priv/erlang_observer.png.license @@ -1,2 +1,7 @@ +%CopyrightBegin% + SPDX-License-Identifier: Apache-2.0 -Copyright 2011-2013 Ericsson AB. All rights reserved. + +Copyright Ericsson AB 2011-2013. All Rights Reserved. + +%CopyrightEnd% diff --git a/lib/snmp/mibs/SNMP-USM-HMAC-SHA2-MIB.mib b/lib/snmp/mibs/SNMP-USM-HMAC-SHA2-MIB.mib index ed031ec4e226..fc651850d220 100644 --- a/lib/snmp/mibs/SNMP-USM-HMAC-SHA2-MIB.mib +++ b/lib/snmp/mibs/SNMP-USM-HMAC-SHA2-MIB.mib @@ -1,8 +1,34 @@ -- %CopyrightBegin% -- --- SPDX-License-Identifier: NOASSERTION +-- SPDX-License-Identifier: BSD-3-Clause -- -- Copyright (C) The Internet Society (2016). All Rights Reserved. +-- +-- Redistribution and use in source and binary forms, with or without +-- modification, are permitted provided that the following conditions are met: +-- +-- 1. Redistributions of source code must retain the above copyright notice, +-- this list of conditions and the following disclaimer. +-- +-- 2. Redistributions in binary form must reproduce the above copyright notice, +-- this list of conditions and the following disclaimer in the documentation +-- and/or other materials provided with the distribution. +-- +-- 3. Neither the name of the copyright holder nor the names of its contributors +-- may be used to endorse or promote products derived from this software +-- without specific prior written permission. +-- +-- THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS “AS IS” +-- AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE +-- IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE +-- ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT HOLDER OR CONTRIBUTORS BE +-- LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR +-- CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF +-- SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS +-- INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN +-- CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) +-- ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE +-- POSSIBILITY OF SUCH DAMAGE. -- -- %CopyrightEnd% diff --git a/lib/stdlib/test/json_SUITE_data/vendor.info b/lib/stdlib/test/json_SUITE_data/vendor.info index c186eed5b728..920638c27c9c 100644 --- a/lib/stdlib/test/json_SUITE_data/vendor.info +++ b/lib/stdlib/test/json_SUITE_data/vendor.info @@ -1,11 +1,11 @@ -%% %CopyrightBegin% -%% -%% SPDX-License-Identifier: Apache-2.0 -%% -%% Copyright Ericsson AB 2025. All Rights Reserved. -%% -%% %CopyrightEnd% -{ +// %CopyrightBegin% +// +// SPDX-License-Identifier: Apache-2.0 +// +// Copyright Ericsson AB 2025. All Rights Reserved. +// +// %CopyrightEnd% +[{ "ID": "stdlib-json-suite", "description": "JSON Test Suite", "copyrightText": "Copyright (c) 2016 Nicolas Seriot", @@ -17,4 +17,4 @@ "path": "./lib/stdlib/test/json_SUITE_data", "supplier": "Person: Nicolas Seriot", "purl": "pkg:github/nst/JSONTestSuite" -} +}] diff --git a/lib/stdlib/uc_spec/vendor.info b/lib/stdlib/uc_spec/vendor.info index a40cb7b8317a..8af69c800c43 100644 --- a/lib/stdlib/uc_spec/vendor.info +++ b/lib/stdlib/uc_spec/vendor.info @@ -1,32 +1,35 @@ -%% %CopyrightBegin% -%% -%% SPDX-License-Identifier: Apache-2.0 -%% -%% Copyright Ericsson AB 2025. All Rights Reserved. -%% -%% %CopyrightEnd% -{ - "ID": "stdlib-unicode", - "description": "Unicode Character Database used for generating code", - "copyrightText": "© 2024 Unicode®, Inc.", - "downloadLocation": "https://www.unicode.org/Public/16.0.0/ucd/", - "homepage": "https://www.unicode.org/", - "licenseDeclared": "Unicode-3.0", - "name": "Unicode Character Database", - "versionInfo": "16.0.0", - "path": ["./lib/stdlib/uc_spec/CaseFolding.txt", - "./lib/stdlib/uc_spec/CompositionExclusions.txt", - "./lib/stdlib/uc_spec/EastAsianWidth.txt", - "./lib/stdlib/uc_spec/emoji-data.txt", - "./lib/stdlib/uc_spec/GraphemeBreakProperty.txt", - "./lib/stdlib/uc_spec/IndicSyllabicCategory.txt", - "./lib/stdlib/uc_spec/PropList.txt", - "./lib/stdlib/uc_spec/SpecialCasing.txt", - "./lib/stdlib/uc_spec/UnicodeData.txt", - "./lib/stdlib/test/unicode_util_SUITE_data/GraphemeBreakTest.txt", - "./lib/stdlib/test/unicode_util_SUITE_data/LineBreakTest.txt", - "./lib/stdlib/test/unicode_util_SUITE_data/NormalizationTest.txt" - ], - "supplier": "Organization: Unicode, Inc", - "purl": "pkg:generic/unicode" -} +// %CopyrightBegin% +// +// SPDX-License-Identifier: Apache-2.0 +// +// Copyright Ericsson AB 2025. All Rights Reserved. +// +// %CopyrightEnd% +[ + { + "ID": "stdlib-unicode", + "description": "Unicode Character Database used for generating code", + "copyrightText": "© 2024 Unicode®, Inc.", + "downloadLocation": "https://www.unicode.org/Public/16.0.0/ucd/", + "homepage": "https://www.unicode.org/", + "licenseDeclared": "Unicode-3.0", + "name": "Unicode Character Database", + "versionInfo": "16.0.0", + "path": [ + "./lib/stdlib/uc_spec/CaseFolding.txt", + "./lib/stdlib/uc_spec/CompositionExclusions.txt", + "./lib/stdlib/uc_spec/EastAsianWidth.txt", + "./lib/stdlib/uc_spec/emoji-data.txt", + "./lib/stdlib/uc_spec/GraphemeBreakProperty.txt", + "./lib/stdlib/uc_spec/IndicSyllabicCategory.txt", + "./lib/stdlib/uc_spec/PropList.txt", + "./lib/stdlib/uc_spec/SpecialCasing.txt", + "./lib/stdlib/uc_spec/UnicodeData.txt", + "./lib/stdlib/test/unicode_util_SUITE_data/GraphemeBreakTest.txt", + "./lib/stdlib/test/unicode_util_SUITE_data/LineBreakTest.txt", + "./lib/stdlib/test/unicode_util_SUITE_data/NormalizationTest.txt" + ], + "supplier": "Organization: Unicode, Inc", + "purl": "pkg:generic/unicode" + } +] diff --git a/lib/wx/vendor.info b/lib/wx/vendor.info index 8041853d9748..a49830b357c3 100644 --- a/lib/wx/vendor.info +++ b/lib/wx/vendor.info @@ -1,21 +1,25 @@ -%% %CopyrightBegin% -%% -%% SPDX-License-Identifier: Apache-2.0 -%% -%% Copyright Ericsson AB 2025. All Rights Reserved. -%% -%% %CopyrightEnd% -{ - "ID": "wx", - "description": "wxWidgets documentation inserted from original project into Erlang bindings", - "copyrightText": "Copyright (c) 1998 Julian Smart, Robert Roebling et al", - "downloadLocation": "https://github.com/wxWidgets/wxWidgets", - "homepage": "https://github.com/wxWidgets/wxWidgets", - "licenseDeclared": "LicenseRef-scancode-wxwindows-free-doc-3", - "name": "wx", - "versionInfo": "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", - "purl": "pkg:github/wxwidgets/wxwidgets" -} +// %CopyrightBegin% +// +// SPDX-License-Identifier: Apache-2.0 +// +// Copyright Ericsson AB 2025. All Rights Reserved. +// +// %CopyrightEnd% +[ + { + "ID": "wx", + "description": "wxWidgets documentation inserted from original project into Erlang bindings", + "copyrightText": "Copyright (c) 1998 Julian Smart, Robert Roebling et al", + "downloadLocation": "https://github.com/wxWidgets/wxWidgets", + "homepage": "https://github.com/wxWidgets/wxWidgets", + "licenseDeclared": "LicenseRef-scancode-wxwindows-free-doc-3", + "name": "wx", + "versionInfo": "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", + "purl": "pkg:github/wxwidgets/wxwidgets" + } +] diff --git a/make/autoconf/vendor.info b/make/autoconf/vendor.info index d135fd3dd428..b52b882cdb70 100644 --- a/make/autoconf/vendor.info +++ b/make/autoconf/vendor.info @@ -1,10 +1,10 @@ -%% %CopyrightBegin% -%% -%% SPDX-License-Identifier: Apache-2.0 -%% -%% Copyright Ericsson AB 2025. All Rights Reserved. -%% -%% %CopyrightEnd% +// %CopyrightBegin% +// +// SPDX-License-Identifier: Apache-2.0 +// +// Copyright Ericsson AB 2025. All Rights Reserved. +// +// %CopyrightEnd% [ { "ID": "make-config", @@ -28,7 +28,7 @@ "licenseDeclared": "MIT", "name": "Autoconf", "versionInfo": "2.71", - "path": "./make/autoconf/install-sh", + "path": ["./make/autoconf/install-sh"], "supplier": "Organization: Free Software Foundation", "purl": "pkg:generic/autoconf" } diff --git a/scripts/license-header.es b/scripts/license-header.es index 5a16d9af87c1..6d742a4679a9 100755 --- a/scripts/license-header.es +++ b/scripts/license-header.es @@ -129,32 +129,29 @@ update(Opts) -> ci(Opts) -> %% The list below is generated by running - %% git diff --name-only --diff-filter=d OTP-27.3 HEAD | ./scripts/license-header.es scan --no-missing --path stdin | grep ":" | awk -F: '{print "\"" $1 "\","}' - NoWarnNewFiles = ["lib/compiler/test/beam_doc_SUITE_data/converted_metadata.erl", + %% git diff --name-only --diff-filter=d OTP-27.3 HEAD | ./scripts/license-header.es scan --no-missing --path stdin | grep ":" | grep -v "^See" | awk -F: '{print "\"" $1 "\","}' | sort + NoWarnNewFiles = ["erts/emulator/test/big_SUITE_data/eq_big.dat", + "erts/emulator/test/big_SUITE_data/eq_big_rem.dat", + "erts/emulator/test/float_SUITE_data/fp_drv.c", + "lib/asn1/test/asn1_SUITE_data/PrimStrings.asn1", + "lib/common_test/test/ct_surefire_SUITE_data/skip_one_suite.spec", + "lib/compiler/test/beam_doc_SUITE_data/converted_metadata.erl", "lib/compiler/test/beam_doc_SUITE_data/converted_metadata_warnings.erl", "lib/compiler/test/beam_doc_SUITE_data/cover_compiled.erl", "lib/compiler/test/beam_ssa_check_SUITE_data/phis.erl", "lib/compiler/test/beam_ssa_check_SUITE_data/ss_depth_limit.erl", "lib/compiler/test/compile_SUITE_data/small.erl", - "make/ex_doc.sha1sum", - "make/ex_doc.sha256sum", - "make/ex_doc_link", - "make/ex_doc_vsn", - "lib/kernel/test/interactive_shell_SUITE_data/ssh_host_rsa_key", - "lib/kernel/test/interactive_shell_SUITE_data/valid_keymap.config", "lib/dialyzer/test/behaviour_SUITE_data/results/gen_server_incorrect_args", "lib/dialyzer/test/indent_SUITE_data/results/dict_use", "lib/dialyzer/test/indent_SUITE_data/results/map_galore", "lib/dialyzer/test/indent_SUITE_data/results/queue_use", "lib/dialyzer/test/indent_SUITE_data/results/rec", "lib/dialyzer/test/indent_SUITE_data/results/simple", + "lib/dialyzer/test/indent_SUITE_data/src/record_send_test.erl", "lib/dialyzer/test/indent_SUITE_data/src/rec/rec_adt.erl", "lib/dialyzer/test/indent_SUITE_data/src/rec/rec_use.erl", - "lib/dialyzer/test/indent_SUITE_data/src/record_send_test.erl", "lib/dialyzer/test/indent_SUITE_data/src/simple/is_rec.erl", "lib/dialyzer/test/map_SUITE_data/results/loop", - "lib/stdlib/test/unicode_util_SUITE_data/unicode_table.bin", - "lib/stdlib/test/zstd_SUITE_data/dict", "lib/dialyzer/test/map_SUITE_data/results/map_galore", "lib/dialyzer/test/map_SUITE_data/results/opaque_key", "lib/dialyzer/test/nowarn_function_SUITE_data/results/warn_function", @@ -168,46 +165,28 @@ ci(Opts) -> "lib/dialyzer/test/opaque_SUITE_data/results/int", "lib/dialyzer/test/opaque_SUITE_data/results/mixed_opaque", "lib/dialyzer/test/opaque_SUITE_data/results/modules", - "lib/syntax_tools/test/syntax_tools_SUITE_data/syntax_tools_SUITE_test_module.erl", "lib/dialyzer/test/opaque_SUITE_data/results/my_queue", "lib/dialyzer/test/opaque_SUITE_data/results/opaque", - "lib/stdlib/test/erl_lint_SUITE_data/bad_behaviour1.erl", "lib/dialyzer/test/opaque_SUITE_data/results/para", "lib/dialyzer/test/opaque_SUITE_data/results/queue", "lib/dialyzer/test/opaque_SUITE_data/results/rec", "lib/dialyzer/test/opaque_SUITE_data/results/simple", - "lib/tools/test/emacs_SUITE_data/comprehensions", "lib/dialyzer/test/opaque_SUITE_data/results/timer", "lib/dialyzer/test/opaque_SUITE_data/results/union", - "lib/tools/test/emacs_SUITE_data/type_specs", "lib/dialyzer/test/opaque_SUITE_data/results/weird", "lib/dialyzer/test/opaque_SUITE_data/results/wings", - "lib/stdlib/test/re_SUITE_data/mod_testoutput8", "lib/dialyzer/test/opaque_SUITE_data/src/opaque/opaque_adt.erl", - "lib/stdlib/test/re_SUITE_data/old_pcre1/mod_testoutput8", - "lib/stdlib/test/re_SUITE_data/old_pcre1/testoutput1", "lib/dialyzer/test/opaque_SUITE_data/src/rec/rec_adt.erl", "lib/dialyzer/test/opaque_SUITE_data/src/rec/rec_use.erl", - "lib/stdlib/test/re_SUITE_data/old_pcre1/testoutput10", "lib/dialyzer/test/opaque_SUITE_data/src/simple/is_rec.erl", "lib/dialyzer/test/opaque_SUITE_data/src/timer/timer_use.erl", - "lib/stdlib/test/re_SUITE_data/old_pcre1/testoutput2", - "lib/stdlib/test/re_SUITE_data/old_pcre1/testoutput3", "lib/dialyzer/test/options1_SUITE_data/src/compiler/sys_expand_pmod.erl", - "lib/stdlib/test/re_SUITE_data/old_pcre1/testoutput4", "lib/dialyzer/test/options2_SUITE_data/src/kernel/global.erl", - "lib/stdlib/test/re_SUITE_data/old_pcre1/testoutput5", "lib/dialyzer/test/overspecs_SUITE_data/dialyzer_options", - "lib/stdlib/test/re_SUITE_data/old_pcre1/testoutput6", "lib/dialyzer/test/overspecs_SUITE_data/results/opaque", "lib/dialyzer/test/r9c_SUITE_data/dialyzer_options", - "lib/stdlib/test/re_SUITE_data/testoutput1", - "lib/stdlib/test/re_SUITE_data/testoutput10", "lib/dialyzer/test/r9c_SUITE_data/results/asn1", - "lib/stdlib/test/re_SUITE_data/testoutput2", - "lib/stdlib/test/re_SUITE_data/testoutput4", "lib/dialyzer/test/r9c_SUITE_data/results/mnesia", - "lib/stdlib/test/re_SUITE_data/testoutput5", "lib/dialyzer/test/r9c_SUITE_data/src/asn1/asn1ct_value.erl", "lib/dialyzer/test/r9c_SUITE_data/src/asn1/asn1rt_per.erl", "lib/dialyzer/test/r9c_SUITE_data/src/mnesia/mnesia_lib.erl", @@ -221,18 +200,37 @@ ci(Opts) -> "lib/dialyzer/test/user_SUITE_data/dialyzer_options", "lib/dialyzer/test/user_SUITE_data/results/gcpFlowControl", "lib/edoc/test/eep48_SUITE_data/eep48_specs.erl", - "lib/asn1/test/asn1_SUITE_data/PrimStrings.asn1", - "lib/common_test/test/ct_surefire_SUITE_data/skip_one_suite.spec", - "erts/emulator/test/big_SUITE_data/eq_big.dat", - "erts/emulator/test/big_SUITE_data/eq_big_rem.dat", - "erts/emulator/test/float_SUITE_data/fp_drv.c"], + "lib/kernel/test/interactive_shell_SUITE_data/ssh_host_rsa_key", + "lib/kernel/test/interactive_shell_SUITE_data/valid_keymap.config", + "lib/stdlib/test/erl_lint_SUITE_data/bad_behaviour1.erl", + "lib/stdlib/test/re_SUITE_data/mod_testoutput8", + "lib/stdlib/test/re_SUITE_data/old_pcre1/mod_testoutput8", + "lib/stdlib/test/re_SUITE_data/old_pcre1/testoutput1", + "lib/stdlib/test/re_SUITE_data/old_pcre1/testoutput10", + "lib/stdlib/test/re_SUITE_data/old_pcre1/testoutput2", + "lib/stdlib/test/re_SUITE_data/old_pcre1/testoutput3", + "lib/stdlib/test/re_SUITE_data/old_pcre1/testoutput4", + "lib/stdlib/test/re_SUITE_data/old_pcre1/testoutput5", + "lib/stdlib/test/re_SUITE_data/old_pcre1/testoutput6", + "lib/stdlib/test/re_SUITE_data/testoutput1", + "lib/stdlib/test/re_SUITE_data/testoutput10", + "lib/stdlib/test/re_SUITE_data/testoutput2", + "lib/stdlib/test/re_SUITE_data/testoutput4", + "lib/stdlib/test/re_SUITE_data/testoutput5", + "lib/stdlib/test/unicode_util_SUITE_data/unicode_table.bin", + "lib/stdlib/test/zstd_SUITE_data/dict", + "lib/syntax_tools/test/syntax_tools_SUITE_data/syntax_tools_SUITE_test_module.erl", + "lib/tools/test/emacs_SUITE_data/comprehensions", + "lib/tools/test/emacs_SUITE_data/type_specs", + "make/ex_doc_link", + "make/ex_doc.sha1sum", + "make/ex_doc.sha256sum", + "make/ex_doc_vsn"], %% A long list of things we currently ignore... all of these should be fixed! NoWarnAllFiles = ["**/doc/**", - "**/internal_doc/**", "**/examples/**", "**/test/**", - "**/*.ico", "**/*.bmp", "**/*.png", "**/*.jpg", "make/gdb_*", "make/otp_patch*", "make/otp_version*", @@ -241,13 +239,6 @@ ci(Opts) -> "**/TAR.exclude", "make/autoconf/*.static", "**/*.cover", - "lib/megaco/src/binary/*.asn", - "lib/megaco/src/binary/*.asn1config", - "lib/megaco/include/megaco_message_v*.hrl", - "lib/snmp/mibs/*.mib", - "lib/snmp/mibs/*.funcs", - "lib/snmp/priv/conf/**", - "lib/snmp/bin/snmp-v2tov1*", "lib/public_key/asn1/*", "lib/public_key/priv/moduli", "lib/public_key/src/pubkey_moduli.hrl", @@ -323,7 +314,7 @@ check_file_header(File, LicenseFile, Data, {Start, StartEnd}, Prefix, Templates, length(string:split(DataAfterHeader,"\n",all)), File, not string:equal(File, LicenseFile), Opts), case maps:get(update, Opts, false) of - true -> update_copyright(File, LicenseFile, Start + StartEnd, End, Prefix, LineEnding, Spdx, Copyrights, License); + true -> update_copyright(LicenseFile, Start + StartEnd, End, Prefix, LineEnding, Spdx, Copyrights, License); false -> ok end; nomatch when map_get(verbose, Opts) -> @@ -332,7 +323,7 @@ check_file_header(File, LicenseFile, Data, {Start, StartEnd}, Prefix, Templates, throw({warn, "Could not find '~ts %CopyrightEnd%'", [Prefix]}) end. -update_copyright(File, LicenseFile, Begin, End, Prefix, LineEnding, Spdx, Copyrights, License) -> +update_copyright(File, Begin, End, Prefix, LineEnding, Spdx, Copyrights, License) -> case update_copyright(File, Copyrights) of Copyrights -> ok; NewCopyrights -> @@ -340,7 +331,7 @@ update_copyright(File, LicenseFile, Begin, End, Prefix, LineEnding, Spdx, Copyri Before = binary:part(Data, 0, Begin), After = binary:part(Data, End, byte_size(Data) - End), ok = file:write_file( - LicenseFile, + File, [Before, string:trim(Prefix, trailing), LineEnding, Prefix, "SPDX-License-Identifier: ", Spdx, LineEnding, @@ -550,10 +541,7 @@ get_vendor_paths(RootPath) -> lists:flatmap(fun get_vendor_path/1, filelib:wildcard(filename:join(RootPath, "**/vendor.info"))). get_vendor_path(File) -> {ok, B} = file:read_file(File), - Vendors = case json:decode(re:replace(B, "^%.*", "", [multiline, global, {return, binary}])) of - #{ } = V -> [V]; - [_ | _] = Vs -> Vs - end, + [_ | _] = Vendors = json:decode(re:replace(B, "^//.*", "", [multiline, global, {return, binary}])), lists:flatmap( fun(V) -> case maps:get(~"path", V) of diff --git a/system/COPYRIGHT b/system/COPYRIGHT deleted file mode 100644 index 7bb4d37b501e..000000000000 --- a/system/COPYRIGHT +++ /dev/null @@ -1,1240 +0,0 @@ -This software is subject to the following Copyrights and Licenses: - ---------------------------------------------------------------------------- -[Erlang/OTP except parts stated below] - -* Info: - * SPDX-License-Identifier: Apache-2.0 - -%CopyrightBegin% - -SPDX-License-Identifier: Apache-2.0 - -Copyright Ericsson AB 1997-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% - ---------------------------------------------------------------------------- -[configure scripts] - -* Info: - * SPDX-License-Identifier: FSFUL - * Tool: Autoconf - * Version: 2.71 - * Website: https://www.gnu.org/software/autoconf/ - * OTP Location: ./make/configure and - ./erts/configure and - ./lib/erl_interface/configure and - ./lib/crypto/configure and - ./lib/wx/configure and - ./lib/megaco/configure and - ./lib/snmp/configure and - ./lib/odbc/configure and - ./lib/common_test/test_server/configure and - ./lib/common_test/configure - -# Copyright (C) 1992-1996, 1998-2012, 2020-2021 Free Software Foundation, Inc. -# -# -# This configure script is free software; the Free Software Foundation -# gives unlimited permission to copy, distribute and modify it. - ---------------------------------------------------------------------------- -[config.guess and config.sub scripts] - -* Info: - * SPDX-License-Identifier: GPL-3.0-or-later WITH Autoconf-exception-generic-3.0 - * Tool: Autoconf - * Version: 2.71 - * Website: https://www.gnu.org/software/autoconf/ - * OTP Location: ./make/autoconf/config.{guess,sub} and - ./erts/autoconf/config.{guess,sub} and - ./lib/common_test/test_server/config.{guess,sub} - -# Copyright 1992-2021 Free Software Foundation, Inc. - -# This file is free software; you can redistribute it and/or modify it -# under the terms of the GNU General Public License as published by -# the Free Software Foundation; either version 3 of the License, or -# (at your option) any later version. -# -# This program is distributed in the hope that it will be useful, but -# WITHOUT ANY WARRANTY; without even the implied warranty of -# MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU -# General Public License for more details. -# -# You should have received a copy of the GNU General Public License -# along with this program; if not, see . -# -# As a special exception to the GNU General Public License, if you -# distribute this file as part of a program that contains a -# configuration script generated by Autoconf, you may include it under -# the same distribution terms that you use for the rest of that -# program. This Exception is an additional permission under section 7 -# of the GNU General Public License, version 3 ("GPLv3"). -# -# Originally written by Per Bothner; maintained since 2000 by Ben Elliston. -# -# You can get the latest version of this script from: -# https://git.savannah.gnu.org/cgit/config.git/plain/config.guess -# -# Please send patches to . - ---------------------------------------------------------------------------- -[install-sh scripts] - -* Info: - * SPDX-License-Identifier: MIT - * Tool: Autoconf - * Version: 2.71 - * Website: https://www.gnu.org/software/autoconf/ - * OTP Location: ./make/autoconf/install-sh and - ./erts/autoconf/install-sh and - ./lib/common_test/test_server/install-sh - -# Copyright (C) 1994 X Consortium -# -# Permission is hereby granted, free of charge, to any person obtaining a copy -# of this software and associated documentation files (the "Software"), to -# deal in the Software without restriction, including without limitation the -# rights to use, copy, modify, merge, publish, distribute, sublicense, and/or -# sell copies of the Software, and to permit persons to whom the Software is -# furnished to do so, subject to the following conditions: -# -# The above copyright notice and this permission notice shall be included in -# all copies or substantial portions of the Software. -# -# THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR -# IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, -# FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE -# X CONSORTIUM BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN -# AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNEC- -# TION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. -# -# Except as contained in this notice, the name of the X Consortium shall not -# be used in advertising or otherwise to promote the sale, use or other deal- -# ings in this Software without prior written authorization from the X Consor- -# tium. -# -# -# FSF changes to this file are in the public domain. - ---------------------------------------------------------------------------- -[erl_posix_str.c] - -* Info: - * SPDX-License-Identifier: TCL - * Modification of tclPosixStr.c from TCL - * Library: TCL - * Version 7.6 - * Website: https://www.tcl.tk/ - * OTP Location: ./erts/emulator/beam/erl_posix_str.c - -Copyright (c) 1991-1994 The Regents of the University of California. -Copyright (c) 1994-1996 Sun Microsystems, Inc. - -This software is copyrighted by the Regents of the University of -California, Sun Microsystems, Inc., and other parties. The following -terms apply to all files associated with the software unless explicitly -disclaimed in individual files. - -The authors hereby grant permission to use, copy, modify, distribute, -and license this software and its documentation for any purpose, provided -that existing copyright notices are retained in all copies and that this -notice is included verbatim in any distributions. No written agreement, -license, or royalty fee is required for any of the authorized uses. -Modifications to this software may be copyrighted by their authors -and need not follow the licensing terms described here, provided that -the new terms are clearly indicated on the first page of each file where -they apply. - -IN NO EVENT SHALL THE AUTHORS OR DISTRIBUTORS BE LIABLE TO ANY PARTY -FOR DIRECT, INDIRECT, SPECIAL, INCIDENTAL, OR CONSEQUENTIAL DAMAGES -ARISING OUT OF THE USE OF THIS SOFTWARE, ITS DOCUMENTATION, OR ANY -DERIVATIVES THEREOF, EVEN IF THE AUTHORS HAVE BEEN ADVISED OF THE -POSSIBILITY OF SUCH DAMAGE. - -THE AUTHORS AND DISTRIBUTORS SPECIFICALLY DISCLAIM ANY WARRANTIES, -INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY, -FITNESS FOR A PARTICULAR PURPOSE, AND NON-INFRINGEMENT. THIS SOFTWARE -IS PROVIDED ON AN "AS IS" BASIS, AND THE AUTHORS AND DISTRIBUTORS HAVE -NO OBLIGATION TO PROVIDE MAINTENANCE, SUPPORT, UPDATES, ENHANCEMENTS, OR -MODIFICATIONS. - -GOVERNMENT USE: If you are acquiring this software on behalf of the -U.S. government, the Government shall have only "Restricted Rights" -in the software and related documentation as defined in the Federal -Acquisition Regulations (FARs) in Clause 52.227.19 (c) (2). If you -are acquiring the software on behalf of the Department of Defense, the -software shall be classified as "Commercial Computer Software" and the -Government shall have only "Restricted Rights" as defined in Clause -252.227-7013 (c) (1) of DFARs. Notwithstanding the foregoing, the -authors grant the U.S. Government and others acting in its behalf -permission to use and distribute the software in accordance with the -terms specified in this license. - ---------------------------------------------------------------------------- -[various contributions] - -* Info: - * SPDX-License-Identifier: Apache-2.0 - * Various contributions made to Erlang/OTP under Apache 2.0 License - -* ./lib/stdlib/include/assert.hrl - and ./bootstrap/lib/stdlib/include/assert.hrl - * is Copyright (C) 2004-1016 Richard Carlsson, Mickaël Rémond -* ./lib/stdlib/src/array.erl - * Copyright (C) 2006-2016 Richard Carlsson and Ericsson AB -* ./lib/stdlib/src/gb_trees.erl - * Copyright (C) 1999-2001 Sven-Olof Nyström, Richard Carlsson -* ./lib/stdlib/src/gb_sets.erl - * Copyright (C) 1999-2001 Richard Carlsson, Sven-Olof Nyström -* ./lib/stdlib/src/proplists.erl - * Copyright (C) 2000-2003 Richard Carlsson -* ./lib/compiler/src/cerl_trees.erl and - ./lib/dialyzer/test/options1_SUITE_data/src/compiler/cerl_trees.erl - * Copyright (C) 1999-2002 Richard Carlsson -* ./lib/compiler/src/cerl_clauses.erl and - ./lib/dialyzer/test/options1_SUITE_data/src/compiler/cerl_clauses.erl - * Copyright (C) 1999-2002 Richard Carlsson -* ./lib/compiler/src/cerl_inline.erl and - ./lib/dialyzer/test/options1_SUITE_data/src/compiler/cerl_inline.erl - * Copyright (C) 1999-2002 Richard Carlsson -* ./lib/kernel/src/pg.erl and - ./lib/kernel/test/pg_SUITE.erl and ./lib/stdlib/src/peer.erl - * Copyright WhatsApp Inc. and its affiliates. All rights reserved. - ---------------------------------------------------------------------------- -[AsmJit] - -* Info - * SPDX-License-Identifier: Zlib - * Library: AsmJit - * Git Repository: https://github.com/asmjit/asmjit - * Commit: 029075b84bf0161a761beb63e6eda519a29020db - * OTP Location: erts/emulator/asmjit - -Copyright (c) 2008-2025 The AsmJit Authors - -This software is provided 'as-is', without any express or implied -warranty. In no event will the authors be held liable for any damages -arising from the use of this software. - -Permission is granted to anyone to use this software for any purpose, -including commercial applications, and to alter it and redistribute it -freely, subject to the following restrictions: - -1. The origin of this software must not be misrepresented; you must not - claim that you wrote the original software. If you use this software - in a product, an acknowledgment in the product documentation would be - appreciated but is not required. -2. Altered source versions must be plainly marked as such, and must not be - misrepresented as being the original software. -3. This notice may not be removed or altered from any source distribution. - ---------------------------------------------------------------------------- -[PCRE2] - -* Info: - * SPDX-License-Identifier: BSD-3-Clause - * Library: PCRE2 - * Version: 10.45 - * Website: https://www.pcre.org - * OTP Location: ./erts/emulator/pcre - -PCRE2 License -============= - -| SPDX-License-Identifier: | BSD-3-Clause WITH PCRE2-exception | -|---------|-------| - -PCRE2 is a library of functions to support regular expressions whose syntax -and semantics are as close as possible to those of the Perl 5 language. - -Releases 10.00 and above of PCRE2 are distributed under the terms of the "BSD" -licence, as specified below, with one exemption for certain binary -redistributions. The documentation for PCRE2, supplied in the "doc" directory, -is distributed under the same terms as the software itself. The data in the -testdata directory is not copyrighted and is in the public domain. - -The basic library functions are written in C and are freestanding. Also -included in the distribution is a just-in-time compiler that can be used to -optimize pattern matching. This is an optional feature that can be omitted when -the library is built. - - -COPYRIGHT ---------- - -### The basic library functions - - Written by: Philip Hazel - Email local part: Philip.Hazel - Email domain: gmail.com - - Retired from University of Cambridge Computing Service, - Cambridge, England. - - Copyright (c) 1997-2007 University of Cambridge - Copyright (c) 2007-2024 Philip Hazel - All rights reserved. - -### PCRE2 Just-In-Time compilation support - - Written by: Zoltan Herczeg - Email local part: hzmester - Email domain: freemail.hu - - Copyright (c) 2010-2024 Zoltan Herczeg - All rights reserved. - -### Stack-less Just-In-Time compiler - - Written by: Zoltan Herczeg - Email local part: hzmester - Email domain: freemail.hu - - Copyright (c) 2009-2024 Zoltan Herczeg - All rights reserved. - -### All other contributions - -Many other contributors have participated in the authorship of PCRE2. As PCRE2 -has never required a Contributor Licensing Agreement, or other copyright -assignment agreement, all contributions have copyright retained by each -original contributor or their employer. - - -THE "BSD" LICENCE ------------------ - -Redistribution and use in source and binary forms, with or without -modification, are permitted provided that the following conditions are met: - -* Redistributions of source code must retain the above copyright notices, - this list of conditions and the following disclaimer. - -* Redistributions in binary form must reproduce the above copyright - notices, this list of conditions and the following disclaimer in the - documentation and/or other materials provided with the distribution. - -* Neither the name of the University of Cambridge nor the names of any - contributors may be used to endorse or promote products derived from this - software without specific prior written permission. - -THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS" -AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE -IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE -ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT OWNER OR CONTRIBUTORS BE -LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR -CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF -SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS -INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN -CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) -ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE -POSSIBILITY OF SUCH DAMAGE. - - -EXEMPTION FOR BINARY LIBRARY-LIKE PACKAGES ------------------------------------------- - -The second condition in the BSD licence (covering binary redistributions) does -not apply all the way down a chain of software. If binary package A includes -PCRE2, it must respect the condition, but if package B is software that -includes package A, the condition is not imposed on package B unless it uses -PCRE2 independently. - -End - ---------------------------------------------------------------------------- -[zlib] - -* Info: - * SPDX-License-Identifier: Zlib - * Library: Zlib - * Version: 1.3.1 - * Website: https://zlib.net/ - * OTP Location: ./erts/emulator/zlib - -/* zlib.h -- interface of the 'zlib' general purpose compression library - version 1.3.1, January 22nd, 2024 - - Copyright (C) 1995-2024 Jean-loup Gailly and Mark Adler - - This software is provided 'as-is', without any express or implied - warranty. In no event will the authors be held liable for any damages - arising from the use of this software. - - Permission is granted to anyone to use this software for any purpose, - including commercial applications, and to alter it and redistribute it - freely, subject to the following restrictions: - - 1. The origin of this software must not be misrepresented; you must not - claim that you wrote the original software. If you use this software - in a product, an acknowledgment in the product documentation would be - appreciated but is not required. - 2. Altered source versions must be plainly marked as such, and must not be - misrepresented as being the original software. - 3. This notice may not be removed or altered from any source distribution. - - Jean-loup Gailly Mark Adler - jloup@gzip.org madler@alumni.caltech.edu - - - The data format used by the zlib library is described by RFCs (Request for - Comments) 1950 to 1952 in the files http://tools.ietf.org/html/rfc1950 - (zlib format), rfc1951 (deflate format) and rfc1952 (gzip format). -*/ - ---------------------------------------------------------------------------- -[ryu] - -* Info: - * SPDX-License-Identifier: Apache-2.0 OR BSL-1.0 - * Library: RYU - * Git repository: https://github.com/ulfjack/ryu - * Commit: 844864ac213bdbf1fb57e6f51c653b3d90af0937 - * OTP Location: ./erts/emulator/ryu - -// Copyright 2018 Ulf Adams -// -// The contents of this file may be used under the terms of the Apache License, -// Version 2.0. -// -// (See accompanying file LICENSE-Apache or copy at -// http://www.apache.org/licenses/LICENSE-2.0) -// -// Alternatively, the contents of this file may be used under the terms of -// the Boost Software License, Version 1.0. -// (See accompanying file LICENSE-Boost or copy at -// https://www.boost.org/LICENSE_1_0.txt) -// -// Unless required by applicable law or agreed to in writing, this software -// is distributed on an "AS IS" BASIS, WITHOUT WARRANTIES OR CONDITIONS OF ANY -// KIND, either express or implied. - ---------------------------------------------------------------------------- -[to_chars() function in ryu] - -* Info: - * SPDX-License-Identifier: (Apache-2.0 WITH LLVM-exception) AND BSL-1.0 - * License Comment: The license information in the original file is not - clear on whether it should be AND or OR between - "Apache 2.0 with LLVM-exception" and "Boost Software - License 1.0". Therefore, just to be safe, an AND was - chosen in the SPDX license identifier expression - above. - * Library: STL - * Git repository: https://github.com/microsoft/STL - * Commit: e745bad3b1d05b5b19ec652d68abb37865ffa454 - * Original function: https://github.com/microsoft/STL/blob/e745bad3b1d05b5b19ec652d68abb37865ffa454/stl/inc/xcharconv_ryu.h#L1926 - * OTP Location: ./erts/emulator/ryu/d2s.c:to_chars() - -// xcharconv_ryu.h internal header - -// Copyright (c) Microsoft Corporation. -// SPDX-License-Identifier: Apache-2.0 WITH LLVM-exception - - -// Copyright 2018 Ulf Adams -// Copyright (c) Microsoft Corporation. All rights reserved. - -// Boost Software License - Version 1.0 - August 17th, 2003 - -// Permission is hereby granted, free of charge, to any person or organization -// obtaining a copy of the software and accompanying documentation covered by -// this license (the "Software") to use, reproduce, display, distribute, -// execute, and transmit the Software, and to prepare derivative works of the -// Software, and to permit third-parties to whom the Software is furnished to -// do so, all subject to the following: - -// The copyright notices in the Software and this entire statement, including -// the above license grant, this restriction and the following disclaimer, -// must be included in all copies of the Software, in whole or in part, and -// all derivative works of the Software, unless such copies or derivative -// works are solely in the form of machine-executable object code generated by -// a source language processor. - -// THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR -// IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, -// FITNESS FOR A PARTICULAR PURPOSE, TITLE AND NON-INFRINGEMENT. IN NO EVENT -// SHALL THE COPYRIGHT HOLDERS OR ANYONE DISTRIBUTING THE SOFTWARE BE LIABLE -// FOR ANY DAMAGES OR OTHER LIABILITY, WHETHER IN CONTRACT, TORT OR OTHERWISE, -// ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER -// DEALINGS IN THE SOFTWARE. - ---------------------------------------------------------------------------- -[fp16] - -* Info: - * SPDX-License-Identifier: MIT - * Library: FP16 - * Git Repository: https://github.com/Maratyszcza/FP16 - * Commit: 0a92994d729ff76a58f692d3028ca1b64b145d91 - * OTP Location: ./erts/emulator/beam/erl_bits_f16.h - -The MIT License (MIT) - -Copyright (c) 2017 Facebook Inc. -Copyright (c) 2017 Georgia Institute of Technology -Copyright 2019 Google LLC - -Permission is hereby granted, free of charge, to any person obtaining a copy of this -software and associated documentation files (the "Software"), to deal in the Software -without restriction, including without limitation the rights to use, copy, modify, -merge, publish, distribute, sublicense, and/or sell copies of the Software, and to -permit persons to whom the Software is furnished to do so, subject to the following -conditions: - -The above copyright notice and this permission notice shall be included in all copies -or substantial portions of the Software. - -THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, -INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR -PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE -FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR -OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER -DEALINGS IN THE SOFTWARE. - ---------------------------------------------------------------------------- -[OpenSSL MD5 implementation] - -* Info: - * SPDX-License-Identifier: Apache-2.0 - * Library: OpenSSL - * Version: 3.1.4 - * Git Repository: https://github.com/openssl/openssl - * Commit: 01d5e2318405362b4de5e670c90d9b40a351d053 - * OTP Location: ./erts/emulator/openssl and - ./lib/erl_interface/src/openssl - -/* - * Copyright 1995-2022 The OpenSSL Project Authors. All Rights Reserved. - * - * Licensed under the Apache License 2.0 (the "License"). You may not use - * this file except in compliance with the License. You can obtain a copy - * in the file LICENSE in the source distribution or at - * https://www.openssl.org/source/license.html - */ - ---------------------------------------------------------------------------- -[dialyzer] - -* Info: - * SPDX-License-Identifier: Apache-2.0 - * Contribution made to Erlang/OTP - * OTP Location: ./lib/dialyzer - -%% Copyright 1997-2016 Tobias Lindahl, Stavros Aronis, Kostis Sagonas, -%% Richard Carlsson, et al. -%% -%% 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. - ---------------------------------------------------------------------------- -[edoc, syntax_tools] - -* Info: - * SPDX-License-Identifier: Apache-2.0 OR LGPL-2.1-or-later - * Contribution made to Erlang/OTP - * OTP Location: ./lib/edoc and ./lib/syntax_tools - -%% Copyright 1997-2016 Richard Carlsson -%% -%% 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 -%% -%% 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. -%% -%% Alternatively, you may use this file under the terms of the GNU Lesser -%% General Public License (the "LGPL") as published by the Free Software -%% Foundation; either version 2.1, or (at your option) any later version. -%% If you wish to allow use of your version of this file only under the -%% terms of the LGPL, you should delete the provisions above and replace -%% them with the notice and other provisions required by the LGPL; see -%% . If you do not delete the provisions -%% above, a recipient may use your version of this file under the terms of -%% either the Apache License or the LGPL. - ---------------------------------------------------------------------------- -[eunit] - -* Info: - * SPDX-License-Identifier: Apache-2.0 OR LGPL-2.1-or-later - * Contribution made to Erlang/OTP - * OTP Location: ./lib/eunit - -%% Copyright 2004-2016 Richard Carlsson , -%% Mickaël Rémond -%% -%% 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 -%% -%% 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. -%% -%% Alternatively, you may use this file under the terms of the GNU Lesser -%% General Public License (the "LGPL") as published by the Free Software -%% Foundation; either version 2.1, or (at your option) any later version. -%% If you wish to allow use of your version of this file only under the -%% terms of the LGPL, you should delete the provisions above and replace -%% them with the notice and other provisions required by the LGPL; see -%% . If you do not delete the provisions -%% above, a recipient may use your version of this file under the terms of -%% either the Apache License or the LGPL. - ---------------------------------------------------------------------------- -[leex] - -* Info: - * SPDX-License-Identifier: BSD-2-Clause - * Contribution made to Erlang/OTP - * OTP Location: ./lib/parsetools/src/leex.erl - -%% Copyright (c) 2008,2009 Robert Virding. All rights reserved. -%% -%% Redistribution and use in source and binary forms, with or without -%% modification, are permitted provided that the following conditions -%% are met: -%% -%% 1. Redistributions of source code must retain the above copyright -%% notice, this list of conditions and the following disclaimer. -%% 2. Redistributions in binary form must reproduce the above copyright -%% notice, this list of conditions and the following disclaimer in the -%% documentation and/or other materials provided with the distribution. -%% -%% THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -%% "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT -%% LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS -%% FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE -%% COPYRIGHT HOLDERS OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, -%% INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, -%% BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; -%% LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER -%% CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT -%% LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN -%% ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE -%% POSSIBILITY OF SUCH DAMAGE. - ---------------------------------------------------------------------------- -[eldap] - -* Info: - * SPDX-License-Identifier: MIT - * Contribution made to Erlang/OTP - * Git Repository: https://github.com/etnt/eldap.git - * Commit: 36c595f56c12a44adbc942eef218df85137cbbee - * OTP Location: ./lib/eldap/src/eldap.erl - -Copyright (c) 2010, Torbjorn Tornkvist - -Permission is hereby granted, free of charge, to any person obtaining a copy -of this software and associated documentation files (the "Software"), to deal -in the Software without restriction, including without limitation the rights -to use, copy, modify, merge, publish, distribute, sublicense, and/or sell -copies of the Software, and to permit persons to whom the Software is -furnished to do so, subject to the following conditions: - -The above copyright notice and this permission notice shall be included in -all copies or substantial portions of the Software. - -THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR -IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, -FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE -AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER -LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, -OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN -THE SOFTWARE. - ---------------------------------------------------------------------------- -[json tests] - -* Info: - * SPDX-License-Identifier: MIT - * Git Repository: https://github.com/nst/JSONTestSuite - * Commit: 984defc2deaa653cb73cd29f4144a720ec9efe7c - * OTP Location: ./lib/stdlib/test/json_SUITE_data - -Copyright (c) 2016 Nicolas Seriot - -Permission is hereby granted, free of charge, to any person obtaining a copy -of this software and associated documentation files (the "Software"), to deal -in the Software without restriction, including without limitation the rights -to use, copy, modify, merge, publish, distribute, sublicense, and/or sell -copies of the Software, and to permit persons to whom the Software is -furnished to do so, subject to the following conditions: - -The above copyright notice and this permission notice shall be included in -all copies or substantial portions of the Software. - -THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR -IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, -FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE -AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER -LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, -OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN -THE SOFTWARE. - ---------------------------------------------------------------------------- -[wx documentation] - -* Info: - * No SPDX License Identifier exist for this license. - * License: wxWindows Free Documentation Licence, Version 3 - * Git Repository: https://github.com/wxWidgets/wxWidgets - * Commit: dc585039bbd426829e3433002023a93f9bedd0c2 - * OTP Location: ./lib/wx/doc/src - -wxWindows Free Documentation Licence, Version 3 -=============================================== - -Copyright (c) 1998 Julian Smart, Robert Roebling et al - -Everyone is permitted to copy and distribute verbatim copies -of this licence document, but changing it is not allowed. - - WXWINDOWS FREE DOCUMENTATION LICENCE - TERMS AND CONDITIONS FOR COPYING, DISTRIBUTION AND MODIFICATION - -1. Permission is granted to make and distribute verbatim copies of this -manual or piece of documentation provided any copyright notice and this -permission notice are preserved on all copies. - -2. Permission is granted to process this file or document through a -document processing system and, at your option and the option of any third -party, print the results, provided a printed document carries a copying -permission notice identical to this one. - -3. Permission is granted to copy and distribute modified versions of this -manual or piece of documentation under the conditions for verbatim copying, -provided also that any sections describing licensing conditions for this -manual, such as, in particular, the GNU General Public Licence, the GNU -Library General Public Licence, and any wxWindows Licence are included -exactly as in the original, and provided that the entire resulting derived -work is distributed under the terms of a permission notice identical to -this one. - -4. Permission is granted to copy and distribute translations of this manual -or piece of documentation into another language, under the above conditions -for modified versions, except that sections related to licensing, including -this paragraph, may also be included in translations approved by the -copyright holders of the respective licence documents in addition to the -original English. - - WARRANTY DISCLAIMER - -5. BECAUSE THIS MANUAL OR PIECE OF DOCUMENTATION IS LICENSED FREE OF -CHARGE, THERE IS NO WARRANTY FOR IT, TO THE EXTENT PERMITTED BY APPLICABLE -LAW. EXCEPT WHEN OTHERWISE STATED IN WRITING THE COPYRIGHT HOLDERS AND/OR -OTHER PARTIES PROVIDE THIS MANUAL OR PIECE OF DOCUMENTATION "AS IS" WITHOUT -WARRANTY OF ANY KIND, EITHER EXPRESSED OR IMPLIED, INCLUDING, BUT NOT -LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A -PARTICULAR PURPOSE. THE ENTIRE RISK AS TO THE QUALITY AND PERFORMANCE OF -THE MANUAL OR PIECE OF DOCUMENTATION IS WITH YOU. SHOULD THE MANUAL OR -PIECE OF DOCUMENTATION PROVE DEFECTIVE, YOU ASSUME THE COST OF ALL -NECESSARY SERVICING, REPAIR OR CORRECTION. - -6. IN NO EVENT UNLESS REQUIRED BY APPLICABLE LAW OR AGREED TO IN WRITING -WILL ANY COPYRIGHT HOLDER, OR ANY OTHER PARTY WHO MAY MODIFY AND/OR -REDISTRIBUTE THE MANUAL OR PIECE OF DOCUMENTATION AS PERMITTED ABOVE, BE -LIABLE TO YOU FOR DAMAGES, INCLUDING ANY GENERAL, SPECIAL, INCIDENTAL OR -CONSEQUENTIAL DAMAGES ARISING OUT OF THE USE OR INABILITY TO USE THE MANUAL -OR PIECE OF DOCUMENTATION (INCLUDING BUT NOT LIMITED TO LOSS OF DATA OR -DATA BEING RENDERED INACCURATE OR LOSSES SUSTAINED BY YOU OR THIRD PARTIES -OR A FAILURE OF A PROGRAM BASED ON THE MANUAL OR PIECE OF DOCUMENTATION TO -OPERATE WITH ANY OTHER PROGRAMS), EVEN IF SUCH HOLDER OR OTHER PARTY HAS -BEEN ADVISED OF THE POSSIBILITY OF SUCH DAMAGES. - ---------------------------------------------------------------------------- -[wx webview2 loader on windows] - -* Info: - * SPDX-License-Identifier: BSD-3-Clause - -Copyright (C) Microsoft Corporation. All rights reserved. - -Redistribution and use in source and binary forms, with or without -modification, are permitted provided that the following conditions are -met: - - * Redistributions of source code must retain the above copyright -notice, this list of conditions and the following disclaimer. - * Redistributions in binary form must reproduce the above -copyright notice, this list of conditions and the following disclaimer -in the documentation and/or other materials provided with the -distribution. - * The name of Microsoft Corporation, or the names of its contributors -may not be used to endorse or promote products derived from this -software without specific prior written permission. - -THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS -"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT -LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR -A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT -OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, -SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT -LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, -DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY -THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT -(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE -OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. - ---------------------------------------------------------------------------- -[jquery] - -* Info: - * SPDX-License-Identifier: MIT - * Tool: jquery - * Git Repository: https://github.com/jquery/jquery - * Version: 3.7.1 - * Commit: f79d5f1a337528940ab7029d4f8bbba72326f269 - * Website: https://jquery.com/ - * OTP Location: ./lib/common_test/priv/jquery-latest.js - -Copyright OpenJS Foundation and other contributors, https://openjsf.org/ - -Permission is hereby granted, free of charge, to any person obtaining -a copy of this software and associated documentation files (the -"Software"), to deal in the Software without restriction, including -without limitation the rights to use, copy, modify, merge, publish, -distribute, sublicense, and/or sell copies of the Software, and to -permit persons to whom the Software is furnished to do so, subject to -the following conditions: - -The above copyright notice and this permission notice shall be -included in all copies or substantial portions of the Software. - -THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, -EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF -MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND -NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE -LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION -OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION -WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. - ---------------------------------------------------------------------------- -[tablesorter] - -* Info: - * SPDX-License-Identifier: MIT or GPL-2.0-only - * Tool: tablesorter - * Git Repository: https://github.com/Mottie/tablesorter - * Version: 2.32 - * Commit: 1423f5408982f58d5baa97648d2e5ee0b55fd3b6 - * OTP Location: ./lib/common_test/priv/jquery.tablesorter.min.js - -Copyright (c) 2007 Christian Bach - ---------------------------------------------------------------------------- -[zstd] - -* Info: - * SPDX-License-Identifier: BSD-3-Clause OR GPL-2.0-only - * Tool: zstd - * Git Repository: https://github.com/facebook/zstd - * Version: v1.5.7 - * Commit: f8745da6ff1ad1e7bab384bd1f9d742439278e99 - * OTP Location: ./erts/emulator/zstd - -BSD License - -For Zstandard software - -Copyright (c) Meta Platforms, Inc. and affiliates. All rights reserved. - -Redistribution and use in source and binary forms, with or without modification, -are permitted provided that the following conditions are met: - - * Redistributions of source code must retain the above copyright notice, this - list of conditions and the following disclaimer. - - * Redistributions in binary form must reproduce the above copyright notice, - this list of conditions and the following disclaimer in the documentation - and/or other materials provided with the distribution. - - * Neither the name Facebook, nor Meta, nor the names of its contributors may - be used to endorse or promote products derived from this software without - specific prior written permission. - -THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS" AND -ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED -WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE -DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT HOLDER OR CONTRIBUTORS BE LIABLE FOR -ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES -(INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; -LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON -ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT -(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS -SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. - - GNU GENERAL PUBLIC LICENSE - Version 2, June 1991 - - Copyright (C) 1989, 1991 Free Software Foundation, Inc., - 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA - Everyone is permitted to copy and distribute verbatim copies - of this license document, but changing it is not allowed. - - Preamble - - The licenses for most software are designed to take away your -freedom to share and change it. By contrast, the GNU General Public -License is intended to guarantee your freedom to share and change free -software--to make sure the software is free for all its users. This -General Public License applies to most of the Free Software -Foundation's software and to any other program whose authors commit to -using it. (Some other Free Software Foundation software is covered by -the GNU Lesser General Public License instead.) You can apply it to -your programs, too. - - When we speak of free software, we are referring to freedom, not -price. Our General Public Licenses are designed to make sure that you -have the freedom to distribute copies of free software (and charge for -this service if you wish), that you receive source code or can get it -if you want it, that you can change the software or use pieces of it -in new free programs; and that you know you can do these things. - - To protect your rights, we need to make restrictions that forbid -anyone to deny you these rights or to ask you to surrender the rights. -These restrictions translate to certain responsibilities for you if you -distribute copies of the software, or if you modify it. - - For example, if you distribute copies of such a program, whether -gratis or for a fee, you must give the recipients all the rights that -you have. You must make sure that they, too, receive or can get the -source code. And you must show them these terms so they know their -rights. - - We protect your rights with two steps: (1) copyright the software, and -(2) offer you this license which gives you legal permission to copy, -distribute and/or modify the software. - - Also, for each author's protection and ours, we want to make certain -that everyone understands that there is no warranty for this free -software. If the software is modified by someone else and passed on, we -want its recipients to know that what they have is not the original, so -that any problems introduced by others will not reflect on the original -authors' reputations. - - Finally, any free program is threatened constantly by software -patents. We wish to avoid the danger that redistributors of a free -program will individually obtain patent licenses, in effect making the -program proprietary. To prevent this, we have made it clear that any -patent must be licensed for everyone's free use or not licensed at all. - - The precise terms and conditions for copying, distribution and -modification follow. - - GNU GENERAL PUBLIC LICENSE - TERMS AND CONDITIONS FOR COPYING, DISTRIBUTION AND MODIFICATION - - 0. This License applies to any program or other work which contains -a notice placed by the copyright holder saying it may be distributed -under the terms of this General Public License. The "Program", below, -refers to any such program or work, and a "work based on the Program" -means either the Program or any derivative work under copyright law: -that is to say, a work containing the Program or a portion of it, -either verbatim or with modifications and/or translated into another -language. (Hereinafter, translation is included without limitation in -the term "modification".) Each licensee is addressed as "you". - -Activities other than copying, distribution and modification are not -covered by this License; they are outside its scope. The act of -running the Program is not restricted, and the output from the Program -is covered only if its contents constitute a work based on the -Program (independent of having been made by running the Program). -Whether that is true depends on what the Program does. - - 1. You may copy and distribute verbatim copies of the Program's -source code as you receive it, in any medium, provided that you -conspicuously and appropriately publish on each copy an appropriate -copyright notice and disclaimer of warranty; keep intact all the -notices that refer to this License and to the absence of any warranty; -and give any other recipients of the Program a copy of this License -along with the Program. - -You may charge a fee for the physical act of transferring a copy, and -you may at your option offer warranty protection in exchange for a fee. - - 2. You may modify your copy or copies of the Program or any portion -of it, thus forming a work based on the Program, and copy and -distribute such modifications or work under the terms of Section 1 -above, provided that you also meet all of these conditions: - - a) You must cause the modified files to carry prominent notices - stating that you changed the files and the date of any change. - - b) You must cause any work that you distribute or publish, that in - whole or in part contains or is derived from the Program or any - part thereof, to be licensed as a whole at no charge to all third - parties under the terms of this License. - - c) If the modified program normally reads commands interactively - when run, you must cause it, when started running for such - interactive use in the most ordinary way, to print or display an - announcement including an appropriate copyright notice and a - notice that there is no warranty (or else, saying that you provide - a warranty) and that users may redistribute the program under - these conditions, and telling the user how to view a copy of this - License. (Exception: if the Program itself is interactive but - does not normally print such an announcement, your work based on - the Program is not required to print an announcement.) - -These requirements apply to the modified work as a whole. If -identifiable sections of that work are not derived from the Program, -and can be reasonably considered independent and separate works in -themselves, then this License, and its terms, do not apply to those -sections when you distribute them as separate works. But when you -distribute the same sections as part of a whole which is a work based -on the Program, the distribution of the whole must be on the terms of -this License, whose permissions for other licensees extend to the -entire whole, and thus to each and every part regardless of who wrote it. - -Thus, it is not the intent of this section to claim rights or contest -your rights to work written entirely by you; rather, the intent is to -exercise the right to control the distribution of derivative or -collective works based on the Program. - -In addition, mere aggregation of another work not based on the Program -with the Program (or with a work based on the Program) on a volume of -a storage or distribution medium does not bring the other work under -the scope of this License. - - 3. You may copy and distribute the Program (or a work based on it, -under Section 2) in object code or executable form under the terms of -Sections 1 and 2 above provided that you also do one of the following: - - a) Accompany it with the complete corresponding machine-readable - source code, which must be distributed under the terms of Sections - 1 and 2 above on a medium customarily used for software interchange; or, - - b) Accompany it with a written offer, valid for at least three - years, to give any third party, for a charge no more than your - cost of physically performing source distribution, a complete - machine-readable copy of the corresponding source code, to be - distributed under the terms of Sections 1 and 2 above on a medium - customarily used for software interchange; or, - - c) Accompany it with the information you received as to the offer - to distribute corresponding source code. (This alternative is - allowed only for noncommercial distribution and only if you - received the program in object code or executable form with such - an offer, in accord with Subsection b above.) - -The source code for a work means the preferred form of the work for -making modifications to it. For an executable work, complete source -code means all the source code for all modules it contains, plus any -associated interface definition files, plus the scripts used to -control compilation and installation of the executable. However, as a -special exception, the source code distributed need not include -anything that is normally distributed (in either source or binary -form) with the major components (compiler, kernel, and so on) of the -operating system on which the executable runs, unless that component -itself accompanies the executable. - -If distribution of executable or object code is made by offering -access to copy from a designated place, then offering equivalent -access to copy the source code from the same place counts as -distribution of the source code, even though third parties are not -compelled to copy the source along with the object code. - - 4. You may not copy, modify, sublicense, or distribute the Program -except as expressly provided under this License. Any attempt -otherwise to copy, modify, sublicense or distribute the Program is -void, and will automatically terminate your rights under this License. -However, parties who have received copies, or rights, from you under -this License will not have their licenses terminated so long as such -parties remain in full compliance. - - 5. You are not required to accept this License, since you have not -signed it. However, nothing else grants you permission to modify or -distribute the Program or its derivative works. These actions are -prohibited by law if you do not accept this License. Therefore, by -modifying or distributing the Program (or any work based on the -Program), you indicate your acceptance of this License to do so, and -all its terms and conditions for copying, distributing or modifying -the Program or works based on it. - - 6. Each time you redistribute the Program (or any work based on the -Program), the recipient automatically receives a license from the -original licensor to copy, distribute or modify the Program subject to -these terms and conditions. You may not impose any further -restrictions on the recipients' exercise of the rights granted herein. -You are not responsible for enforcing compliance by third parties to -this License. - - 7. If, as a consequence of a court judgment or allegation of patent -infringement or for any other reason (not limited to patent issues), -conditions are imposed on you (whether by court order, agreement or -otherwise) that contradict the conditions of this License, they do not -excuse you from the conditions of this License. If you cannot -distribute so as to satisfy simultaneously your obligations under this -License and any other pertinent obligations, then as a consequence you -may not distribute the Program at all. For example, if a patent -license would not permit royalty-free redistribution of the Program by -all those who receive copies directly or indirectly through you, then -the only way you could satisfy both it and this License would be to -refrain entirely from distribution of the Program. - -If any portion of this section is held invalid or unenforceable under -any particular circumstance, the balance of the section is intended to -apply and the section as a whole is intended to apply in other -circumstances. - -It is not the purpose of this section to induce you to infringe any -patents or other property right claims or to contest validity of any -such claims; this section has the sole purpose of protecting the -integrity of the free software distribution system, which is -implemented by public license practices. Many people have made -generous contributions to the wide range of software distributed -through that system in reliance on consistent application of that -system; it is up to the author/donor to decide if he or she is willing -to distribute software through any other system and a licensee cannot -impose that choice. - -This section is intended to make thoroughly clear what is believed to -be a consequence of the rest of this License. - - 8. If the distribution and/or use of the Program is restricted in -certain countries either by patents or by copyrighted interfaces, the -original copyright holder who places the Program under this License -may add an explicit geographical distribution limitation excluding -those countries, so that distribution is permitted only in or among -countries not thus excluded. In such case, this License incorporates -the limitation as if written in the body of this License. - - 9. The Free Software Foundation may publish revised and/or new versions -of the General Public License from time to time. Such new versions will -be similar in spirit to the present version, but may differ in detail to -address new problems or concerns. - -Each version is given a distinguishing version number. If the Program -specifies a version number of this License which applies to it and "any -later version", you have the option of following the terms and conditions -either of that version or of any later version published by the Free -Software Foundation. If the Program does not specify a version number of -this License, you may choose any version ever published by the Free Software -Foundation. - - 10. If you wish to incorporate parts of the Program into other free -programs whose distribution conditions are different, write to the author -to ask for permission. For software which is copyrighted by the Free -Software Foundation, write to the Free Software Foundation; we sometimes -make exceptions for this. Our decision will be guided by the two goals -of preserving the free status of all derivatives of our free software and -of promoting the sharing and reuse of software generally. - - NO WARRANTY - - 11. BECAUSE THE PROGRAM IS LICENSED FREE OF CHARGE, THERE IS NO WARRANTY -FOR THE PROGRAM, TO THE EXTENT PERMITTED BY APPLICABLE LAW. EXCEPT WHEN -OTHERWISE STATED IN WRITING THE COPYRIGHT HOLDERS AND/OR OTHER PARTIES -PROVIDE THE PROGRAM "AS IS" WITHOUT WARRANTY OF ANY KIND, EITHER EXPRESSED -OR IMPLIED, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF -MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE. THE ENTIRE RISK AS -TO THE QUALITY AND PERFORMANCE OF THE PROGRAM IS WITH YOU. SHOULD THE -PROGRAM PROVE DEFECTIVE, YOU ASSUME THE COST OF ALL NECESSARY SERVICING, -REPAIR OR CORRECTION. - - 12. IN NO EVENT UNLESS REQUIRED BY APPLICABLE LAW OR AGREED TO IN WRITING -WILL ANY COPYRIGHT HOLDER, OR ANY OTHER PARTY WHO MAY MODIFY AND/OR -REDISTRIBUTE THE PROGRAM AS PERMITTED ABOVE, BE LIABLE TO YOU FOR DAMAGES, -INCLUDING ANY GENERAL, SPECIAL, INCIDENTAL OR CONSEQUENTIAL DAMAGES ARISING -OUT OF THE USE OR INABILITY TO USE THE PROGRAM (INCLUDING BUT NOT LIMITED -TO LOSS OF DATA OR DATA BEING RENDERED INACCURATE OR LOSSES SUSTAINED BY -YOU OR THIRD PARTIES OR A FAILURE OF THE PROGRAM TO OPERATE WITH ANY OTHER -PROGRAMS), EVEN IF SUCH HOLDER OR OTHER PARTY HAS BEEN ADVISED OF THE -POSSIBILITY OF SUCH DAMAGES. - - END OF TERMS AND CONDITIONS - - How to Apply These Terms to Your New Programs - - If you develop a new program, and you want it to be of the greatest -possible use to the public, the best way to achieve this is to make it -free software which everyone can redistribute and change under these terms. - - To do so, attach the following notices to the program. It is safest -to attach them to the start of each source file to most effectively -convey the exclusion of warranty; and each file should have at least -the "copyright" line and a pointer to where the full notice is found. - - - Copyright (C) - - This program is free software; you can redistribute it and/or modify - it under the terms of the GNU General Public License as published by - the Free Software Foundation; either version 2 of the License, or - (at your option) any later version. - - This program is distributed in the hope that it will be useful, - but WITHOUT ANY WARRANTY; without even the implied warranty of - MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the - GNU General Public License for more details. - - You should have received a copy of the GNU General Public License along - with this program; if not, write to the Free Software Foundation, Inc., - 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA. - -Also add information on how to contact you by electronic and paper mail. - -If the program is interactive, make it output a short notice like this -when it starts in an interactive mode: - - Gnomovision version 69, Copyright (C) year name of author - Gnomovision comes with ABSOLUTELY NO WARRANTY; for details type `show w'. - This is free software, and you are welcome to redistribute it - under certain conditions; type `show c' for details. - -The hypothetical commands `show w' and `show c' should show the appropriate -parts of the General Public License. Of course, the commands you use may -be called something other than `show w' and `show c'; they could even be -mouse-clicks or menu items--whatever suits your program. - -You should also get your employer (if you work as a programmer) or your -school, if any, to sign a "copyright disclaimer" for the program, if -necessary. Here is a sample; alter the names: - - Yoyodyne, Inc., hereby disclaims all copyright interest in the program - `Gnomovision' (which makes passes at compilers) written by James Hacker. - - , 1 April 1989 - Ty Coon, President of Vice - -This General Public License does not permit incorporating your program into -proprietary programs. If your program is a subroutine library, you may -consider it more useful to permit linking proprietary applications with the -library. If this is what you want to do, use the GNU Lesser General -Public License instead of this License. - ---------------------------------------------------------------------------- \ No newline at end of file