Skip to content
Snippets Groups Projects
  1. Dec 22, 2015
    • Edward Z. Yang's avatar
      Implement -hide-all-plugin-packages and -plugin-package(-id), fixing #11244 · 1faf1fca
      Edward Z. Yang authored
      
      Summary:
      The basic idea is that we have a new set of "exposed modules"
      which are /only/ used for plugins, i.e. -fplugin Foo and
      --frontend Foo.  You can interact with this namespace
      using the flags -plugin-package-id and -plugin-package.
      By default, this namespace contains all modules in the
      user namespace (as before), but you can toggle that using
      -hide-all-plugin-packages.
      
      There is one nasty hack: GhcMake respects -fplugin in
      GHC_OPTIONS to make local plugins work correctly.  It also
      bails out of you have an import of a module which doesn't
      exist locally or in the package database.  The upshot is
      that we need to be sure to check in the plugin modules
      too, so we don't give a spurious failure when a plugin
      is in the plugin namespace but not the main namespace.
      A better way to fix this would be to distinguish between
      plugin and normal dependencies in ModSummary.
      
      I cheated a little and tweaked a few existing plugins
      tests to exercise the new code paths.
      
      TODO: Documentation
      
      Signed-off-by: default avatarEdward Z. Yang <ezyang@cs.stanford.edu>
      
      Test Plan: validate
      
      Reviewers: bgamari, austin, simonpj, duncan
      
      Subscribers: thomie
      
      Differential Revision: https://phabricator.haskell.org/D1661
      
      GHC Trac Issues: #11244
      1faf1fca
    • Edward Z. Yang's avatar
      Refactor package flags into several distinct types. · 998739df
      Edward Z. Yang authored
      
      Summary:
      Previously, all package flags (-package, -trust-package,
      -ignore-package) were bundled up into a single packageFlags
      field in DynFlags, under a single type.  This commit separates
      them based on what they do.
      
      This is a nice improvement, because it means that Packages can
      then be refactored so that a number of functions are "tighter":
      
          - We know longer have to partition PackageFlags into
            the ignore flag and other flags; ignore flags are just
            put into their own field.
      
          - Trust flags modify the package database, but exposed
            flags do not (they modify the visibility map); now
            applyPackageFlag and applyTrustFlag have tighter signatures
            which reflect this.
      
      This patch was motivated by the need to have a separate visibility
      map for plugin packages, which will be in a companion patch.
      
      Signed-off-by: default avatarEdward Z. Yang <ezyang@cs.stanford.edu>
      
      Test Plan: validate
      
      Reviewers: austin, bgamari, duncan
      
      Subscribers: thomie
      
      Differential Revision: https://phabricator.haskell.org/D1659
      998739df
    • Richard Eisenberg's avatar
      CoercionN is not in scope in TyCoRep · 21b25dff
      Richard Eisenberg authored
      21b25dff
    • Richard Eisenberg's avatar
      Tweak comments around UnivCos. · d3ce4172
      Richard Eisenberg authored
      d3ce4172
    • Alan Zimmerman's avatar
      APIAnnotations:AnnComma in wrong place in qcnames1 · 721d56d5
      Alan Zimmerman authored
      The list is reversed when it is used, so the comma must be added to the
      item at the front of it, to be following it when used.
      721d56d5
    • Simon Peyton Jones's avatar
      Refactor named wildcards (again) · 575a98e4
      Simon Peyton Jones authored
      Michal's work on #10982, #11098, refactored the handling of named
      wildcards by making them more like ordinary type variables.
      
      This patch takes the same idea to its logical conclusion, resulting
      in a much tidier, tighter implementation.
      
      Read Note [The wildcard story for types] in HsTypes.
      
      Changes:
      
       * Named wildcards are ordinary type variables, throughout
      
       * HsType no longer has a data constructor for named wildcards
         (was NamedWildCard in HsWildCardInfo).  Named wildcards are
         simply HsTyVars
      
       * Similarly named wildcards disappear from Template Haskell
      
       * I refactored RnTypes to avoid polluting LocalRdrEnv with something
         as narrow as named wildcards.  Instead the named wildcard set is
         carried in RnTyKiEnv.
      
      There is a submodule update for Haddock.
      575a98e4
    • Ben Gamari's avatar
      Remove another duplicate test · 01b0461e
      Ben Gamari authored
      01b0461e
    • Alan Zimmerman's avatar
      Localize API Annotation in LInjectivtyAnn · 7966eea9
      Alan Zimmerman authored
      The injectivity_cond production in Parser.y returns the annotation for
      the '->' to the calling production, rather than applying it directly.
      
      Rather apply it directly, so LInjectivityAnn can be rendered as a unit
      from the API Annotations.
      7966eea9
    • Ben Gamari's avatar
      Remove duplicate T11224 test definition · 51d83302
      Ben Gamari authored
      51d83302
    • Simon Peyton Jones's avatar
      Fix typechecking for pattern synonym signatures · f40e122b
      Simon Peyton Jones authored
      Various tickets have revealed bad shortcomings in the typechecking of
      pattern type synonyms.  Discussed a lot in (the latter part of)
      Trac #11224.
      
      This patch fixes the most complex issues:
      
      - Both parser and renamer now treat pattern synonyms as an
        ordinary LHsSigType.  Nothing special.  Hooray.
      
      - tcPatSynSig (now in TcPatSyn) typechecks the signature, and
        decomposes it into its pieces.
        See Note [Pattern synonym signatures]
      
      - tcCheckPatSyn has had a lot of refactoring.
        See Note [Checking against a pattern signature]
      
      The result is a lot tidier and more comprehensible.
      Plus, it actually works!
      
      NB: this patch doesn't actually address the precise
          target of #11224, namely "inlining pattern synonym
          does not preserve semantics".  That's an unrelated
          bug, with a separate patch.
      
      ToDo: better documentation in the user manual
      
      Test Plan: Validate
      
      Reviewers: austin, hvr, goldfire
      
      Subscribers: goldfire, mpickering, thomie, simonpj
      
      Differential Revision: https://phabricator.haskell.org/D1685
      
      GHC Trac Issues: #11224
      f40e122b
    • Simon Peyton Jones's avatar
      Fix grouping for pattern synonyms · 29928f29
      Simon Peyton Jones authored
      When grouping pattern synonyms in the desugarer, to find when a single
      match will work for the whole group, we use `Match.sameGroup`.  But this
      function was declaring two pattern-synonym matches equal to often.
      Result: Lint errors and broken semantics.
      
      The fix is easy.  See Note [Pattern synonym groups].
      
      Re-do typechecking for pattern synonym signatures
      
      Test Plan: Validate
      
      Reviewers: austin
      
      Subscribers: thomie, mpickering, simonpj
      
      Differential Revision: https://phabricator.haskell.org/D1684
      29928f29
    • Herbert Valerio Riedel's avatar
      Update stm submodule to v2.4.4.1 release · 6eabd93d
      Herbert Valerio Riedel authored
      This `stm` release also addresses #10967
      6eabd93d
    • Ryan Scott's avatar
      Rework Template Haskell's handling of strictness · f975b0b1
      Ryan Scott authored
      Currently, Template Haskell's treatment of strictness is not enough to
      cover all possible combinations of unpackedness and strictness. In
      addition, it isn't equipped to deal with new features (such as
      `-XStrictData`) which can change a datatype's fields' strictness during
      compilation.
      
      To address this, I replaced TH's `Strict` datatype with
      `SourceUnpackedness` and `SourceStrictness` (which give the programmer a
      more complete toolkit to configure a datatype field's strictness than
      just `IsStrict`, `IsLazy`, and `Unpack`). I also added the ability to
      reify a constructor fields' strictness post-compilation through the
      `reifyConStrictness` function.
      
      Fixes #10697.
      
      Test Plan: ./validate
      
      Reviewers: simonpj, goldfire, bgamari, austin
      
      Reviewed By: goldfire, bgamari
      
      Subscribers: thomie
      
      Differential Revision: https://phabricator.haskell.org/D1603
      
      GHC Trac Issues: #10697
      f975b0b1
    • Alan Zimmerman's avatar
      Retain AnnTilde in splitTildeApps · b407bd77
      Alan Zimmerman authored
      splitTildeApps can introduce a new HsAppInfix for a tilde, with a fresh
      SrcSpan, disconnecting its existing AnnTilde API Annotation.
      
      A tilde needs AnnTilde to render properly, this patch adds a new one on
      the fresh SrcSpan
      b407bd77
    • Simon Peyton Jones's avatar
      Comments only, about coercion holes · ea3f733a
      Simon Peyton Jones authored
      Richard, pls take a look
      ea3f733a
    • Herbert Valerio Riedel's avatar
      Update Cabal submodule to latest snapshot · 44de66b6
      Herbert Valerio Riedel authored
      The addition of several new Semigroup instances caused
      a Haddock allocation increase.
      44de66b6
    • Alan Zimmerman's avatar
      Make HsAppsType contents Located · ff923954
      Alan Zimmerman authored
      An HsAppInfix can carry a qconop/varop preceded by a SIMPLEQUOTE as a
      Located RdrName.
      
      In this case AnnSimpleQuote is attached to the Located HsAppType.
      
          | SIMPLEQUOTE qconop            {% ams (sLL $1 $> $ HsAppInfix $2)
                                                 [mj AnnSimpleQuote $1] }
          | SIMPLEQUOTE varop             {% ams (sLL $1 $> $ HsAppInfix $2)
                                                 [mj AnnSimpleQuote $1] }
      
      This patch changes
      
          data HsType name
            ...
            | HsAppsTy [HsAppType name]
      
      to
      
          data HsType name
            ...
            | HsAppsTy [LHsAppType name]
      
      so that the annotation is not discarded when it reaches the ParsedSource
      ff923954
    • Tamar Christina's avatar
      Fix GHCi segfault in Windows 32bit · aa7fb9a6
      Tamar Christina authored
      Summary:
      Add missing calling convention to function pointer,
      incorrect `cdecl` calling convention which should be `stdcall`
      on x86 was causing the stack to be corrupted. When it tried to
      return from the function the return pointer would be invalid.
      
      Test Plan: ./validate
      
      Reviewers: austin, erikd, bgamari, thomie
      
      Reviewed By: bgamari, thomie
      
      Differential Revision: https://phabricator.haskell.org/D1683
      
      GHC Trac Issues: #11234
      aa7fb9a6
  2. Dec 21, 2015
    • Herbert Valerio Riedel's avatar
      Update hoopl submodule to final 3.10.2.1 release · c12fc2e6
      Herbert Valerio Riedel authored
      This is the designated release to go with GHC 8.0.1
      
      /cc @mlite
      c12fc2e6
    • Ben Gamari's avatar
      083b7006
    • Ben Gamari's avatar
      base: Add sections to changelog · fb3302c9
      Ben Gamari authored
      fb3302c9
    • Ben Gamari's avatar
    • duairc's avatar
      Added missing instances for Identity and Const (#11210) · 2dff6c18
      duairc authored
      The following instances are added
      
          instance Bounded a => Bounded (Const a b)
          instance Enum a => Enum (Const a b)
          instance Ix a => Ix (Const a b)
          instance Storable a => Storable (Const a b)
      
          instance Bounded a => Bounded (Identity a)
          instance Enum a => Enum (Identity a)
          instance Ix a => Ix (Identity a)
          instance Semigroup a => Semigroup (Identity a)
          instance Storable a => Storable (Identity a)
      
      Reviewers: ekmett, RyanGlScott, rwbarton, hvr, austin, bgamari
      
      Reviewed By: RyanGlScott, hvr
      
      Subscribers: rwbarton, RyanGlScott, thomie
      
      Differential Revision: https://phabricator.haskell.org/D1626
      
      GHC Trac Issues: #11210
      2dff6c18
    • Edward Z. Yang's avatar
      Fix #11256 by not immediately erroring if we can't find a module. · ff3f918d
      Edward Z. Yang authored
      Test Plan: validate
      
      Reviewers: austin, bgamari, thomie
      
      Reviewed By: bgamari, thomie
      
      Differential Revision: https://phabricator.haskell.org/D1669
      
      GHC Trac Issues: #11256
      ff3f918d
    • Herbert Valerio Riedel's avatar
      Rename GHCi's UI modules into GHCi.UI(.*) · 55250a63
      Herbert Valerio Riedel authored
      Further work refactoring and enhancing GHCi will make it desirable to
      split up GHCi's code-base into multiple modules with specific functions,
      and rather than have several top-level 'Ghci*' modules, it's nicer to
      have a common namespace. This commit is provides the basis for that.
      
      Note that the remaining GHCi.* namespace belongs to the new `ghci`
      package.
      
      Differential Revision: https://phabricator.haskell.org/D1593
      55250a63
    • Jan Stolarek's avatar
      Add proper GADTs support to Template Haskell · eeecb864
      Jan Stolarek authored
      Until now GADTs were supported in Template Haskell by encoding them using
      normal data types.  This patch adds proper support for representing GADTs
      in TH.
      
      Test Plan: T10828
      
      Reviewers: goldfire, austin, bgamari
      
      Subscribers: thomie, mpickering
      
      Differential Revision: https://phabricator.haskell.org/D1465
      
      GHC Trac Issues: #10828
      eeecb864
    • Ben Gamari's avatar
      testsuite: Add testcase for #8316 · a61e717f
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      This is still broken but really out to be fixed. At least know we'll
      know if someone fixes it inadvertently.
      
      Test Plan: validate
      
      Reviewers: austin
      
      Reviewed By: austin
      
      Subscribers: thomie
      
      Differential Revision: https://phabricator.haskell.org/D1682
      
      GHC Trac Issues: #8316
      a61e717f
    • Ben Gamari's avatar
      testsuite/ClassOperator: This actually should_fail · fd1b5ae7
      Ben Gamari authored
      See #11264 for details.
      fd1b5ae7
    • Ömer Sinan Ağacan's avatar
    • Simon Marlow's avatar
      Maintain cost-centre stacks in the interpreter · c8c44fd9
      Simon Marlow authored
      Summary:
      Breakpoints become SCCs, so we have detailed call-stack info for
      interpreted code.  Currently this only works when GHC is compiled with
      -prof, but D1562 (Remote GHCi) removes this constraint so that in the
      future call stacks will be available without building your own GHCi.
      
      How can you get a stack trace?
      
      * programmatically: GHC.Stack.currentCallStack
      * I've added an experimental :where command that shows the stack when
        stopped at a breakpoint
      * `error` attaches a call stack automatically, although since calls to
        `error` are often lifted out to the top level, this is less useful
        than it might be (ImplicitParams still works though).
      * Later we might attach call stacks to all exceptions
      
      Other related changes in this diff:
      
      * I reduced the number of places that get ticks attached for
        breakpoints.  In particular there was a breakpoint around the whole
        declaration, which was often redundant because it bound no variables.
        This reduces clutter in the stack traces and speeds up compilation.
      
      * I tidied up some RealSrcSpan stuff in InteractiveUI, and made a few
        other small cleanups
      
      Test Plan: validate
      
      Reviewers: ezyang, bgamari, austin, hvr
      
      Subscribers: thomie
      
      Differential Revision: https://phabricator.haskell.org/D1595
      
      GHC Trac Issues: #11047
      c8c44fd9
    • Ryan Scott's avatar
      Encode strictness in GHC generics metadata · ee6fba89
      Ryan Scott authored
      This augments `MetaSel` with a `Bang` field, which gives generic
      programmers access to the following information about each field
      selector:
      
      * `SourceUnpackedness`: whether a field was marked `{-# NOUNPACK #-}`,
        `{-# UNPACK #-}`, or not
      * `SourceStrictness`: whether a field was given a strictness (`!`) or
        laziness (`~`) annotation
      * `DecidedStrictness`: what strictness GHC infers for a field during
        compilation, which may be influenced by optimization levels,
        `-XStrictData`, `-funbox-strict-fields`, etc.
      
      Unlike in Phab:D1603, generics does not grant a programmer the ability
      to "splice" in metadata, so there is no issue including
      `DecidedStrictness` with `Bang` (whereas in Template Haskell, it had to
      be split off).
      
      One consequence of this is that `MetaNoSel` had to be removed, since it
      became redundant. The `NoSelector` empty data type was also removed for
      similar reasons.
      
      Fixes #10716.
      
      Test Plan: ./validate
      
      Reviewers: dreixel, goldfire, kosmikus, austin, hvr, bgamari
      
      Reviewed By: bgamari
      
      Subscribers: thomie
      
      Differential Revision: https://phabricator.haskell.org/D1646
      
      GHC Trac Issues: #10716
      ee6fba89
    • Herbert Valerio Riedel's avatar
      Fix-up GHC 7.12 artifacts · 99b956ef
      Herbert Valerio Riedel authored
      The haddock submodule also still assumed that GHC 7.12 would be the next
      major release (rather than GHC 8.0)
      99b956ef
    • Alan Zimmerman's avatar
      Fix AnnDotDot in module export · e29ee494
      Alan Zimmerman authored
      The annotation for the ".." in
      
          module GADTRecords2 (H1(..)) where
      
      was in the wrong place
      e29ee494
    • Herbert Valerio Riedel's avatar
      Minor clean-up to ghc-bin.cabal.in · 25db56c2
      Herbert Valerio Riedel authored
      This has been factored out of D1673
      25db56c2
    • Ben Gamari's avatar
      testsuite: Add ClassOperator testcase · 9f23dd9d
      Ben Gamari authored and Ben Gamari's avatar Ben Gamari committed
      This is derived from Haddock's `Operators` `html-test`, which appears to
      fail with GHC master yet compiles with 7.10.2
      
      Reviewers: simonpj, austin
      
      Subscribers: thomie
      
      Differential Revision: https://phabricator.haskell.org/D1667
      
      GHC Trac Issues: #11264
      9f23dd9d
    • dolio's avatar
      Implement phase 1 of expanded Floating · 6457903e
      dolio authored and Ben Gamari's avatar Ben Gamari committed
      - This part of the proposal is to add log1p, expm1, log1pexp and
        log1mexp to the Floating class, and export the full Floating class
        from Numeric
      
      Reviewers: ekmett, #core_libraries_committee, bgamari, hvr, austin
      
      Reviewed By: ekmett, #core_libraries_committee, bgamari
      
      Subscribers: Phyx, RyanGlScott, ekmett, thomie
      
      Differential Revision: https://phabricator.haskell.org/D1605
      
      GHC Trac Issues: #11166
      6457903e
    • duairc's avatar
      Move Const to own module in Data.Functor.Const and enable PolyKinds · edcf17bd
      duairc authored
      `Const` from `Control.Applicative` can trivially be made
      kind-polymorphic in its second argument. There has been a Trac issue
      about this for nearly a year now. It doesn't look like anybody objects
      to it, so I figured I might as well make a patch.
      
      Trac Issues: #10039, #10865, #11135
      
      Differential Revision: https://phabricator.haskell.org/D1630
      
      Reviewers: ekmett, hvr, bgamari
      
      Subscribers: RyanGlScott, thomie
      edcf17bd
    • msosn's avatar
      Warn about unused type variables in type families · eb7796f1
      msosn authored and Ben Gamari's avatar Ben Gamari committed
      The warnings are enabled with the flag -fwarn-unused-matches, the same
      one that enables warnings on the term level.
      
      Identifiers starting with an underscore are now always parsed as type
      variables.  When the NamedWildCards extension is enabled, the renamer
      replaces those variables with named wildcards.
      
      An additional NameSet nwcs is added to LocalRdrEnv. It's used to keep
      names of the type variables that should be replaced with wildcards.
      
      While renaming HsForAllTy, when a name is explicitly bound it is removed
      from the nwcs NameSet. As a result, the renamer doesn't replace them in
      the quantifier body. (Trac #11098)
      
      Fixes #10982, #11098
      
      Reviewers: alanz, bgamari, hvr, austin, jstolarek
      
      Reviewed By: jstolarek
      
      Subscribers: goldfire, mpickering, RyanGlScott, thomie
      
      Differential Revision: https://phabricator.haskell.org/D1576
      
      GHC Trac Issues: #10982
      eb7796f1
    • dolio's avatar
      Modify IsString String instance (fixes #10814) · b225b234
      dolio authored and Ben Gamari's avatar Ben Gamari committed
      The new instance resolves to `s ~ [Char]` as soon as we know that `s ~
      [a]`, to avoid certain functions (like (++)) causing a situation where
      `a` is ambiguous and (currently) unable to be defaulted.
      
      Reviewers: #core_libraries_committee, hvr, austin, bgamari
      
      Reviewed By: hvr, bgamari
      
      Subscribers: thomie
      
      Differential Revision: https://phabricator.haskell.org/D1572
      
      GHC Trac Issues: #10814
      b225b234
    • Alan Zimmerman's avatar
      Add Location to RdrName in FieldOcc · d8ed20c8
      Alan Zimmerman authored
      Summary:
      Post #11019, there have been some new instances of RdrName that are not
      located, in particular
      
      ```#!hs
      data FieldOcc name = FieldOcc { rdrNameFieldOcc  :: RdrName
                                    , selectorFieldOcc :: PostRn name name
                                    }
      
      data AmbiguousFieldOcc name
        = Unambiguous RdrName (PostRn name name)
        | Ambiguous   RdrName (PostTc name name)
        deriving (Typeable)
      ```
      Add locations to them
      
      Updates haddock submodule to match
      
      Test Plan: ./validate
      
      Reviewers: goldfire, hvr, bgamari, austin
      
      Reviewed By: hvr
      
      Subscribers: hvr, thomie, mpickering
      
      Differential Revision: https://phabricator.haskell.org/D1670
      
      GHC Trac Issues: #11258
      d8ed20c8
Loading