Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension


Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
53 changes: 53 additions & 0 deletions .github/scripts/create-openvex-pr.sh
Original file line number Diff line number Diff line change
@@ -0,0 +1,53 @@
#!/usr/bin/env sh

## %CopyrightBegin%
##
## SPDX-License-Identifier: Apache-2.0
##
## Copyright Ericsson AB 2026. 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%


REPO=$1
BRANCH_NAME=$2
# Fetch PR data using gh CLI
PR_STATUS=$(gh pr view "$BRANCH_NAME" --repo "$REPO" --json state -q ".state")

if [ $? -ne 0 ]; then
echo "Failed to fetch PR #$BRANCH_NAME from $REPO"
exit 2
fi

git config user.name "github-actions[bot]"
git config user.email "41898282+github-actions[bot]@users.noreply.github.com"

# Check if PR is closed
if [ "$PR_STATUS" = "CLOSED" ] || [ "$PR_STATUS" = "MERGED" ]; then
echo "✅ Pull request #$BRANCH_NAME is CLOSED or MERGED."
git branch "$BRANCH_NAME" master
git checkout "$BRANCH_NAME"
git add make/openvex.table
git add vex
git commit -m "Automatic update of OpenVEX Statements for erlang/otp"
git push --force origin "$BRANCH_NAME"
gh pr create --repo "$REPO" -B master \
--title "Automatic update of OpenVEX Statements for erlang/otp" \
--body "Automatic Action. There is a vulnerability from GH Advisories without a matching OpenVEX statement"
exit 0
else
echo "❌ Pull request #$BRANCH_NAME is OPEN. Create a PR once the PR is closed or merged."
exit 0
fi
158 changes: 126 additions & 32 deletions .github/scripts/otp-compliance.es
Original file line number Diff line number Diff line change
Expand Up @@ -96,17 +96,23 @@
%% VEX MACROS
%%
-define(VexPath, ~"vex/").
-define(OpenVEXTablePath, "make/openvex.table").
-define(ErlangPURL, "pkg:github/erlang/otp").

-define(FOUND_VENDOR_VULNERABILITY_TITLE, "Vendor vulnerability found").
-define(FOUND_VENDOR_VULNERABILITY, lists:append(string:replace(?FOUND_VENDOR_VULNERABILITY_TITLE, " ", "+", all))).

-define(OTP_GH_URI, "https://raw.githubusercontent.com/" ++ ?GH_ACCOUNT ++ "/refs/heads/master/").

%% GH default options
-define(GH_ADVISORIES_OPTIONS, "state=published&direction=desc&per_page=100&sort=updated").

%% Advisories to download from last X years.
-define(GH_ADVISORIES_FROM_LAST_X_YEARS, 5).

%% Defines path of script to create PRs for missing openvex/vulnerabilities
-define(CREATE_OPENVEX_PR_SCRIPT_FILE, ".github/scripts/create-openvex-pr.sh").

%% Sets end point account to fetch information from GH
%% used by `gh` command-line tool.
%% change to your fork for testing, e.g., `kikofernandez/otp`
Expand Down Expand Up @@ -260,7 +266,8 @@ cli() ->
"osv-scan" =>
#{ help =>
"""
Performs vulnerability scanning on vendor libraries
Performs vulnerability scanning on vendor libraries.
As a side effect,

Example:

Expand Down Expand Up @@ -295,10 +302,15 @@ cli() ->
#{ help =>
"""
Download Github Advisories for erlang/otp.
Checks that those are present in OpenVEX statements.
Download OpenVEX statement from erlang/otp for the selected branch.
Checks that those Advisories are present in OpenVEX statements.
Creates PR for any non-present Github Advisory.

Example:
> .github/scripts/otp-compliance.es vex verify -p

