[Git][ghc/ghc][wip/T18857] 4 commits: gitlab-ci: Run LLVM job on appropriately-labelled MRs

Moritz Angermann gitlab at gitlab.haskell.org
Thu Nov 19 02:26:44 UTC 2020



Moritz Angermann pushed to branch wip/T18857 at Glasgow Haskell Compiler / GHC


Commits:
0c4c0082 by Ben Gamari at 2020-11-19T10:25:11+08:00
gitlab-ci: Run LLVM job on appropriately-labelled MRs

Namely, those marked with the ~"LLVM backend" label

- - - - -
03b9d65f by Ben Gamari at 2020-11-19T10:25:11+08:00
gitlab-ci: Run LLVM builds on Debian 10

The current Debian 9 image doesn't provide LLVM 7.

- - - - -
09ce35c7 by Ben Gamari at 2020-11-19T10:25:11+08:00
hadrian: Don't use -fllvm to bootstrap under LLVM flavour

Previously Hadrian's LLVM build flavours would use `-fllvm` for all
invocations, even those to stage0 GHC. This meant that we needed to keep
two LLVM versions around in all of the CI images. Moreover, it differed
from the behavior of the old make build system's llvm flavours.

Change this to reflect the behavior of the `make` build system, using
`-fllvm` only with the stage1 and stage2 compilers.

- - - - -
5807df4f by Ben Gamari at 2020-11-19T10:25:12+08:00
CmmToLlvm: Declare signature for memcmp

Otherwise `opt` fails with:

    error: use of undefined value '@memcmp$def'

fixup ShortText & SymbolExtras

- - - - -


9 changed files:

- .gitlab-ci.yml
- compiler/GHC/CmmToLlvm/Base.hs
- hadrian/src/Settings/Flavours/Llvm.hs
- libraries/ghc-boot/GHC/Data/ShortText.hs
- rts/LinkerInternals.h
- rts/linker/Elf.c
- rts/linker/SymbolExtras.c
- rts/linker/elf_reloc_aarch64.c
- testsuite/driver/testlib.py


Changes:

=====================================
.gitlab-ci.yml
=====================================
@@ -659,22 +659,6 @@ validate-x86_64-linux-deb9-debug:
     when: always
     expire_in: 2 week
 
-# Disabled to alleviate CI load
-.validate-x86_64-linux-deb9-llvm:
-  extends: .build-x86_64-linux-deb9
-  stage: full-build
-  variables:
-    BUILD_FLAVOUR: perf-llvm
-    TEST_ENV: "x86_64-linux-deb9-llvm"
-
-nightly-x86_64-linux-deb9-llvm:
-  <<: *nightly
-  extends: .build-x86_64-linux-deb9
-  stage: full-build
-  variables:
-    BUILD_FLAVOUR: perf-llvm
-    TEST_ENV: "x86_64-linux-deb9-llvm"
-
 validate-x86_64-linux-deb9-integer-simple:
   extends: .build-x86_64-linux-deb9
   stage: full-build
@@ -759,6 +743,23 @@ release-x86_64-linux-deb10-dwarf:
     TEST_ENV: "x86_64-linux-deb10-dwarf"
     BIN_DIST_PREP_TAR_COMP: "ghc-x86_64-deb10-linux-dwarf.tar.xz"
 
+validate-x86_64-linux-deb10-llvm:
+  extends: .build-x86_64-linux-deb10
+  stage: full-build
+  rules:
+    - if: '$CI_MERGE_REQUEST_LABELS =~ /.*LLVM backend.*/'
+  variables:
+    BUILD_FLAVOUR: perf-llvm
+    TEST_ENV: "x86_64-linux-deb10-llvm"
+
+nightly-x86_64-linux-deb10-llvm:
+  <<: *nightly
+  extends: .build-x86_64-linux-deb10
+  stage: full-build
+  variables:
+    BUILD_FLAVOUR: perf-llvm
+    TEST_ENV: "x86_64-linux-deb10-llvm"
+
 #################################
 # x86_64-linux-ubuntu 20.04
 #################################


