File 0345-gh-Migrate-PR-test-logs-and-docs-to-erlang.org.patch of Package erlang

From 65c32746369d4c6fcd374bd02980f420d6e4337e Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Lukas=20Backstr=C3=B6m?= <lukas@erlang.org>
Date: Mon, 17 Feb 2025 13:34:00 +0100
Subject: [PATCH] gh: Migrate PR test logs and docs to erlang.org

Github has a limitation of 10GB of data that you can have in
a github pages instance, and we constantly hit that limit for
our PRs. So the PR viewing service has not been migrated to
erlang.org. This commit redirects the links and removes the
infrastructure to upload PR results.
---
 .github/scripts/pr-comment.js          |   4 +-
 .github/scripts/sync-github-prs.es     | 252 -------------------------
 .github/workflows/pr-comment.yaml      |  31 ---
 .github/workflows/sync-github-prs.yaml |  66 -------
 4 files changed, 2 insertions(+), 351 deletions(-)
 delete mode 100755 .github/scripts/sync-github-prs.es
 delete mode 100644 .github/workflows/sync-github-prs.yaml

diff --git a/.github/scripts/pr-comment.js b/.github/scripts/pr-comment.js
index c1d178f45f..9bc0dc8d8f 100644
--- a/.github/scripts/pr-comment.js
+++ b/.github/scripts/pr-comment.js
@@ -102,8 +102,8 @@ To speed up review, make sure that you have read [Contributing to Erlang/OTP](${
 See the [TESTING](${repoURL}/blob/master/HOWTO/TESTING.md) and [DEVELOPMENT](${repoURL}/blob/master/HOWTO/DEVELOPMENT.md) HowTo guides for details about how to run test locally.
 
 ## Artifacts
-* ` + (ct_logs ? `[Complete CT logs](https://erlang.github.io/prs/${pr_number}/ct_logs/index.html) ([Download Logs](${nightlyURL(ct_logs)}))` : "No CT logs found") + `
-* ` + (html_docs ? `[HTML Documentation](https://erlang.github.io/prs/${pr_number}/doc/index.html) ([Download HTML Docs](${nightlyURL(html_docs)}))` : "No HTML docs found") + `
+* ` + (ct_logs ? `[Complete CT logs](https://erlang.org/github-pr/prs/${pr_number}/ct_logs/index.html) ([Download Logs](${nightlyURL(ct_logs)}))` : "No CT logs found") + `
+* ` + (html_docs ? `[HTML Documentation](https://erlang.org/github-pr/prs/${pr_number}/doc/index.html) ([Download HTML Docs](${nightlyURL(html_docs)}))` : "No HTML docs found") + `
 * ` + (win_exe ? `[Windows Installer](${nightlyURL(win_exe)})` : "No Windows Installer found") + `
 
 // Erlang/OTP Github Action Bot
diff --git a/.github/scripts/sync-github-prs.es b/.github/scripts/sync-github-prs.es
deleted file mode 100755
index ccfbd6cc79..0000000000
--- a/.github/scripts/sync-github-prs.es
+++ /dev/null
@@ -1,252 +0,0 @@
-#!/usr/bin/env escript
-%%! -pa jsx/_build/default/lib/jsx/ebin/
-
-%% -*- erlang -*-
-
-%%
-%% %CopyrightBegin%
-%%
-%% Copyright Ericsson AB 2024. All Rights Reserved.
-%%
-%% Licensed under the Apache License, Version 2.0 (the "License");
-%% you may not use this file except in compliance with the License.
-%% You may obtain a copy of the License at
-%%
-%%     http://www.apache.org/licenses/LICENSE-2.0
-%%
-%% Unless required by applicable law or agreed to in writing, software
-%% distributed under the License is distributed on an "AS IS" BASIS,
-%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
-%% See the License for the specific language governing permissions and
-%% limitations under the License.
-%%
-%% %CopyrightEnd%
-
-%% This scripts downloads the docs + test results from an otp repo
-%% into the Target folder. It tries its best to not create too large
-%% files so that gh will still be happy with us when this is published to
-%% gh pages
--module('sync-github-prs').
--mode(compile).
-
-main([Repo, Target]) ->
-
-    io:format("Updating PRs in ~ts, current PRs are: ~p~n",
-              [Target, filelib:wildcard(filename:join(Target,"*"))]),
-
-    AllOpenPrs = ghapi("gh api --paginate -X GET /repos/"++Repo++"/pulls -f state=open"),
-    %% Download all updates, there really should not be any to download as they
-    %% are updated when a PR is updated, but we do it anyways just to be safe.
-    handle_prs(Repo, Target,AllOpenPrs),
-
-    %% Delete any PRs that have been closed
-    {ok, AllPrs} = file:list_dir(Target),
-    lists:foreach(
-      fun(PRNo) ->
-              case lists:search(
-                     fun(#{ <<"number">> := No }) ->
-                        No =:= list_to_integer(PRNo)
-                     end, AllOpenPrs) of
-                  {value, _} ->
-                      ok;
-                  false ->
-                      cmd("rm -rf " ++ filename:join(Target,PRNo))
-              end
-      end, AllPrs),
-
-    purge_prs(Target);
-
-main([Repo, Target, PRNo]) ->
-    handle_prs(Repo, Target, [ghapi("gh api /repos/"++Repo++"/pulls/"++PRNo)]).
-
-handle_prs(Repo, Target, AllPRs) ->
-
-    %% We fetch all runs for the main.yaml repo. This takes a while,
-    %% but for some reason when we try to filter results using either
-    %%   -f event=pull_request or -f branch=Ref github decides to not
-    %% return all the runs.... So we do it the slow way...
-    AllRuns = ghapi(["gh api --paginate -X GET /repos/"++Repo++"/actions/workflows/main.yaml/runs"]),
-
-    [handle_pr(Repo, Target, PR, AllRuns) || PR <- AllPRs],
-
-    %% Remove all links and files > 50MB
-    cmd(["find ",Target," -type l -exec rm -f {} \\;"]),
-    cmd(["find ",Target," -type f -size +50M -exec rm -f {} \\;"]),
-
-    ok.
-
-%% In order to get the latest gh actions run for a PR, we have to first list
-%% all workflow runs for that branch, and then look for a matching sha with the
-%% current top of the PR. Github does not have any API to find it any other way.
-%% See https://github.community/t/retrieve-workflow-id-for-a-given-pr/199745/4
-%%   for a discussion about this.
-%%
-handle_pr(_Repo, Target,
-          #{ <<"number">> := Number,
-             <<"head">> := #{ <<"ref">> := _Ref, <<"sha">> := Sha } },
-          Runs) ->
-    PRDir = filename:join(Target,integer_to_list(Number)),
-    case lists:search(
-           fun(#{ <<"head_sha">> := HeadSha, <<"status">> := Status }) ->
-                   string:equal(HeadSha, Sha) andalso string:equal(Status, <<"completed">>)
-           end, maps:get(<<"workflow_runs">>, Runs)) of
-        {value, Run} ->
-            Ident = integer_to_list(
-                      erlang:phash2(
-                        {maps:get(<<"id">>,Run), ?MODULE:module_info(md5)})),
-            io:format("Checking for ~ts~n", [filename:join(PRDir, Ident)]),
-            case file:read_file_info(filename:join(PRDir, Ident)) of
-                {error, enoent} ->
-                    io:format("Did not find ~ts. Files in dir are: ~p~n",
-                              [filename:join(PRDir, Ident),
-                               filelib:wildcard(filename:join(PRDir, "*"))]),
-                    cmd("rm -rf "++PRDir),
-                    ok = file:make_dir(PRDir),
-                    ok = file:write_file(filename:join(PRDir,Ident), integer_to_list(Number)),
-
-                    #{ <<"artifacts">> := Artifacts } =
-                        ghapi(["gh api --paginate -X GET ",maps:get(<<"artifacts_url">>, Run)]),
-
-                    lists:foreach(
-                      fun(#{ <<"name">> := <<"test_results">>, <<"archive_download_url">> := Url }) ->
-                              cmd(["gh api ", unicode:characters_to_list(Url), " > /tmp/test_results.zip"]),
-                              cmd("unzip -d /tmp/test_results /tmp/test_results.zip"),
-                              cmd(["tar xvzf /tmp/test_results/test_results.tar.gz "
-                                   "-C ",PRDir," make_test_dir/ct_logs --strip-components=1"]),
-                              cmd("rm -rf /tmp/test_results*");
-                         (#{ <<"name">> := <<"otp_doc_html">>, <<"archive_download_url">> := Url }) ->
-                              cmd(["gh api ", unicode:characters_to_list(Url), " > /tmp/otp_doc_html.zip"]),
-                              cmd("unzip -d /tmp/otp_doc_html /tmp/otp_doc_html.zip"),
-                              cmd(["tar xvzf /tmp/otp_doc_html/otp_doc_html.tar.gz -C ",PRDir]),
-                              cmd(["find ",PRDir," -name '*.pdf' -exec rm -f {} \\;"]),
-                              cmd("rm -rf /tmp/otp_doc_html*");
-                         (_) ->
-                              ok
-                      end, Artifacts),
-                    CTLogsIndex = filename:join([PRDir,"ct_logs","index.html"]),
-                    case file:read_file_info(CTLogsIndex) of
-                        {ok, _} ->
-                            CTSuiteFiles = filename:join([PRDir,"ct_logs","ct_run*","*.logs","run.*","suite.log"]),
-                            lists:foreach(fun purge_suite/1, filelib:wildcard(CTSuiteFiles));
-                        _ ->
-                             ok = filelib:ensure_dir(CTLogsIndex),
-                             ok = file:write_file(CTLogsIndex, ["No test logs found for ", Sha])
-                    end,
-                    %% If we ever want to de-duplicate the docs, this command will create a
-                    %% stable md5sum.
-                    %% (cd $dir && find doc lib erts-* -type f \! -path "lib/jinterface-*" \! -name erlresolvelinks.js \! -name index.html \! -name release_notes.html \! -name users_guide.html \! -name internal_docs.html \! -name "*.eix" -exec md5sum {} \;) | sort -k 2 | awk "{print $1}" | md5sum
-                    %% where $dir is the pr directory.
-                    DocIndex = filename:join([PRDir,"doc","index.html"]),
-                    case file:read_file_info(DocIndex) of
-                        {ok, _} -> ok;
-                        _ -> ok = filelib:ensure_dir(DocIndex),
-                             ok = file:write_file(DocIndex, ["No documentation found for ", Sha])
-                    end;
-                {ok,_} ->
-                    ok
-            end;
-        false ->
-            ok
-    end.
-
-%% We truncate the logs of all testcases of any suite that did not have any failures
-purge_suite(SuiteFilePath) ->
-    {ok, SuiteFile} = file:read_file(SuiteFilePath),
-    SuiteDir = filename:dirname(SuiteFilePath),
-    Placeholder = "<html><body>github truncated successful testcase</body></html>",
-    case re:run(SuiteFile,"^=failed\s*\([0-9]+\)$",[multiline,{capture,all_but_first,binary}]) of
-        {match,[<<"0">>]} ->
-            io:format("Purging logs from: ~ts~n",[SuiteDir]),
-            ok = file:del_dir_r(filename:join(SuiteDir,"log_private")),
-            lists:foreach(
-              fun(File) ->
-                      case filename:basename(File) of
-                          "suite" ++ _ ->
-                              ok;
-                          "unexpected_io" ++_ ->
-                              ok;
-                          "cover.html" ->
-                              ok;
-                          _Else ->
-                              file:write_file(File,Placeholder)
-                      end
-              end, filelib:wildcard(filename:join(SuiteDir,"*.html")));
-        _FailedTestcases ->
-            io:format("Purging logs from: ~ts~n",[SuiteDir]),
-            lists:foreach(
-              fun(File) ->
-                      {ok, B} = file:read_file(File),
-                      case re:run(B,"^=== Config value:",[multiline]) of
-                          {match,_} ->
-                              case re:run(B,"^=== successfully completed test case",[multiline]) of
-                                  {match, _} ->
-                                      file:write_file(File,Placeholder);
-                                  nomatch ->
-                                      ok
-                              end;
-                          nomatch ->
-                              ok
-                      end
-              end, filelib:wildcard(filename:join(SuiteDir,"*.html")))
-    end.
-
-%% If we have more the 10 GB of PR data we need to remove some otherwise
-%% github actions will not work them. So we purge the largest files until we
-%% reach the 10 GB limit.
-purge_prs(Target) ->
-    %% Start by deleting all data from common_test test runs as they are huge.
-    os:cmd("rm -rf "++Target++"*/ct_logs/ct_run*/*common_test_test*/run*/log_private/ct_run*"),
-    Files = string:split(cmd("find " ++ Target ++ " -type f -a "
-                             "\\! -name suite.log.html -exec du -a {} \\+"),"\n",all),
-    SortedFiles =
-        lists:sort(fun([A|_],[B|_]) ->
-                               binary_to_integer(A) >= binary_to_integer(B)
-                   end, [string:split(F,"\t") || F <- Files, F =/= <<>>]),
-    purge_prs(SortedFiles, Target, get_directory_size(Target)).
-purge_prs(Files, Target, Size) when Size > 10_000_000_000 ->
-    {H,T} = lists:split(10, Files),
-    [file:write_file(File, io_lib:format("Large file (~p bytes) truncated", [Sz]))
-     || [Sz, File] <- H],
-    purge_prs(T, Target, get_directory_size(Target));
-purge_prs(_, _, _) ->
-    ok.
-
-get_directory_size(Dir) ->
-    binary_to_integer(hd(string:split(cmd("du -b --max-depth=0 " ++ Dir),"\t"))).
-
-
-ghapi(CMD) ->
-    decode(cmd(CMD)).
-
-decode(Data) ->
-    try jsx:decode(Data,[{return_maps, true}, return_tail]) of
-        {with_tail, Json, <<>>} ->
-            Json;
-        {with_tail, Json, Tail} when is_map(Json) ->
-            [Key] = maps:keys(maps:remove(<<"total_count">>, Json)),
-            #{ Key => lists:flatmap(
-                        fun(J) -> maps:get(Key, J) end,
-                        [Json | decodeTail(Tail)])
-                       };
-        {with_tail, Json, Tail} when is_list(Json) ->
-            lists:concat([Json | decodeTail(Tail)])
-    catch E:R:ST ->
-            io:format("Failed to decode: ~ts",[Data]),
-            erlang:raise(E,R,ST)
-    end.
-
-decodeTail(Data) ->
-    try jsx:decode(Data,[{return_maps, true}, return_tail]) of
-        {with_tail, Json, <<>>} ->
-            [Json];
-        {with_tail, Json, Tail} ->
-            [Json | decodeTail(Tail)]
-    catch E:R:ST ->
-            io:format("Failed to decode: ~ts",[Data]),
-            erlang:raise(E,R,ST)
-    end.
-
-cmd(CMD) ->
-    ListCmd = unicode:characters_to_list(CMD),
-    io:format("cmd: ~ts~n",[ListCmd]),
-    unicode:characters_to_binary(os:cmd(ListCmd)).
diff --git a/.github/workflows/pr-comment.yaml b/.github/workflows/pr-comment.yaml
index b1e8dd354a..d53b32b981 100644
--- a/.github/workflows/pr-comment.yaml
+++ b/.github/workflows/pr-comment.yaml
@@ -109,12 +109,6 @@ jobs:
              echo "HAS_TEST_ARTIFACTS=false" >> $GITHUB_OUTPUT
            fi
 
-      - uses: actions/checkout@11bd71901bbe5b1630ceea73d27597364c9af683 # ratchet:actions/checkout@v4.2.2
-        with:
-          token: ${{ secrets.ERLANG_TOKEN }}
-          repository: 'erlang/erlang.github.io'
-          path: erlang.github.io
-
       - name: Publish CT Test Results
         uses: EnricoMi/publish-unit-test-result-action@afb2984f4d89672b2f9d9c13ae23d53779671984 # ratchet:EnricoMi/publish-unit-test-result-action@v2.19.0
         if: steps.extract.outputs.HAS_TEST_ARTIFACTS == 'true'
@@ -125,31 +119,6 @@ jobs:
           check_name: "CT Test Results"
           files: "artifacts/**/*.xml"
 
-      - name: Upload PR to github pages
-        env:
-          GITHUB_TOKEN: ${{secrets.GITHUB_TOKEN}}
-        run: |
-           git clone https://github.com/talentdeficit/jsx
-           (cd jsx && rebar3 compile)
-           mkdir -p "${GITHUB_WORKSPACE}/erlang.github.io/prs/"
-           .github/scripts/sync-github-prs.es erlang/otp \
-             "${GITHUB_WORKSPACE}/erlang.github.io/prs/" \
-             "${{ needs.pr-number.outputs.result }}"
-
-      - name: Deploy to github pages 🚀
-        run: |
-          cd erlang.github.io
-          set -x
-          git config user.name github-actions
-          git config user.email github-actions@github.com
-          git add .
-          git add -u
-          git update-index --refresh
-          if ! git diff-index --quiet HEAD --; then
-            git commit -m "Update github pages content"
-            git push origin master
-          fi
-
         ## Append some useful links and tips to the test results posted by
         ## Publish CT Test Results
       - uses: actions/github-script@60a0d83039c74a4aee543508d2ffcb1c3799cdea # ratchet:actions/github-script@v7.0.1
diff --git a/.github/workflows/sync-github-prs.yaml b/.github/workflows/sync-github-prs.yaml
deleted file mode 100644
index 7cfbd8da37..0000000000
--- a/.github/workflows/sync-github-prs.yaml
+++ /dev/null
@@ -1,66 +0,0 @@
-## %CopyrightBegin%
-##
-## Copyright Ericsson AB 2024. All Rights Reserved.
-##
-## Licensed under the Apache License, Version 2.0 (the "License");
-## you may not use this file except in compliance with the License.
-## You may obtain a copy of the License at
-##
-##     http://www.apache.org/licenses/LICENSE-2.0
-##
-## Unless required by applicable law or agreed to in writing, software
-## distributed under the License is distributed on an "AS IS" BASIS,
-## WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
-## See the License for the specific language governing permissions and
-## limitations under the License.
-##
-## %CopyrightEnd%
-
-name: Sync all github prs with erlang.github.io/prs/
-
-## Sync all github prs twice a day
-on:
-  workflow_dispatch:
-  schedule:
-  ## In UTC
-  - cron: '0 */4 * * *'
-
-permissions:
-  contents: read
-
-jobs:
-
-  sync-prs:
-    if: github.repository == 'erlang/otp'
-    concurrency: erlang.github.io-deploy
-    runs-on: ubuntu-20.04
-    steps:
-      - uses: actions/checkout@11bd71901bbe5b1630ceea73d27597364c9af683 # ratchet:actions/checkout@v4.2.2
-      - uses: actions/checkout@11bd71901bbe5b1630ceea73d27597364c9af683 # ratchet:actions/checkout@v4.2.2
-        with:
-          token: ${{ secrets.ERLANG_TOKEN }}
-          repository: 'erlang/erlang.github.io'
-          path: erlang.github.io
-      - name: Update PRs
-        env:
-          GITHUB_TOKEN: ${{secrets.GITHUB_TOKEN}}
-        run: |
-            git clone https://github.com/talentdeficit/jsx
-            (cd jsx && rebar3 compile)
-            mkdir -p "${GITHUB_WORKSPACE}/erlang.github.io/prs/"
-            touch "${GITHUB_WORKSPACE}/erlang.github.io/.nojekyll"
-            .github/scripts/sync-github-prs.es erlang/otp "${GITHUB_WORKSPACE}/erlang.github.io/prs/"
-
-      - name: Deploy to github pages 🚀
-        run: |
-          cd erlang.github.io
-          set -x
-          git config user.name github-actions
-          git config user.email github-actions@github.com
-          git add .
-          git add -u
-          git update-index --refresh
-          if ! git diff-index --quiet HEAD --; then
-            git commit -m "Update github pages content"
-            git push origin master
-          fi
-- 
2.43.0

openSUSE Build Service is sponsored by