Skip to content
Snippets Groups Projects
  1. Apr 02, 2025
    • sheaf's avatar
      GHC settings: always unescape escaped spaces · cc1588cf
      sheaf authored
      In #25204, it was noted that GHC didn't properly deal with having
      spaces in its executable path, as it would compute an invalid path
      for the C compiler.
      
      The original fix in 31bf85ee used a
      trick: escape spaces before splitting up flags into a list. This fixed
      the behaviour with extra flags (e.g. -I), but forgot to also unescape
      for non-flags, e.g. for an executable path (such as the C compiler).
      
      This commit rectifies this oversight by consistently unescaping the
      spaces that were introduced in order to split up argument lists.
      
      Fixes #25204
      cc1588cf
  2. Mar 20, 2025
    • Bodigrim's avatar
      Improve haddock-visible documentation for GHC.Driver.Flags · 47646ce2
      Bodigrim authored and Marge Bot's avatar Marge Bot committed
      47646ce2
    • sheaf's avatar
      Don't cache solved [W] HasCallStack constraints · 256ac29c
      sheaf authored and Marge Bot's avatar Marge Bot committed
      This commit ensures we do not add solved Wanted constraints that mention
      HasCallStack or HasExceptionContext constraints to the set of solved
      Wanted dictionary constraints: caching them is invalid, because re-using
      such cached dictionaries means using an old call-stack instead of
      constructing a new one, as was reported in #25529.
      
      Fixes #25529.
      256ac29c
    • Cheng Shao's avatar
      testsuite: mark T7919 as fragile on i386 as well · a8f543a9
      Cheng Shao authored and Marge Bot's avatar Marge Bot committed
      T7919 may also fail i386 CI jobs with test timeout.
      a8f543a9
    • sheaf's avatar
      Reject instance with non-class head in renamer · 75c29aa1
      sheaf authored and Marge Bot's avatar Marge Bot committed
      This commit modifies rnClsInstDecl so that, when renaming, we reject a class
      instance declaration in which the head is not a class. Before this change, it
      would get rejected in the type-checker, but that meant that the renamer could
      emit unhelpful error messages, e.g.:
      
        data Foo m a
        instance Foo m where
          fmap _ x = case x of
      
      would rather unhelpfully say:
      
          ‘fmap’ is not a (visible) method of class ‘Foo’
      
      when of course 'Foo' is not even a class. We now reject the above program
      with the following error message:
      
          Illegal instance for data type ‘Foo’.
          Instance heads must be of the form
            C ty_1 ... ty_n
          where ‘C’ is a class.
      
      Fixes #22688
      75c29aa1
    • sheaf's avatar
      Remove SDocs from HsDocContext · 4329f3b6
      sheaf authored and Marge Bot's avatar Marge Bot committed
      This commit removes the remaining SDocs from the HsDocContext data type.
      It adds the following constructors:
      
        ClassInstanceCtx  -- Class instances
        ClassMethodSigCtx -- Class method signatures
        SpecialiseSigCtx  -- SPECIALISE pragmas
        PatSynSigCtx      -- Pattern synonym signatures
      
      We now report a bit more information for errors while renaming class instances,
      which slightly improves renamer-emitted error messages.
      4329f3b6
    • sheaf's avatar
      Remove SDoc from UnknownSubordinate/MissingBinding · 9003ef0a
      sheaf authored and Marge Bot's avatar Marge Bot committed
      This commit replaces unstructured SDoc arguments in error message constructors
      with uses of the following two datatypes:
      
        - SigLike: for different kinds of signatures (e.g. standalone kind signatures,
          fixity signatures, COMPLETE pragmas, etc)
        - Subordinate: for class methods, associated types, and record fields
      
      The following error message constructors now no longer have any SDocs in them:
      
        - TcRnIllegalBuiltinSyntax: SDoc -> SigLike
        - MissingBinding: SDoc -> SigLike
        - UnknownSubordinate: SDoc -> (Name, Subordinate)
        - SuggestMoveToDeclarationSite: SDoc -> SigLike
      9003ef0a
    • Simon Peyton Jones's avatar
      Remove the Core flattener · 5d65393e
      Simon Peyton Jones authored and Marge Bot's avatar Marge Bot committed
      This big MR entirely removes the "flattener" that took a type and
      replaced each type-family application with a fresh type variable.
      The flattener had its origin in the paper
           Injective type families for Haskell
      
      But (a) #25657 showed that flattening doesn't really work.
          (b) since we wrote the paper we have introduced the so-called
              "fine-grained" unifier GHC.Core.Unify, which can return
                       * SurelyApart
                       * Unifiable subst
                       * MaybeApart subst
              where the MaybeApart says that the two types are not unifiable by a
              substitution, but could (perhaps) be unified "later" after some type
              family reductions.  This turns out to subsume flattening.
      
      This MR does a major refactor of GHC.Core.Unify to make it capable of
      subsuming flattening.   The main payload is described in
             Note [Apartness and type families]
      and its many wrinkles.
      
      The key (non-refactoring) implementation change is to add `um_fam_env`
      to the `UMState` in the unification monad.
      
      Careful review with Richard revealed various bugs in the treament of
      `kco`, the kind coercion carried around by the unifier, so that is
      substantially fixed too: see Note [Kind coercions in Unify].
      
      Compile-time performance is improved by 0.1% with a few improvements over
      1% and one worsening by 1.3% namely T9872a.  (I have not investigated the
      latter.)
      
      Metric Decrease:
          T9872b
          T9872c
          TcPlugin_RewritePerf
      Metric Increase:
          T9872a
      5d65393e
  3. Mar 19, 2025
    • Matthew Craven's avatar
      Add README reference for the interface-stability tests · 25d46547
      Matthew Craven authored and Marge Bot's avatar Marge Bot committed
      25d46547
    • Matthew Craven's avatar
      Add interface-stability test for ghc-bignum · 27cf7361
      Matthew Craven authored and Marge Bot's avatar Marge Bot committed
      As with ghc-prim, it makes sense to have some protection against
      accidental interface changes to this package caused by changes
      in ghc-internal.
      27cf7361
    • Ticat Fp's avatar
      Pass the mcmodel=medium parameter to CC via GHC · 1a3f1131
      Ticat Fp authored and Marge Bot's avatar Marge Bot committed
      Ensure that GHC-driver builds default to mcmodel=medium, so that GHC
      passes this default parameter to CC without having to add it to the
      compiled project.
      
      Commit e70d4140 does not ensure that all
      GHC-built object files have a default model of medium, and will raise an
      R_LARCH_B26 overflow error.
      1a3f1131
    • Ben Gamari's avatar
      rts: Ensure that WinIO flag is set when --io-manager=auto · 5b94f99f
      Ben Gamari authored and Marge Bot's avatar Marge Bot committed
      As noted in #25838, previously `selectIOManager` failed to set
      `rts_IOManagerIsWin32Native` in its `IO_MNGR_FLAG_AUTO`. This meant
      that the MIO path was taken when WinIO was supposedly selected,
      resulting in chaos.
      
      Fixes #25838.
      5b94f99f
    • Ben Gamari's avatar
      gitlab-ci: Drop CentOS 7 binary distributions · 313cf271
      Ben Gamari authored and Marge Bot's avatar Marge Bot committed
      CentOS 7 is EoL and moreover we cannot even build images for it.
      
      See #25061.
      313cf271
    • Sjoerd Visscher's avatar
      Multiplicity annotation on records · 443fc8b1
      Sjoerd Visscher authored and Marge Bot's avatar Marge Bot committed
      Needing to store multiplicity annotations on records triggered a refactoring of AST of data declarations:
      
      Moved HsBangTy and HsRecTy from HsType to HsTypeGhcPsExt, the extension of HsType during parsing, since they are only needed during parsing.
      
      New HsConDeclField that stores all source data shared by all constructor declaration fields: unpackedness, strictness, multiplicity, documentation and the type of the field.
      
      Merged HsMultAnn and HsArrowOf, so all multiplicity annotations share the same data type.
      
      HsBang was no longer needed as a separate type, and was inlined into HsSrcBang.
      443fc8b1
    • Andreas Klebinger's avatar
      Bump nofib submodule. · e576468c
      Andreas Klebinger authored and Marge Bot's avatar Marge Bot committed
      Fixes #25867. (Ben-raytrace being broken by library changes)
      e576468c
    • ARATA Mizuki's avatar
      Fix code generation for SSE vector operations · 25850b22
      ARATA Mizuki authored and Marge Bot's avatar Marge Bot committed
      The new implementation generates correct code
      even if the registers overlap.
      
      Closes #25859
      25850b22
    • Ben Gamari's avatar
      compiler: Add export list to GHC.SysTools.Process · b00b3ef0
      Ben Gamari authored and Marge Bot's avatar Marge Bot committed
      This also revealed that `readProcessEnvWithExitCode` and its local
      helpers were dead code.
      b00b3ef0
    • Simon Peyton Jones's avatar
      Add -Wrule-lhs-equalities warning · 1884dd1a
      Simon Peyton Jones authored and Marge Bot's avatar Marge Bot committed
      This commit adds a new warning, controlled by the warning flag,
      -Wrule-lhs-equalities, which is emitted when the LHS of a RULE gives
      rise to equality constraints that previous GHC versions would have
      quantified over.
      
      GHC instead discards such RULES, as GHC was never able to generate
      a rule template that would ever fire; it's better to be explicit about
      the fact that the RULE doesn't work.
      1884dd1a
    • Simon Peyton Jones's avatar
      Specialising expressions -- at last · 393531ff
      Simon Peyton Jones authored and Marge Bot's avatar Marge Bot committed
      This MR addresses #24359, which implements the GHC proposal 493 on SPECIALISE pragmas.
      
      * The old code path (using SpecSig and SpecPrag) still exists.
      * The new code path (using SpecSigE and SpecPragE) runs alongside it.
      * All SPECIALISE pragmas are routed through the new code path, except
        if you give multiple type sigs, when the old code path is still used.
      * Main documentation: Note [Handling new-form SPECIALISE pragmas] in
        GHC.Tc.Gen.Sig`
      
      Thanks to @sheaf for helping with this MR.
      
      The Big Thing is to introduce
      
        {-# SPECIALISE forall x.  f @Int x True #-}
      
      where you can give type arguments and value argument to specialise; and
      you can quantify them with forall, just as in Rules.
      
      I thought it was going to be pretty simple, but it was a Long, Long Saga.
      
      Highlights
      
      * Overview Note [Handling new-form SPECIALISE pragmas] in GHC.Tc.Gen.Sig
        - New data constructor `SpecSigE` in data type `L.H.S.Binds.Sig`
        - New data construtor `SpecPragE` in data type `GHC.Hs.Binds.TcSpecPrag`
        - Renamer: uses `checkSpecESigShape` to decide which function to assocate the
                   SPECIALISE pragma with
        - Some of the action is in `GHC.Tc.Gen.Sig.tcSpecPrag`
        - The rest is in `GHC.HsToCore.Binds.dsSpec`
      
      * We use a new TcS mode, TcSFullySolve, when simplifying the Wanteds
        that arise from the specialise expression. The mechanism is explained
        in Note [TcSFullySolve] in GHC.Tc.Solver.Monad. The reason why we need
        to do this is explained in Note [Fully solving constraints for specialisation]
        in GHC.Tc.Gen.Sig.
      
      * All of GHC.Tc.Gen.Rule is moved into GHC.Tc.Gen.Sig, because the code is
        very closely related.
      
      * The forall'd binders for SPECIALISE are the same as those for a RULE, so I
        refactored, introducing data type `L.H.S.Binds.RuleBndrs`, with functions
        to rename, zonk, typecheck it.  I refactored this data type a bit; nicer now.
      
      * On the LHS of RULES, or SPECIALISE, we want to disable the tricky mechanims
        described in Note [Desugaring non-canonical evidence] in GHC.HsToCore.Expr.
        Previously it wasn't fully disabled (just set to the empty set), and that
        didn't quite work in the new regime.
      
      * There are knock-on changes to Template Haskell.
      
      * For the LHS of a RULE and a SPECIALISE expression, I wanted to simplify
        it /without/ inlining the let-bindings for evidence variables.  I added
        a flag `so_inline` to the SimpleOpt optimiser to support this.  The
        entry point is `GHC.Core.SimpleOpt.simpleOptExprNoInline`
      
      * Since forever we have had a hack for type variables on the LHS of
        RULES. I took the opportunity to tidy this up.  The main action is
        in the zonker.  See GHC.Tc.Zonk.Type Note [Free tyvars on rule LHS],
        and especially data construtor `SkolemiseFlexi`
        in data type `GHC.Tc.Zonk.Env.ZonkFlexi`
      
      * Move `scopedSort` from GHC.Core.TyCo.FVs to GHC.Core.Predicate
        Reason: it now works for Ids as well, and I wanted to use isEvVar,
                which is defined in GHC.Core.Predicate
        Avoiding module loops meant that instead of exporting GHC.Core.TyCo.Tidy
        from GHC.Core.Type, modules now import the former directly.
      
        I also took the opportunity to remove unused exports
        from GHC.Core.Type.hs-boot
      
      * Flag stuff:
        - Add flag `-Wdeprecated-pragmas` and use it to control the warning when
          using old-style SPECIALISE pragmas with multiple type ascriptions,
      
        - Add flag `-Wuseless-specialisations` and use it to control the warning emitted
          when GHC determines that a SPECIALISE pragma would have no effect. Don't
          want if the SPECIALISE is SPECIALISE INLINE (#4444)
      
          In response to #25389, we continue to generate these seemingly code for these
          seemingly useless SPECIALISE pragmas
      
        - Adds deprecations to Template Haskell `pragSpecD` and `pracSpecInlD`,
      
      * Split up old-style SPECIALISE pragmas in GHC.Internal.Float,
        GHC.Internal.Numeric, GHC.Internal.Real
      
      * Remove useless SPECIALISE pragmas in Data.Array (updating the array submodule)
      
      Smaller things:
      
      - Update the Users Guide
      
      - Add mention of the changes to the 9.14 release notes as well as
        the Template Haskell changelog,
      393531ff
    • sheaf's avatar
      Add mapMaybeTM method to TrieMap class · 9f9fe0b3
      sheaf authored and Marge Bot's avatar Marge Bot committed
      This commit adds a new method to the TrieMap class, mapMaybeTM, and
      adds implementations to all the instances.
      
      mapMaybeTM is useful when filtering containers that contain other
      containers.
      9f9fe0b3
    • sheaf's avatar
      Fix buglet in isEmptyWorkList · cfaaca14
      sheaf authored and Marge Bot's avatar Marge Bot committed
      There was a missing case in GHC.Tc.Solver.InertSet.isEmptyWorkList; it
      mistakenly ignored the 'wl_rw_eqs' field. This commit simply fixes that.
      No test case.
      cfaaca14
  4. Mar 15, 2025
    • Ben Gamari's avatar
      configure: Fix incorrect SettingsLlvmAsFlags value · c758cb71
      Ben Gamari authored and Marge Bot's avatar Marge Bot committed
      Previously this was set to `LlvmAsCmd` rather than `LlvmAsFlags`,
      resulting in #25856.
      c758cb71
    • Matthew Pickering's avatar
      iface: Store logical parts of ModIface together · b15fca2b
      Matthew Pickering authored and Marge Bot's avatar Marge Bot committed
      The ModIface structure is divided into several logical parts:
      
      1. mi_mod_info: Basic module metadata (name, version, etc.)
      
      2. mi_public: The public interface of the module (the ABI), which includes:
         - Exports, declarations, fixities, warnings, annotations
         - Class and type family instances
         - Rewrite rules and COMPLETE pragmas
         - Safe Haskell and package trust information
         - ABI hashes for recompilation checking
      
      4. mi_self_recomp: Information needed for self-recompilation checking
         (see Note [Self recompilation information in interface files])
      
      5. mi_simplified_core: Optional simplified Core for bytecode generation
         (only present when -fwrite-if-simplified-core is enabled)
      
      6. mi_docs: Optional documentation (only present when -haddock is enabled)
      
      7. mi_top_env: Information about the top-level environment of the original source
      
      8. mi_ext_fields: Additional fields for extensibility
      
      This structure helps organize the interface data according to its purpose and usage
      patterns. Different parts of the compiler use different fields. By separating them
      logically in the interface we can arrange to only deserialize the fields that are needed.
      
      This patch also enforces the invariant that the fields of ModIface are
      lazy. If you are keeping a ModIface on disk, then force it using
      `forceModIface`. Otherwise, when the `ModIface` is read from disk, only
      the parts which are needed from the interface will be deserialised.
      
      In a follow-up patch I will tackle follow-up issues:
      
      * Recompilation checking doesn't take into account exported named defaults (#25855)
      * Recompilation checking does not take into account COMPLETE pragmas (#25854)
      * mi_deps_ field in an interface is confused about whether the
        information is for self-recompilation checking or part of the ABI
        (#25844)
      
      Fixes #25845
      
      -------------------------
      Metric Decrease:
          MultiLayerModulesDefsGhciWithCore
      -------------------------
      b15fca2b
  5. Mar 14, 2025
    • Matthew Pickering's avatar
      binary: Directly copy ShortByteString to buffer rather than go via ByteString · f1830d74
      Matthew Pickering authored and Marge Bot's avatar Marge Bot committed
      This avoids allocating an intermediate bytestring. I just noticed on a
      profile that `putFS` was allocating, and it seemed strange to me why
      since it should just copy the contents of the FastString into the
      already allocated buffer. It turned out we were going indirectly via a
      ByteString.
      
      Fixes #25861
      f1830d74
    • sheaf's avatar
      Don't report used duplicate record fields as unused · 0cb1db92
      sheaf authored and Marge Bot's avatar Marge Bot committed
      This commit fixes the bug reported in #24035 in which the import of a
      duplicate record field could be erroneously reported as unused.
      
      The issue is that an import of the form "import M (fld)" can import
      several different 'Name's, and we should only report an error if ALL
      of those 'Name's are unused, not if ANY are.
      
      Note [Reporting unused imported duplicate record fields]
      in GHC.Rename.Names explains the solution to this problem.
      
      Fixes #24035
      0cb1db92
  6. Mar 13, 2025
    • Matthew Craven's avatar
      Add interface-stability test for ghc-prim · 24d373a6
      Matthew Craven authored and Marge Bot's avatar Marge Bot committed
      24d373a6
    • Matthew Pickering's avatar
      interfaces: Ensure that forceModIface deeply forces a ModIface · 915a6781
      Matthew Pickering authored and Marge Bot's avatar Marge Bot committed
      A ModIface is the result of compilation that we keep for a long time in
      memory. Therefore, it's very important to manage what we are going to
      retain and remove any external references to things which we might have
      captured compilation.
      
      If storing your ModIface in memory uses too much space, then store
      less things or make it use a more efficient representation.
      
      In the past there have been many space leak bugs by not sufficiently
      forcing a ModIface (#15111)
      
      This patch adds all the missing NFData instances for all the places I
      could find where we weren't deeply forcing the structure.
      915a6781
  7. Mar 12, 2025
  8. Mar 11, 2025
    • Matthew Pickering's avatar
      Remove mi_hpc field from interface files · 6bb0e261
      Matthew Pickering authored and Marge Bot's avatar Marge Bot committed
      The `mi_hpc` field is not used for anything as far as I can discern so
      there is no reason to record in the private interface of a module that
      there are modules in the transitive closure which use `hpc`.
      
      You can freely mix modules which use `-fhpc` and ones which don't.
      
      Whether to recompile a module due to `-fhpc` being passed to the module
      itself is determined in `fingerprintDynFlags`.
      6bb0e261
    • Matthew Pickering's avatar
      Remove mi_used_th field from interface files · 03c72f01
      Matthew Pickering authored and Marge Bot's avatar Marge Bot committed
      In the distant past, recompilation checking was disabled for interfaces which used
      TemplateHaskell, but for several years now recompilation checking has
      been more fine-grained. This has rendered this field unused and
      lingering in an interface file.
      03c72f01
    • Matthew Pickering's avatar
      Pass -fPIC to dynamicToo001 test to avoid platform dependence issues · 48b8f110
      Matthew Pickering authored and Marge Bot's avatar Marge Bot committed
      On darwin platforms, `-fPIC` is always enabled but on linux it is only
      enabled in the dynamic flavour. This can cause a difference in
      interface files (see #25836).
      
      The purpose of this test isn't to test module A recompilation, so we
      avoid this platform dependency by always passing `-fPIC`.
      48b8f110
    • Matthew Pickering's avatar
      Take into account all flags when computing iface_hash · 77df05d0
      Matthew Pickering authored and Marge Bot's avatar Marge Bot committed
      The "interface hash" should contain a hash of everything in the
      interface file. We are not doing that yet but at least a start is to
      include a hash of everything in `mi_self_recomp`, rather than just
      `mi_src_hash` and `mi_usages`.
      
      In particular, this fixes #25837, a bug where we should recompile a
      `dyn_hi` file but fail to do so.
      77df05d0
    • sheaf's avatar
      user's guide: NamedDefaults vs ExtendedDefaultRules · 2df171d4
      sheaf authored and Marge Bot's avatar Marge Bot committed
      This commit clarifies the defaulting rules with NamedDefaults,
      in particular in situations where a type variable appears in other
      constraints than standard/unary constraints.
      2df171d4
    • sheaf's avatar
      user's guide: flesh out XOverloadedStrings docs · 0c9fd8d4
      sheaf authored and Marge Bot's avatar Marge Bot committed
      This commit extends the documentation of the OverloadedStrings extension
      with some usage information, in particular suggestions to:
      
        - use default declarations, such as `default (Text)` or
          `default IsString(Text)` (with the NamedDefaults extension),
      
        - enable the ExtendedDefaultRules extension to relax the requirement
          that a defaultable type variable must only appear in unary standard
          classes
      
      Fixes #23388
      0c9fd8d4
    • sheaf's avatar
      user's guide: consolidate defaulting documentation · 37d8b50b
      sheaf authored and Marge Bot's avatar Marge Bot committed
      This commit adds a new section on defaulting, which consolidates various
      parts of documentation surrounding defaulting into one central place.
      
      It explains type class defaulting in detail, extensions to it with
      OverloadedStrings, NamedDefaults and ExtendedDefaultRules, as well
      as other defaulting mechanisms (e.g. kind-based defaulting such as
      RuntimeRep defaulting, and defaulting of equalities).
      37d8b50b
    • Vladislav Zavialov's avatar
      Error message with EmptyCase and RequiredTypeArguments (#25004) · cce869ea
      Vladislav Zavialov authored and Marge Bot's avatar Marge Bot committed
      Fix a panic triggered by a combination of \case{} and forall t ->
      
        ghci> let f :: forall (xs :: Type) -> (); f = \case {}
        panic! (the 'impossible' happened)
          GHC version 9.10.1:
                Util: only
      
      The new error message looks like this:
      
        ghci> let f :: forall (xs :: Type) -> (); f = \case {}
        <interactive>:5:41: error: [GHC-48010]
            • Empty list of alternatives in \case expression
              checked against a forall-type: forall xs -> ...
      
      This is achieved as follows:
      
      * A new data type, BadEmptyCaseReason, is now used to describe
        why an empty case has been rejected. Used in TcRnEmptyCase.
      
      * HsMatchContextRn is passed to tcMatches, so that the type checker
        can attach the syntactic context to the error message.
      
      * tcMatches now rejects type arguments if the list of alternatives is
        empty. This is what fixes the bug.
      cce869ea
Loading