Skip to content

Commit

Permalink
gh: check copyrights and make Apache only approved
Browse files Browse the repository at this point in the history
  • Loading branch information
kikofernandez committed Nov 21, 2024
1 parent dbbcc28 commit 21e0b4d
Showing 1 changed file with 63 additions and 38 deletions.
101 changes: 63 additions & 38 deletions scripts/scan-code.escript
Original file line number Diff line number Diff line change
Expand Up @@ -38,18 +38,22 @@ cli() ->
handler => fun scancode/1}.

approved() ->
[ ~"mit", ~"agpl-3.0", ~"apache-2.0", ~"boost-1.0", ~"llvm-exception",
~"lgpl-2.1-plus", ~"cc0-1.0", ~"bsd-simplified", ~"bsd-new", ~"pcre",
~"fsf-free", ~"autoconf-exception-3.0", ~"mpl-1.1", ~"public-domain",
~"autoconf-simple-exception", ~"unicode", ~"tcl", ~"gpl-2.0 WITH classpath-exception-2.0",
~"zlib", ~"lgpl-2.0-plus WITH wxwindows-exception-3.1", ~"lgpl-2.0-plus",
~"openssl-ssleay", ~"cc-by-sa-3.0", ~"cc-by-4.0", ~"dco-1.1", ~"fsf-ap",
~"agpl-1.0-plus", ~"agpl-1.0", ~"agpl-3.0-plus", ~"classpath-exception-2.0",
~"ietf-trust"].
[ <<"apache-2.0">> ].

reviewed() ->
[ <<"mit">>, <<"boost-1.0">>, <<"llvm-exception">>,
<<"cc0-1.0">>, <<"bsd-simplified">>, <<"bsd-new">>, <<"pcre">>,
<<"fsf-free">>, <<"autoconf-exception-3.0">>, <<"public-domain">>,
<<"autoconf-simple-exception">>, <<"unicode">>, <<"tcl">>, <<"gpl-2.0 WITH classpath-exception-2.0">>,
<<"zlib">>, <<"lgpl-2.0-plus WITH wxwindows-exception-3.1">>,
<<"openssl-ssleay">>, <<"cc-by-sa-3.0">>, <<"cc-by-4.0">>, <<"dco-1.1">>, <<"fsf-ap">>,
<<"classpath-exception-2.0">>, <<"ietf-trust">> ].

not_approved() ->
[~"gpl", ~"gpl-3.0-plus", ~"gpl-2.0", ~"gpl-1.0-plus", ~"unlicense",
~"erlangpl-1.1", ~"gpl-2.0-plus", ~"null", 'null'].
[<<"gpl">>, <<"gpl-3.0-plus">>, <<"gpl-2.0">>, <<"gpl-1.0-plus">>, <<"unlicense">>,
<<"lgpl-2.0-plus">>, <<"lgpl-2.1-plus">>, <<"agpl-1.0-plus">>, <<"agpl-1.0">>,
<<"agpl-3.0-plus">>, <<"erlangpl-1.1">>, <<"gpl-2.0-plus">>, <<"null">>, <<"agpl-3.0">>,
<<"mpl-1.1">>, 'null'].

scan_option() ->
#{name => scan_option,
Expand Down Expand Up @@ -135,40 +139,48 @@ execute(Command, Config) ->
Licenses = fetch_licenses(folder_path(Config), Json),

Errors = compliance_check(Licenses),
io:format("~n~nResuling Errors: ~p~n~n", [Errors]),

maps:get(sarif, Config) =/= undefined andalso
sarif(maps:get(sarif, Config), Errors),

Errors =/= [] andalso erlang:raise(exit, Errors, []),

ok.

compliance_check(Licenses) when is_list(Licenses) ->
lists:filtermap(fun (License) ->
case compliance_check(License) of
ok ->
false;
{error, Err} ->
{true, Err}
end
end, Licenses);
compliance_check({Path, 'null'=License}) ->
{error, {License, Path, no_license}};
compliance_check({Path, License}) ->
case lists:member(License, not_approved()) of
true ->
{error, {License, Path, license_not_approved}};
false ->
case lists:member(License, approved()) of
false ->
%% this can happen if a license is
%% not in the approve/not_approved list
{error, {License, Path, license_not_recognised}};
true ->
ok
end
end.
lists:foldl(fun ({Path, License, Copyright}, Acc) ->
io:format("Copyright: ~p~n", [Copyright]),
CopyrightResult = check_copyright(Copyright),
LicenseResult = compliance_check(License),
R = lists:foldl(fun (ok, Acc0) -> Acc0;
({error, Msg}, Acc0) -> [{License, Path, Msg} | Acc0]
end, [], [CopyrightResult, LicenseResult]),
R ++ Acc
end, [], Licenses);
compliance_check('null') ->
{error, no_license};
compliance_check(License) ->
Handler = [ {not_approved(), {error, license_not_approved}},
{reviewed(), {error, license_to_be_reviewed}},
{approved(), ok}],
license_check(License, Handler).

check_copyright([]) ->
{error, no_copyright};
check_copyright([#{<<"copyright">> := _} | _]) ->
ok.

license_check(License, Handler) ->
lists:foldl(fun(_, {error, X}=Error) when X =/= license_not_recognised ->
Error;
({Licenses, Msg}, Acc) ->
case lists:member(License, Licenses) of
true ->
Msg;
false ->
Acc
end
end, {error, license_not_recognised}, Handler).


decode(Filename) ->
{ok, Bin} = file:read_file(Filename),
Expand All @@ -177,8 +189,9 @@ decode(Filename) ->
fetch_licenses(FolderPath, #{<<"files">> := Files}) ->
lists:filtermap(fun(#{<<"type">> := <<"file">>,
<<"detected_license_expression">> := License,
<<"copyrights">> := Copyrights,
<<"path">> := Path}) ->
{true, {string:trim(Path, leading, FolderPath), License}};
{true, {string:trim(Path, leading, FolderPath), License, Copyrights}};
(_) ->
false
end, Files).
Expand Down Expand Up @@ -242,19 +255,31 @@ error_type_to_id(ErrorType) ->
base64:encode(integer_to_binary(erlang:phash2(ErrorType))).
error_type_to_text({license_not_recognised, L}) ->
<<"License not recognized: ", L/binary>>;
error_type_to_text({license_to_be_reviewed, L}) ->
<<"License must be reviewed: ", L/binary>>;
error_type_to_text({no_license, _}) ->
<<"License not found">>;
error_type_to_text({license_not_approved, L}) ->
<<"License not approved: ",L/binary>>.
<<"License not approved: ",L/binary>>;
error_type_to_text({no_copyright, L}) ->
<<"No copyright found for license: ", L/binary>>.

error_type_to_name({no_copyright, _}) ->
~"NoCopyright";
error_type_to_name({no_license, _}) ->
~"NoLicense";
error_type_to_name({license_not_recognised, _}) ->
~"NoLicense";
error_type_to_name({license_not_approved, _}) ->
~"UnapprovedLicense".
error_type_to_name({license_to_be_reviewed, _}) ->
~"LicenseMustBeReviewed".
error_type_to_level({no_license, _}) ->
~"warning";
error_type_to_level({no_copyright, _}) ->
~"warning";
error_type_to_level({license_to_be_reviewed, _}) ->
~"warning";
error_type_to_level({license_not_recognised, _}) ->
~"error";
error_type_to_level({license_not_approved, _}) ->
Expand Down

0 comments on commit 21e0b4d

Please sign in to comment.