""",
arguments => [branch_option(), vex_path_option()],
arguments => [create_pr()],
handler => fun verify_openvex/1
},

Expand Down Expand Up @@ -480,6 +492,13 @@ vex_path_option() ->
help => "Path to folder containing openvex statements, e.g., `vex/`",
long => "-vex-path"}.

create_pr() ->
#{name => create_pr,
short => $p,
type => boolean,
default => false,
help => "Indicates if missing OpenVEX statements create and submit a PR"}.

%%
%% Commands
%%
Expand Down Expand Up @@ -1497,7 +1516,7 @@ create_gh_issue(Version, Title, BodyText) ->
ok.

ignore_vex_cves(Branch, Vulns) ->
OpenVex = get_otp_openvex_file(Branch),
OpenVex = download_otp_openvex_file(Branch),
OpenVex1 = format_vex_statements(OpenVex),

case OpenVex1 of
Expand Down Expand Up @@ -1544,33 +1563,54 @@ format_vex_statements(OpenVex) ->
Result ++ Acc
end, [], Stmts).

get_otp_openvex_file(Branch) ->
OpenVexPath = fetch_openvex_filename(Branch),
read_openvex_file(Branch) ->
_ = create_dir(?VexPath),
OpenVexPath = path_to_openvex_filename(Branch),
OpenVexStr = erlang:binary_to_list(OpenVexPath),
decode(OpenVexStr).

-spec download_otp_openvex_file(Branch :: binary()) -> Json :: map() | EmptyMap :: #{} | no_return().
download_otp_openvex_file(Branch) ->
_ = create_dir(?VexPath),
OpenVexPath = path_to_openvex_filename(Branch),
OpenVexStr = erlang:binary_to_list(OpenVexPath),
GithubURI = "https://raw.githubusercontent.com/" ++ ?GH_ACCOUNT ++ "/refs/heads/master/" ++ OpenVexStr,
GithubURI = get_gh_download_uri(OpenVexStr),

io:format("Checking OpenVex statements in '~s' from~n'~s'...~n", [OpenVexPath, GithubURI]),

ValidURI = "curl -I -Lj --silent " ++ GithubURI ++ " | head -n1 | cut -d' ' -f2",
case string:trim(os:cmd(ValidURI)) of
"200" ->
%% Overrides existing file.
io:format("OpenVex file found.~n~n"),
Command = "curl -LJ " ++ GithubURI ++ " --output " ++ OpenVexStr,
io:format("Proceed to download:~n~s~n~n", [Command]),
os:cmd(Command, #{ exception_on_failure => true }),
decode(OpenVexStr);
E ->
io:format("[~p] No OpenVex file found.~n~n", [E]),
io:format("[~p] No OpenVex statements found for file '~s'.~n~n", [E, OpenVexStr]),
#{}
end.

fetch_openvex_filename(Branch) ->
-spec get_gh_download_uri(String :: list()) -> String :: list().
get_gh_download_uri(File) ->
?OTP_GH_URI ++ File.

-spec create_dir(DirName :: binary()) -> ok | no_return().
create_dir(DirName) ->
case file:make_dir(DirName) of
Result when Result == ok;
Result == {error, eexist} ->
io:format("Directory ~s created successfully.~n", [DirName]);
{error, Reason} ->
fail("Failed to create directory ~s: ~p~n", [DirName, Reason])
end.

-spec path_to_openvex_filename(Branch :: binary()) -> Path :: binary().
path_to_openvex_filename(Branch) ->
_ = valid_scan_branches(Branch),
Version = maint_to_otp_conversion(Branch),
vex_path(Version).
fetch_openvex_filename(Branch, VexPath) ->
_ = valid_scan_branches(Branch),
Version = maint_to_otp_conversion(Branch),
vex_path(VexPath, Version).

maint_to_otp_conversion(Branch) ->
case Branch of
Expand All @@ -1588,6 +1628,7 @@ maint_to_otp_conversion(Branch) ->
OTP
end.

-spec valid_scan_branches(Branch :: binary()) -> ok | no_return().
valid_scan_branches(Branch) ->
case Branch of
~"master" ->
Expand Down Expand Up @@ -2474,28 +2515,80 @@ run_openvex1(VexStmts, VexTableFile, Branch, VexPath) ->
Statements = calculate_statements(VexStmts, VexTableFile, Branch, VexPath),
lists:foreach(fun (St) -> io:format("~ts", [St]) end, Statements).

verify_openvex(#{branch := Branch, vex_path := VexPath}) ->
UpdatedBranch = maint_to_otp_conversion(Branch),
OpenVEX = read_openvex(VexPath, UpdatedBranch),
Advisory = download_advisory_from_branch(UpdatedBranch),
case verify_advisory_against_openvex(OpenVEX, Advisory) of
[] ->
ok;
MissingAdvisories when is_list(MissingAdvisories) ->
create_advisory(MissingAdvisories)
end.

read_openvex(VexPath, Branch) ->
InitVex = fetch_openvex_filename(Branch, VexPath),
case filelib:is_file(InitVex) of
true -> % file exists
decode(InitVex);
verify_openvex(#{create_pr := PR}) ->
Branches = get_supported_branches(),
io:format("Sync ~p~n", [Branches]),
_ = lists:foreach(
fun (Branch) ->
case verify_openvex_advisories(Branch) of
[] ->
io:format("No new advisories nor OpenVEX statements created for '~s'.", [Branch]);
MissingAdvisories ->
io:format("Missing Advisories:~n~p~n~n", [MissingAdvisories]),
case PR of
false ->
io:format("To automatically update openvex.table and create a PR run:~n" ++
".github/scripts/otp-compliance.es vex verify -b ~s -p~n~n", [Branch]);
true ->
Advs = create_advisory(MissingAdvisories),
_ = update_openvex_otp_table(Branch, Advs),
BranchStr = erlang:binary_to_list(Branch),
_ = cmd(".github/scripts/otp-compliance.es vex run -b "++ BranchStr ++ " | bash")
end
end
end, Branches),
case PR of
true ->
cmd(".github/scripts/create-openvex-pr.sh " ++ ?GH_ACCOUNT ++ " vex");
false ->
throw(file_not_found)
ok
end.

verify_openvex_advisories(Branch) ->
OpenVEX = read_openvex_file(Branch),
Advisory = download_advisory_from_branch(Branch),
verify_advisory_against_openvex(OpenVEX, Advisory).

-spec get_supported_branches() -> [Branches :: binary()].
get_supported_branches() ->
Branches = cmd(".github/scripts/get-supported-branches.sh"),
BranchesBin = json:decode(erlang:list_to_binary(Branches)),
io:format("~p~n~p~n", [Branches, BranchesBin]),
lists:filtermap(fun (<<"maint-", _/binary>>=OTP) -> {true, maint_to_otp_conversion(OTP)};
(_) -> false
end, BranchesBin).

create_advisory(Advisories) ->
io:format("Missing:~n~p~n~n", [Advisories]).
lists:foldl(fun (Adv, Acc) ->
create_openvex_otp_entries(Adv) ++ Acc
end, [], Advisories).

create_openvex_otp_entries(#{'CVE' := CVEId,
'appName' := AppName,
'affectedVersions' := AffectedVersions,
'fixedVersions' := FixedVersions}) ->
AppFixedVersions = lists:map(fun (Ver) -> create_app_purl(AppName, Ver) end, FixedVersions),
lists:map(fun (Affected) ->
Purl = create_app_purl(AppName, Affected),
create_openvex_app_entry(Purl, CVEId, AppFixedVersions)
end, AffectedVersions).

create_app_purl(AppName, Version) when is_binary(AppName), is_binary(Version) ->
<<"pkg:otp/", AppName/binary, "@", Version/binary>>.

create_openvex_app_entry(Purl, CVEId, FixedVersions) ->
#{Purl => CVEId,
~"status" =>
#{ ~"affected" => iolist_to_binary(io_lib:format("Update to any of the following versions: ~s", [FixedVersions])),
~"fixed" => FixedVersions}}.

update_openvex_otp_table(Branch, Advs) ->
Path = ?OpenVEXTablePath,
io:format("OpenVEX Statements:~n~p~n~n", [Advs]),
#{Branch := Statements}=Table = decode(Path),
UpdatedTable = Table#{Branch := Advs ++ Statements},
io:format("Update table:~n~p~n", [UpdatedTable]),
file:write_file(Path, json:format(UpdatedTable)).

generate_gh_link(Part) ->
"\"/repos/erlang/otp/security-advisories?" ++ Part ++ "\"".
Expand Down Expand Up @@ -2886,7 +2979,8 @@ format_vexctl(VexPath, Versions, CVE, S) when S =:= ~"fixed";
[VexPath, Versions, CVE, S]).


-spec fetch_otp_purl_versions(OTP :: binary(), FixedVersions :: [binary()] ) -> OTPAppVersions :: binary().
-spec fetch_otp_purl_versions(OTP :: binary(), FixedVersions :: [binary()] ) ->
{AffectedPurls :: binary(), FixedPurls :: binary()} | false.
fetch_otp_purl_versions(<<?ErlangPURL, _/binary>>, _FixedVersions) ->
%% ignore
false;
Expand Down
59 changes: 59 additions & 0 deletions .github/workflows/openvex-sync.yml
Original file line number Diff line number Diff line change
@@ -0,0 +1,59 @@
## %CopyrightBegin%
##
## SPDX-License-Identifier: Apache-2.0
##
## Copyright Ericsson AB 2024-2025. All Rights Reserved.
##
## Licensed under the Apache License, Version 2.0 (the "License");
## you may not use this file except in compliance with the License.
## You may obtain a copy of the License at
##
## http://www.apache.org/licenses/LICENSE-2.0
##
## Unless required by applicable law or agreed to in writing, software
## distributed under the License is distributed on an "AS IS" BASIS,
## WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
## See the License for the specific language governing permissions and
## limitations under the License.
##
## %CopyrightEnd%

## Periodically syncs OpenVEX files against Erlang OTP Securities,
## creating an automatic PR with the missing published securities.
name: OpenVEX Securities Syncing

on:
workflow_dispatch:
schedule:
- cron: 0 1 * * *

permissions:
contents: read

jobs:
run-scheduled-openvex-sync:
runs-on: ubuntu-latest
permissions:
security-events: read
actions: write
contents: write
pull-requests: write
steps:
- uses: actions/checkout@11bd71901bbe5b1630ceea73d27597364c9af683 # ratchet:actions/[email protected]
with:
ref: 'master' # '' = default branch

- uses: erlef/setup-beam@5304e04ea2b355f03681464e683d92e3b2f18451 # racket:actions/checkout@v1
with:
otp-version: '28'

- uses: openvex/setup-vexctl@e85ca48f3c8a376289f6476129d59cda82147e71 # ratchet:openvex/[email protected]
with:
vexctl-release: '0.3.0'

- name: 'Open OpenVEX Pull Requests for newly released vulnerabilities'
env:
GH_TOKEN: ${{ github.token }}
REPO: ${{ github.repository }}
run: |
.github/scripts/otp-compliance.es vex verify -p
5 changes: 4 additions & 1 deletion .github/workflows/osv-scanner-scheduled.yml
Original file line number Diff line number Diff line change
Expand Up @@ -57,8 +57,11 @@ jobs:
type: ${{ fromJson(needs.schedule-scan.outputs.versions) }}
fail-fast: false
permissions:
actions: write
security-events: read
issues: write
actions: write
contents: write
pull-requests: write
steps:
# this call to a workflow_dispatch ref=master is important because
# using ref={{matrix.type}} would trigger the workflow
Expand Down
2 changes: 0 additions & 2 deletions .github/workflows/reusable-vendor-vulnerability-scanner.yml
Original file line number Diff line number Diff line change
Expand Up @@ -115,8 +115,6 @@ jobs:
chmod +x otp-compliance.es
cp otp-compliance.es /home/runner/work/otp/otp/.github/scripts/otp-compliance.es
cd /home/runner/work/otp/otp && \
mkdir -p vex && \
.github/scripts/otp-compliance.es sbom osv-scan \
--version ${{ inputs.version }} \
--fail_if_cve ${{ inputs.fail_if_cve }}
.github/scripts/otp-compliance.es vex verify -b ${{ inputs.version }}
Loading
Loading