Skip to content
Snippets Groups Projects
  1. Nov 16, 2020
  2. Nov 15, 2020
    • Ben Gamari's avatar
      ghc-bin: Build with eventlogging by default · fc644b1a
      Ben Gamari authored and Marge Bot's avatar Marge Bot committed
      We now have all sorts of great facilities using the
      eventlog which were previously unavailable without
      building a custom GHC. Fix this by linking with
      `-eventlog` by default.
      fc644b1a
    • Moritz Angermann's avatar
      AArch64/arm64 adjustments · 8887102f
      Moritz Angermann authored and Marge Bot's avatar Marge Bot committed
      This addes the necessary logic to support aarch64 on elf, as well
      as aarch64 on mach-o, which Apple calls arm64.
      
      We change architecture name to AArch64, which is the official arm
      naming scheme.
      8887102f
    • Ryan Scott's avatar
      Use tcSplitForAllInvisTyVars (not tcSplitForAllTyVars) in more places · 645444af
      Ryan Scott authored and Marge Bot's avatar Marge Bot committed
      The use of `tcSplitForAllTyVars` in `tcDataFamInstHeader` was the immediate
      cause of #18939, and replacing it with a new `tcSplitForAllInvisTyVars`
      function (which behaves like `tcSplitForAllTyVars` but only splits invisible
      type variables) fixes the issue. However, this led me to realize that _most_
      uses of `tcSplitForAllTyVars` in GHC really ought to be
      `tcSplitForAllInvisTyVars` instead. While I was in town, I opted to replace
      most uses of `tcSplitForAllTys` with `tcSplitForAllTysInvis` to reduce the
      likelihood of such bugs in the future.
      
      I say "most uses" above since there is one notable place where we _do_ want
      to use `tcSplitForAllTyVars`: in `GHC.Tc.Validity.forAllTyErr`, which produces
      the "`Illegal polymorphic type`" error message if you try to use a higher-rank
      `forall` without having `RankNTypes` enabled. Here, we really do want to split
      all `forall`s, not just invisible ones, or we run the risk of giving an
      inaccurate error message in the newly added `T18939_Fail` test case.
      
      I debated at some length whether I wanted to name the new function
      `tcSplitForAllInvisTyVars` or `tcSplitForAllTyVarsInvisible`, but in the end,
      I decided that I liked the former better. For consistency's sake, I opted to
      rename the existing `splitPiTysInvisible` and `splitPiTysInvisibleN` functions
      to `splitInvisPiTys` and `splitPiTysInvisN`, respectively, so that they use the
      same naming convention. As a consequence, this ended up requiring a `haddock`
      submodule bump.
      
      Fixes #18939.
      645444af
    • Ryan Scott's avatar
      Name (tc)SplitForAll- functions more consistently · d61adb3d
      Ryan Scott authored and Marge Bot's avatar Marge Bot committed
      There is a zoo of `splitForAll-` functions in `GHC.Core.Type` (as well as
      `tcSplitForAll-` functions in `GHC.Tc.Utils.TcType`) that all do very similar
      things, but vary in the particular form of type variable that they return. To
      make things worse, the names of these functions are often quite misleading.
      Some particularly egregious examples:
      
      * `splitForAllTys` returns `TyCoVar`s, but `splitSomeForAllTys` returns
        `VarBndr`s.
      * `splitSomeForAllTys` returns `VarBndr`s, but `tcSplitSomeForAllTys` returns
        `TyVar`s.
      * `splitForAllTys` returns `TyCoVar`s, but `splitForAllTysInvis` returns
        `InvisTVBinder`s. (This in particular arose in the context of #18939, and
        this finally motivated me to bite the bullet and improve the status quo
        vis-à-vis how we name these functions.)
      
      In an attempt to bring some sanity to how these functions are named, I have
      opted to rename most of these functions en masse to use consistent suffixes
      that describe the particular form of type variable that each function returns.
      In concrete terms, this amounts to:
      
      * Functions that return a `TyVar` now use the suffix `-TyVar`.
        This caused the following functions to be renamed:
        * `splitTyVarForAllTys` -> `splitForAllTyVars`
        * `splitForAllTy_ty_maybe` -> `splitForAllTyVar_maybe`
        * `tcSplitForAllTys` -> `tcSplitForAllTyVars`
        * `tcSplitSomeForAllTys` -> `tcSplitSomeForAllTyVars`
      * Functions that return a `CoVar` now use the suffix `-CoVar`.
        This caused the following functions to be renamed:
        * `splitForAllTy_co_maybe` -> `splitForAllCoVar_maybe`
      * Functions that return a `TyCoVar` now use the suffix `-TyCoVar`.
        This caused the following functions to be renamed:
        * `splitForAllTy` -> `splitForAllTyCoVar`
        * `splitForAllTys` -> `splitForAllTyCoVars`
        * `splitForAllTys'` -> `splitForAllTyCoVars'`
        * `splitForAllTy_maybe` -> `splitForAllTyCoVar_maybe`
      * Functions that return a `VarBndr` now use the suffix corresponding to the
        most relevant type synonym. This caused the following functions to be renamed:
        * `splitForAllVarBndrs` -> `splitForAllTyCoVarBinders`
        * `splitForAllTysInvis` -> `splitForAllInvisTVBinders`
        * `splitForAllTysReq` -> `splitForAllReqTVBinders`
        * `splitSomeForAllTys` -> `splitSomeForAllTyCoVarBndrs`
        * `tcSplitForAllVarBndrs` -> `tcSplitForAllTyVarBinders`
        * `tcSplitForAllTysInvis` -> `tcSplitForAllInvisTVBinders`
        * `tcSplitForAllTysReq` -> `tcSplitForAllReqTVBinders`
        * `tcSplitForAllTy_maybe` -> `tcSplitForAllTyVarBinder_maybe`
      
      Note that I left the following functions alone:
      
      * Functions that split apart things besides `ForAllTy`s, such as `splitFunTys`
        or `splitPiTys`. Thankfully, there are far fewer of these functions than
        there are functions that split apart `ForAllTy`s, so there isn't much of a
        pressing need to apply the new naming convention elsewhere.
      * Functions that split apart `ForAllCo`s in `Coercion`s, such as
        `GHC.Core.Coercion.splitForAllCo_maybe`. We could theoretically apply the new
        naming convention here, but then we'd have to figure out how to disambiguate
        `Type`-splitting functions from `Coercion`-splitting functions. Ultimately,
        the `Coercion`-splitting functions aren't used nearly as much as the
        `Type`-splitting functions, so I decided to leave the former alone.
      
      This is purely refactoring and should cause no change in behavior.
      d61adb3d
    • Ben Gamari's avatar
      gitlab-ci: Add DWARF release jobs for Debian 10, Fedora27 · a2539650
      Ben Gamari authored and Marge Bot's avatar Marge Bot committed
      a2539650
    • Ben Gamari's avatar
      nativeGen/dwarf: Use DW_AT_linkage instead of DW_AT_MIPS_linkage · ad73370f
      Ben Gamari authored and Marge Bot's avatar Marge Bot committed
      ad73370f
    • Ben Gamari's avatar
      nativeGen/dwarf: Only produce DW_AT_source_note DIEs in -g3 · 1e19183d
      Ben Gamari authored and Marge Bot's avatar Marge Bot committed
      Standard debugging tools don't know how to understand these so let's not
      produce them unless asked.
      1e19183d
    • Ben Gamari's avatar
      nativeGen/dwarf: Fix procedure end addresses · 0a7e592c
      Ben Gamari authored and Marge Bot's avatar Marge Bot committed
      Previously the `.debug_aranges` and `.debug_info` (DIE) DWARF
      information would claim that procedures (represented with a
      `DW_TAG_subprogram` DIE) would only span the range covered by their entry
      block. This omitted all of the continuation blocks (represented by
      `DW_TAG_lexical_block` DIEs), confusing `perf`. Fix this by introducing
      a end-of-procedure label and using this as the `DW_AT_high_pc` of
      procedure `DW_TAG_subprogram` DIEs
      
      Fixes #17605.
      0a7e592c
  3. Nov 13, 2020
  4. Nov 12, 2020
  5. Nov 11, 2020
    • Krzysztof Gogolewski's avatar
      Force argument in setIdMult (#18925) · 5506f134
      Krzysztof Gogolewski authored and Marge Bot's avatar Marge Bot committed
      5506f134
    • GHC GitLab CI's avatar
      Introduce test for dynamic library unloading · e9e1b2e7
      GHC GitLab CI authored and Marge Bot's avatar Marge Bot committed
      This uses the highMemDynamic flag introduced earlier to verify that
      dynamic objects are properly unloaded.
      e9e1b2e7
    • GHC GitLab CI's avatar
      rts: Introduce highMemDynamic · 7a65f9e1
      GHC GitLab CI authored and Marge Bot's avatar Marge Bot committed
      7a65f9e1
    • Ray Shih's avatar
      Add loadNativeObj and unloadNativeObj · 2782487f
      Ray Shih authored and Marge Bot's avatar Marge Bot committed
      (This change is originally written by niteria)
      
      This adds two functions:
      * `loadNativeObj`
      * `unloadNativeObj`
      and implements them for Linux.
      
      They are useful if you want to load a shared object with Haskell code
      using the system linker and have GHC call dlclose() after the
      code is no longer referenced from the heap.
      
      Using the system linker allows you to load the shared object
      above outside the low-mem region. It also loads the DWARF sections
      in a way that `perf` understands.
      
      `dl_iterate_phdr` is what makes this implementation Linux specific.
      2782487f
    • Ömer Sinan Ağacan's avatar
      Fix and enable object unloading in GHCi · c34a4b98
      Ömer Sinan Ağacan authored and Marge Bot's avatar Marge Bot committed
      Fixes #16525 by tracking dependencies between object file symbols and
      marking symbol liveness during garbage collection
      
      See Note [Object unloading] in CheckUnload.c for details.
      c34a4b98
    • Ben Gamari's avatar
      Enable -fexpose-internal-symbols when debug level >=2 · 584058dd
      Ben Gamari authored and Marge Bot's avatar Marge Bot committed
      This seems like a reasonable default as the object file size increases
      by around 5%.
      584058dd
    • Ben Gamari's avatar
      codeGen: Produce local symbols for module-internal functions · c6264a2d
      Ben Gamari authored and Marge Bot's avatar Marge Bot committed
      It turns out that some important native debugging/profiling tools (e.g.
      perf) rely only on symbol tables for function name resolution (as
      opposed to using DWARF DIEs). However, previously GHC would emit
      temporary symbols (e.g. `.La42b`) to identify module-internal
      entities. Such symbols are dropped during linking and therefore not
      visible to runtime tools (in addition to having rather un-helpful unique
      names). For instance, `perf report` would often end up attributing all
      cost to the libc `frame_dummy` symbol since Haskell code was no covered
      by any proper symbol (see #17605).
      
      We now rather follow the model of C compilers and emit
      descriptively-named local symbols for module internal things. Since this
      will increase object file size this behavior can be disabled with the
      `-fno-expose-internal-symbols` flag.
      
      With this `perf record` can finally be used against Haskell executables.
      Even more, with `-g3` `perf annotate` provides inline source code.
      c6264a2d
    • Ben Gamari's avatar
      Move this_module into NCGConfig · 6e23695e
      Ben Gamari authored and Marge Bot's avatar Marge Bot committed
      In various places in the NCG we need the Module currently being
      compiled. Let's move this into the environment instead of chewing threw
      another register.
      6e23695e
    • Ben Gamari's avatar
      nativeGen: Make makeImportsDoc take an NCGConfig rather than DynFlags · fcfda909
      Ben Gamari authored and Marge Bot's avatar Marge Bot committed
      It appears this was an oversight as there is no reason the full DynFlags
      is necessary.
      fcfda909
  6. Nov 10, 2020
  7. Nov 08, 2020
  8. Nov 06, 2020
    • Ben Gamari's avatar
      rts/Sanity: Avoid nasty race in weak pointer sanity-checking · b1d2c1f3
      Ben Gamari authored and Marge Bot's avatar Marge Bot committed
      See Note [Racing weak pointer evacuation] for all of the gory details.
      b1d2c1f3
    • Moritz Angermann's avatar
      [AArch64] Aarch64 Always PIC · 2cb87909
      Moritz Angermann authored and Marge Bot's avatar Marge Bot committed
      2cb87909
    • Sylvain Henry's avatar
      Refactor -dynamic-too handling · c85f4928
      Sylvain Henry authored and Marge Bot's avatar Marge Bot committed
      1) Don't modify DynFlags (too much) for -dynamic-too: now when we
         generate dynamic outputs for "-dynamic-too", we only set "dynamicNow"
         boolean field in DynFlags instead of modifying several other fields.
         These fields now have accessors that take dynamicNow into account.
      
      2) Use DynamicTooState ADT to represent -dynamic-too state. It's much
         clearer than the undocumented "DynamicTooConditional" that was used
         before.
      
      As a result, we can finally remove the hscs_iface_dflags field in
      HscRecomp. There was a comment on this field saying:
      
         "FIXME (osa): I don't understand why this is necessary, but I spent
         almost two days trying to figure this out and I couldn't .. perhaps
         someone who understands this code better will remove this later."
      
      I don't fully understand the details, but it was needed because of the
      changes made to the DynFlags for -dynamic-too.
      
      There is still something very dubious in GHC.Iface.Recomp: we have to
      disable the "dynamicNow" flag at some point for some Backpack's "heinous
      hack" to continue to work. It may be because interfaces for indefinite
      units are always non-dynamic, or because we mix and match dynamic and
      non-dynamic interfaces (#9176), or something else, who knows?
      c85f4928
    • Ryan Scott's avatar
      Replace HsImplicitBndrs with HsOuterTyVarBndrs · e07e383a
      Ryan Scott authored and Marge Bot's avatar Marge Bot committed
      
      This refactors the GHC AST to remove `HsImplicitBndrs` and replace it with
      `HsOuterTyVarBndrs`, a type which records whether the outermost quantification
      in a type is explicit (i.e., with an outermost, invisible `forall`) or
      implicit. As a result of this refactoring, it is now evident in the AST where
      the `forall`-or-nothing rule applies: it's all the places that use
      `HsOuterTyVarBndrs`. See the revamped `Note [forall-or-nothing rule]` in
      `GHC.Hs.Type` (previously in `GHC.Rename.HsType`).
      
      Moreover, the places where `ScopedTypeVariables` brings lexically scoped type
      variables into scope are a subset of the places that adhere to the
      `forall`-or-nothing rule, so this also makes places that interact with
      `ScopedTypeVariables` easier to find. See the revamped
      `Note [Lexically scoped type variables]` in `GHC.Hs.Type` (previously in
      `GHC.Tc.Gen.Sig`).
      
      `HsOuterTyVarBndrs` are used in type signatures (see `HsOuterSigTyVarBndrs`)
      and type family equations (see `HsOuterFamEqnTyVarBndrs`). The main difference
      between the former and the latter is that the former cares about specificity
      but the latter does not.
      
      There are a number of knock-on consequences:
      
      * There is now a dedicated `HsSigType` type, which is the combination of
        `HsOuterSigTyVarBndrs` and `HsType`. `LHsSigType` is now an alias for an
        `XRec` of `HsSigType`.
      * Working out the details led us to a substantial refactoring of
        the handling of explicit (user-written) and implicit type-variable
        bindings in `GHC.Tc.Gen.HsType`.
      
        Instead of a confusing family of higher order functions, we now
        have a local data type, `SkolemInfo`, that controls how these
        binders are kind-checked.
      
        It remains very fiddly, not fully satisfying. But it's better
        than it was.
      
      Fixes #16762. Bumps the Haddock submodule.
      
      Co-authored-by: default avatarSimon Peyton Jones <simonpj@microsoft.com>
      Co-authored-by: Richard Eisenberg's avatarRichard Eisenberg <rae@richarde.dev>
      Co-authored-by: default avatarZubin Duggal <zubin@cmi.ac.in>
      e07e383a
  9. Nov 05, 2020
    • Ryan Scott's avatar
      Add a regression test for #18920 · 2125b1d6
      Ryan Scott authored and Marge Bot's avatar Marge Bot committed
      Commit f594a68a
      (`Use level numbers for generalisation`) ended up fixing #18920. Let's add a
      regression test to ensure that it stays fixed.
      
      Fixes #18920.
      2125b1d6
    • vdukhovni's avatar
      Naming, value types and tests for Addr# atomics · 17d5c518
      vdukhovni authored and Marge Bot's avatar Marge Bot committed
      The atomic Exchange and CAS operations on integral types are updated to
      take and return more natural `Word#` rather than `Int#` values.  These
      are bit-block not arithmetic operations, and the sign bit plays no
      special role.
      
      Standardises the names to `atomic<OpType><ValType>Addr#`, where `OpType` is one
      of `Cas` or `Exchange` and `ValType` is presently either `Word` or `Addr`.
      Eventually, variants for `Word32` and `Word64` can and should be added,
      once #11953 and related issues (e.g. #13825) are resolved.
      
      Adds tests for `Addr#` CAS that mirror existing tests for
      `MutableByteArray#`.
      17d5c518
  10. Nov 04, 2020
Loading