=====================================
compiler/GHC/CmmToLlvm/Base.hs
=====================================
@@ -476,6 +476,8 @@ ghcInternalFunctions :: LlvmM ()
 ghcInternalFunctions = do
     platform <- getPlatform
     let w = llvmWord platform
+        cint = LMInt $ widthInBits $ cIntWidth platform
+    mk "memcmp" cint [i8Ptr, i8Ptr, w]
     mk "memcpy" i8Ptr [i8Ptr, i8Ptr, w]
     mk "memmove" i8Ptr [i8Ptr, i8Ptr, w]
     mk "memset" i8Ptr [i8Ptr, w, w]


=====================================
hadrian/src/Settings/Flavours/Llvm.hs
=====================================
@@ -25,5 +25,5 @@ mkLlvmFlavour :: Flavour -> Flavour
 mkLlvmFlavour flav = flav
     { name = name flav ++ "-llvm"
     , args = mconcat [ args flav
-                     , builder Ghc ? arg "-fllvm" ]
+                     , notStage0 ? builder Ghc ? arg "-fllvm" ]
     }


=====================================
libraries/ghc-boot/GHC/Data/ShortText.hs
=====================================
@@ -1,6 +1,22 @@
-{-# LANGUAGE BangPatterns, MagicHash, UnboxedTuples, GeneralizedNewtypeDeriving, DerivingStrategies #-}
+{-# LANGUAGE BangPatterns, MagicHash, UnboxedTuples, GeneralizedNewtypeDeriving, DerivingStrategies, CPP #-}
 {-# OPTIONS_GHC -O2 -funbox-strict-fields #-}
-
+-- gross hack: we manuvered ourselves into a position where we can't boot GHC with a LLVM based GHC anymore.
+-- LLVM based GHC's fail to compile memcmp ffi calls.  These end up as memcmp$def in the llvm ir, however we
+-- don't have any prototypes and subsequently the llvm toolchain chokes on them.  Since 7fdcce6d, we use
+-- ShortText for the package database.  This however introduces this very module; which through inlining ends
+-- up bringing memcmp_ByteArray from bytestring:Data.ByteString.Short.Internal into scope, which results in
+-- the memcmp call we choke on.
+--
+-- The solution thusly is to force late binding via the linker instead of inlining when comping with the
+-- bootstrap compiler.  This will produce a slower (slightly less optimised) stage1 compiler only.
+--
+-- See issue 18857. hsyl20 deserves credit for coming up with the idea for the soltuion.
+--
+-- This can be removed when we exit the boot compiler window. Thus once we drop GHC-9.2 as boot compiler,
+-- we can drop this code as well.
+#if GHC_STAGE < 1
+{-# OPTIONS_GHC -fignore-interface-pragmas #-}
+#endif
 -- |
 -- An Unicode string for internal GHC use. Meant to replace String
 -- in places where being a lazy linked is not very useful and a more


=====================================
rts/LinkerInternals.h
=====================================
@@ -141,7 +141,7 @@ typedef struct _Segment {
     int n_sections;
 } Segment;
 
-#if defined(powerpc_HOST_ARCH) || defined(x86_64_HOST_ARCH)
+#if defined(powerpc_HOST_ARCH) || defined(x86_64_HOST_ARCH) || defined(aarch64_HOST_ARCH)
 #define NEED_SYMBOL_EXTRAS 1
 #endif
 


=====================================
rts/linker/Elf.c
=====================================
@@ -940,7 +940,7 @@ ocGetNames_ELF ( ObjectCode* oc )
                    symbol->addr = (SymbolAddr*)(
                            (intptr_t) oc->sections[secno].start +
                            (intptr_t) symbol->elf_sym->st_value);
-
+                   ASSERT(symbol->addr != 0x0);
                    if (ELF_ST_BIND(symbol->elf_sym->st_info) == STB_LOCAL) {
                        isLocal = true;
                        isWeak = false;
@@ -1867,6 +1867,7 @@ ocResolve_ELF ( ObjectCode* oc )
 #endif
                 ASSERT(symbol->elf_sym->st_name == 0);
                 ASSERT(symbol->elf_sym->st_value == 0);
+                ASSERT(0x0 != oc->sections[ secno ].start);
                 symbol->addr = oc->sections[ secno ].start;
             }
         }
@@ -1940,6 +1941,7 @@ int ocRunInit_ELF( ObjectCode *oc )
          init_start = (init_t*)init_startC;
          init_end = (init_t*)(init_startC + shdr[i].sh_size);
          for (init = init_start; init < init_end; init++) {
+            ASSERT(0x0 != *init);
             (*init)(argc, argv, envv);
          }
       }


=====================================
rts/linker/SymbolExtras.c
=====================================
@@ -77,7 +77,9 @@ int ocAllocateExtras(ObjectCode* oc, int count, int first, int bssSize)
       /* N.B. We currently can't mark symbol extras as non-executable in this
        * case. */
       size_t n = roundUpToPage(oc->fileSize);
-      bssSize = roundUpToAlign(bssSize, 8);
+      // round bssSize up to the nearest page size since we need to ensure that
+      // symbol_extras is aligned to a page boundary so it can be mprotect'd.
+      bssSize = roundUpToPage(bssSize);
       size_t allocated_size = n + bssSize + extras_size;
       void *new = mmapForLinker(allocated_size, PROT_READ | PROT_WRITE, MAP_ANONYMOUS, -1, 0);
       if (new) {


=====================================
rts/linker/elf_reloc_aarch64.c
=====================================
@@ -297,7 +297,7 @@ relocateObjectCodeAarch64(ObjectCode * oc) {
                                relTab->sectionHeader->sh_link,
                                ELF64_R_SYM((Elf64_Xword)rel->r_info));
 
-            assert(symbol != NULL);
+            assert(0x0 != symbol);
 
             /* decode implicit addend */
             int64_t addend = decodeAddendAarch64(targetSection, rel);
@@ -324,6 +324,7 @@ relocateObjectCodeAarch64(ObjectCode * oc) {
                                ELF64_R_SYM((Elf64_Xword)rel->r_info));
 
             assert(0x0 != symbol);
+            assert(0x0 != symbol->addr);
 
             /* take explicit addend */
             int64_t addend = rel->r_addend;


=====================================
testsuite/driver/testlib.py
=====================================
@@ -2216,6 +2216,13 @@ def normalise_errmsg(s: str) -> str:
         s = re.sub('Failed to remove file (.*); error= (.*)$', '', s)
         s = re.sub('DeleteFile "(.+)": permission denied \(Access is denied\.\)(.*)$', '', s)
 
+    # filter out unsupported GNU_PROPERTY_TYPE (5), which is emitted by LLVM10
+    # and not understood by older binutils (ar, ranlib, ...)
+    s = modify_lines(s, lambda l: re.sub('^(.+)warning: (.+): unsupported GNU_PROPERTY_TYPE \(5\) type: 0xc000000(.*)$', '', l))
+
+    # filter out nix garbage, that just keeps on showing up as errors on darwin
+    s = modify_lines(s, lambda l: re.sub('^(.+)\.dylib, ignoring unexpected dylib file$','', l))
+
     return s
 
 # normalise a .prof file, so that we can reasonably compare it against
@@ -2286,6 +2293,9 @@ def normalise_output( s: str ) -> str:
     s = re.sub('([^\\s])\\.exe', '\\1', s)
     s = normalise_callstacks(s)
     s = normalise_type_reps(s)
+    # ghci outputs are pretty unstable with -fexternal-dynamic-refs, which is
+    # requires for -fPIC
+    s = re.sub('  -fexternal-dynamic-refs\n','',s)
     return s
 
 def normalise_asm( s: str ) -> str:



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/866234216353eb87ba5fa5e9fccaf747c88bcab3...5807df4f99a6d109070b591331ed9f1f90cbd4f7

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/866234216353eb87ba5fa5e9fccaf747c88bcab3...5807df4f99a6d109070b591331ed9f1f90cbd4f7
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20201118/204634da/attachment-0001.html>


More information about the ghc-commits mailing list