Takenobu Tani [Sat, 27 Apr 2019 11:54:21 +0000 (20:54 +0900)]
users-guide: Fix directive errors on 8.10
The following sections are not displayed due to a directive error:
* -Wunused-record-wildcards
* -Wredundant-record-wildcards
I changed the location of the `since` directive.
[skip ci]
David Eichmann [Mon, 20 May 2019 18:45:56 +0000 (19:45 +0100)]
Recalculate Performance Test Baseline T9630 #16680
Metric Decrease:
T9630
David Eichmann [Thu, 16 May 2019 12:19:38 +0000 (13:19 +0100)]
Improve test runner logging when calculating performance metric baseline #16662
We attempt to get 75 commit hashes via `git log`, but this only gave 10
hashes in a CI run (see #16662). Better logging may help solve this
error if it occurs again in the future.
Ben Gamari [Thu, 16 May 2019 16:47:59 +0000 (12:47 -0400)]
rts: Explicit state that CONSTR tag field is zero-based
This was a bit unclear as we use both one-based and zero-based
tags in GHC.
[skip ci]
Alp Mestanogullari [Thu, 9 May 2019 13:09:45 +0000 (15:09 +0200)]
Hadrian: 'need' source files for various docs in Rules.Documentation
Previously, changing one of the .rst files from the user guide would not cause
the user guide to be rebuilt. This patch take a first stab at declaring the
documentation source files that our documentation rules depend on, focusing
on the .rst files only for now.
We eventually might want to rebuild docs when we, say, change the haddock style
file, but this level of tracking isn't really necessary for now.
This fixes #16645.
Vladislav Zavialov [Thu, 9 May 2019 08:01:17 +0000 (11:01 +0300)]
Restore the --coerce option in 'happy' configuration
happy-1.19.10 has been released with a fix for --coerce in the presence
of higher rank types. This should result in about 10% performance
improvement in the parser.
Vladislav Zavialov [Wed, 8 May 2019 22:53:26 +0000 (01:53 +0300)]
Guard CUSKs behind a language pragma
GHC Proposal #36 describes a transition plan away from CUSKs and to
top-level kind signatures:
1. Introduce a new extension, -XCUSKs, on by default, that detects CUSKs
as they currently exist.
2. We turn off the -XCUSKs extension in a few releases and remove it
sometime thereafter.
This patch implements phase 1 of this plan, introducing a new language
extension to control whether CUSKs are enabled. When top-level kind
signatures are implemented, we can transition to phase 2.
Vladislav Zavialov [Wed, 8 May 2019 18:47:38 +0000 (21:47 +0300)]
Add a minimized regression test for #12928
Oleg Grenrus [Wed, 8 May 2019 06:35:15 +0000 (09:35 +0300)]
Update terminal title while running test-suite
Useful progress indicator even when `make test VERBOSE=1`,
and when you do something else, but have terminal title visible.
John Ericson [Wed, 27 Mar 2019 04:27:01 +0000 (00:27 -0400)]
Remove all target-specific portions of Config.hs
1. If GHC is to be multi-target, these cannot be baked in at compile
time.
2. Compile-time flags have a higher maintenance than run-time flags.
3. The old way makes build system implementation (various bootstrapping
details) with the thing being built. E.g. GHC doesn't need to care
about which integer library *will* be used---this is purely a crutch
so the build system doesn't need to pass flags later when using that
library.
4. Experience with cross compilation in Nixpkgs has shown things work
nicer when compiler's can *optionally* delegate the bootstrapping the
package manager. The package manager knows the entire end-goal build
plan, and thus can make top-down decisions on bootstrapping. GHC can
just worry about GHC, not even core library like base and ghc-prim!
John Ericson [Tue, 7 May 2019 23:09:25 +0000 (19:09 -0400)]
Dont refer to `cLeadingUnderscore` in test
Can't use this config entry because it's about to go away
John Ericson [Sun, 7 Apr 2019 14:24:03 +0000 (10:24 -0400)]
hadrian: Make settings stage specific
Kevin Buhr [Tue, 7 May 2019 02:40:37 +0000 (21:40 -0500)]
Add regression test for old parser issue #504
Giles Anderson [Mon, 8 Apr 2019 19:52:51 +0000 (21:52 +0200)]
Change GHC.hs to Packages.hs in Hadrian user-settings.md
... "all packages that are currently built as part of the GHC are
defined in src/Packages.hs"
Kevin Buhr [Tue, 7 May 2019 00:24:31 +0000 (19:24 -0500)]
Add regression test case for old issue #493
Ben Gamari [Mon, 6 May 2019 13:34:19 +0000 (09:34 -0400)]
gitlab-ci: Disable cleanup job on Windows
As discussed in the Note, we now have a cron job to handle this and the
cleanup job itself is quite fragile.
[skip ci]
David Eichmann [Tue, 30 Apr 2019 11:02:41 +0000 (12:02 +0100)]
Hadrian: programs need registered ghc-pkg libraries
In Hadrian, building programs (e.g. `ghc` or `haddock`) requires libraries located in the ghc-pkg package database i.e.
_build/stage1/lib/x86_64-linux-ghc-8.9.0.
20190430/libHSdeepseq-1.4.4.0-ghc8.9.0.
20190430.so
Add the corresponding `need`s for these library files and the subsequent rules.
Roland Senn [Sun, 14 Apr 2019 12:21:40 +0000 (14:21 +0200)]
Fix bugs and documentation for #13456
Oleg Grenrus [Thu, 11 Apr 2019 13:46:06 +0000 (16:46 +0300)]
Add Generic tuple instances up to 15-tuple
Why 15? Because we have Eq instances up to 15.
Metric Increase:
T9630
haddock.base
Vladislav Zavialov [Tue, 7 May 2019 15:17:44 +0000 (18:17 +0300)]
Add a regression test for #14548
Kevin Buhr [Tue, 7 May 2019 04:32:42 +0000 (23:32 -0500)]
Add regression test for old issue #507
John Ericson [Wed, 27 Mar 2019 03:48:47 +0000 (23:48 -0400)]
Purge TargetPlatform_NAME and cTargetPlatformString
Richard Eisenberg [Sat, 4 May 2019 02:04:19 +0000 (22:04 -0400)]
Regression test for #16627.
test: typecheck/should_fail/T16627
Ömer Sinan Ağacan [Thu, 2 May 2019 10:48:09 +0000 (13:48 +0300)]
Print PAP object address in stg_PAP_info entry code
Continuation to
ce23451c
Kevin Buhr [Wed, 1 May 2019 22:13:33 +0000 (17:13 -0500)]
stg_floatToWord32zh: zero-extend the Word32 (#16617)
The primop stgFloatToWord32 was sign-extending the 32-bit word, resulting
in weird negative Word32s. Zero-extend them instead.
Closes #16617.
Shayne Fletcher [Tue, 7 May 2019 21:35:50 +0000 (17:35 -0400)]
Implement ImportQualifiedPost
Ryan Scott [Tue, 7 May 2019 12:56:30 +0000 (08:56 -0400)]
Fix #16632 by using the correct SrcSpan in checkTyClHdr
`checkTyClHdr`'s case for `HsTyVar` was grabbing the wrong `SrcSpan`,
which lead to error messages pointing to the wrong location. Easily
fixed.
Ryan Scott [Sat, 4 May 2019 15:05:20 +0000 (11:05 -0400)]
Fix #16603 by documenting some important changes in changelogs
This addresses some glaring omissions from
`libraries/base/changelog.md` and
`docs/users_guide/8.8.1-notes.rst`, fixing #16603 in the process.
Kevin Buhr [Tue, 7 May 2019 02:42:33 +0000 (21:42 -0500)]
Add regression test for old typechecking issue #505
Ryan Scott [Mon, 6 May 2019 18:49:44 +0000 (14:49 -0400)]
Check for duplicate variables in associated default equations
A follow-up to !696's, which attempted to clean up the error messages
for ill formed associated type family default equations. The previous
attempt, !696, forgot to account for the possibility of duplicate
kind variable arguments, as in the following example:
```hs
class C (a :: j) where
type T (a :: j) (b :: k)
type T (a :: k) (b :: k) = k
```
This patch addresses this shortcoming by adding an additional check
for this. Fixes #13971 (hopefully for good this time).
Ryan Scott [Sat, 4 May 2019 14:30:47 +0000 (10:30 -0400)]
Add /includes/dist to .gitignore
As of commit
d37d91e9a444a7822eef1558198d21511558515e, the GHC build
now autogenerates a `includes/dist/build/settings` file. To avoid
dirtying the current `git` status, this adds `includes/dist` to
`.gitignore`.
[ci skip]
Alp Mestanogullari [Tue, 23 Apr 2019 12:46:42 +0000 (14:46 +0200)]
Hadrian: override $(ghc-config-mk), to prevent redundant config generation
This required making the 'ghc-config-mk' variable overridable in
testsuite/mk/boilerplate.mk, and then making use of this in hadrian
to point to '<build root>/test/ghcconfig' instead, which is where we
always put the test config.
Previously, we would build ghc-config and run it against the
GHC to be tested, a second time, while we're running the tests, because some
include testsuite/mk/boilerplate.mk. This was causing unexpected output
failures.
Alp Mestanogullari [Fri, 3 May 2019 10:21:44 +0000 (12:21 +0200)]
Enable external interpreter when TH is requested but no internal interpreter is available
Takenobu Tani [Mon, 29 Apr 2019 09:12:31 +0000 (18:12 +0900)]
Remove `$(TOP)/ANNOUNCE` file
Remove `$(TOP)/ANNOUNCE` because maintaining this file is expensive
for each release.
Currently, release announcements of ghc are made on ghc blogs and wikis.
[skip ci]
John Ericson [Wed, 27 Mar 2019 04:27:01 +0000 (00:27 -0400)]
Remove cGhcEnableTablesNextToCode
Get "Tables next to code" from the settings file instead.
Vladislav Zavialov [Thu, 2 May 2019 04:42:16 +0000 (07:42 +0300)]
'warnSpaceAfterBang' only in patterns (#16619)
Chaitanya Koparkar [Fri, 19 Apr 2019 13:50:54 +0000 (09:50 -0400)]
Fix #16593 by having only one definition of -fprint-explicit-runtime-reps
[skip ci]
gallais [Fri, 3 May 2019 08:24:21 +0000 (04:24 -0400)]
[ typo ] 'castFloatToWord32' -> 'castFloatToWord64'
Probably due to a copy/paste gone wrong.
iustin [Fri, 26 Apr 2019 13:07:33 +0000 (09:07 -0400)]
Fix typo in 8.8.1 notes related to traceBinaryEvent
- fixes double mention of `traceBinaryEvent#` (the second one should be `traceEvent#`, I think)
- fixes note about `traceEvent#` taking a `String` - the docs say it takes a zero-terminated ByteString.
Ömer Sinan Ağacan [Fri, 3 May 2019 05:13:57 +0000 (08:13 +0300)]
PrimOps.cmm: remove unused stuff
Ömer Sinan Ağacan [Fri, 3 May 2019 05:12:48 +0000 (08:12 +0300)]
StgCmmMonad: remove emitProc_, don't export emitProc
Ömer Sinan Ağacan [Wed, 1 May 2019 15:40:33 +0000 (18:40 +0300)]
rts: Properly free the RTSSummaryStats structure
`stat_exit` always allocates a `RTSSummaryStats` but only sometimes
frees it, which casues leaks. With this patch we unconditionally free
the structure, fixing the leak.
Fixes #16584
Ryan Scott [Tue, 30 Apr 2019 15:28:41 +0000 (11:28 -0400)]
Make equality constraints in kinds invisible
Issues #12102 and #15872 revealed something strange about the way GHC
handles equality constraints in kinds: it treats them as _visible_
arguments! This causes a litany of strange effects, from strange
error messages
(https://gitlab.haskell.org/ghc/ghc/issues/12102#note_169035)
to bizarre `Eq#`-related things leaking through to GHCi output, even
without any special flags enabled.
This patch is an attempt to contain some of this strangeness.
In particular:
* In `TcHsType.etaExpandAlgTyCon`, we propagate through the
`AnonArgFlag`s of any `Anon` binders. Previously, we were always
hard-coding them to `VisArg`, which meant that invisible binders
(like those whose kinds were equality constraint) would mistakenly
get flagged as visible.
* In `ToIface.toIfaceAppArgsX`, we previously assumed that the
argument to a `FunTy` always corresponding to a `Required`
argument. We now dispatch on the `FunTy`'s `AnonArgFlag` and map
`VisArg` to `Required` and `InvisArg` to `Inferred`. As a
consequence, the iface pretty-printer correctly recognizes that
equality coercions are inferred arguments, and as a result,
only displays them in `-fprint-explicit-kinds` is enabled.
* Speaking of iface pretty-printing, `Anon InvisArg` binders were
previously being pretty-printed like `T (a :: b ~ c)`, as if they
were required. This seemed inconsistent with other invisible
arguments (that are printed like `T @{d}`), so I decided to switch
this to `T @{a :: b ~ c}`.
Along the way, I also cleaned up a minor inaccuracy in the users'
guide section for constraints in kinds that was spotted in
https://gitlab.haskell.org/ghc/ghc/issues/12102#note_136220.
Fixes #12102 and #15872.
Ömer Sinan Ağacan [Tue, 30 Apr 2019 09:42:08 +0000 (12:42 +0300)]
Fix interface version number printing in --show-iface
Before
Version: Wanted [8, 0, 9, 0, 2, 0, 1, 9, 0, 4, 2, 5],
got [8, 0, 9, 0, 2, 0, 1, 9, 0, 4, 2, 5]
After
Version: Wanted
809020190425,
got
809020190425
Ningning Xie [Mon, 29 Apr 2019 14:57:37 +0000 (22:57 +0800)]
Only skip decls with CUSKs with PolyKinds on (fix #16609)
Vladislav Zavialov [Tue, 23 Apr 2019 18:21:33 +0000 (21:21 +0300)]
Pattern/expression ambiguity resolution
This patch removes 'EWildPat', 'EAsPat', 'EViewPat', and 'ELazyPat'
from 'HsExpr' by using the ambiguity resolution system introduced
earlier for the command/expression ambiguity.
Problem: there are places in the grammar where we do not know whether we
are parsing an expression or a pattern, for example:
do { Con a b <- x } -- 'Con a b' is a pattern
do { Con a b } -- 'Con a b' is an expression
Until we encounter binding syntax (<-) we don't know whether to parse
'Con a b' as an expression or a pattern.
The old solution was to parse as HsExpr always, and rejig later:
checkPattern :: LHsExpr GhcPs -> P (LPat GhcPs)
This meant polluting 'HsExpr' with pattern-related constructors. In
other words, limitations of the parser were affecting the AST, and all
other code (the renamer, the typechecker) had to deal with these extra
constructors.
We fix this abstraction leak by parsing into an overloaded
representation:
class DisambECP b where ...
newtype ECP = ECP { runECP_PV :: forall b. DisambECP b => PV (Located b) }
See Note [Ambiguous syntactic categories] for details.
Now the intricacies of parsing have no effect on the hsSyn AST when it
comes to the expression/pattern ambiguity.
Alp Mestanogullari [Fri, 26 Apr 2019 11:58:32 +0000 (13:58 +0200)]
Hadrian: generate JUnit testsuite report in Linux CI job
We also keep it as an artifact, like we do for non-Hadrian jobs, and list it
as a junit report, so that the test results are reported in the GitLab UI for
merge requests.
Ben Gamari [Fri, 26 Apr 2019 04:54:21 +0000 (00:54 -0400)]
testsuite: Mark concprog001 as fragile
Due to #16604.
Shayne Fletcher [Thu, 25 Apr 2019 15:09:00 +0000 (11:09 -0400)]
Make Extension derive Bounded
Sven Tennie [Mon, 22 Apr 2019 23:35:33 +0000 (01:35 +0200)]
Typeset Big-O complexities with Tex-style notation (#16090)
Use `\min` instead of `min` to typeset it as an operator.
Ben Gamari [Tue, 16 Apr 2019 19:19:01 +0000 (15:19 -0400)]
Emit GHC timing events to eventlog
Ben Gamari [Sun, 14 Apr 2019 21:05:50 +0000 (17:05 -0400)]
ErrUtils: Emit progress messages to eventlog
Alp Mestanogullari [Mon, 15 Apr 2019 11:52:34 +0000 (13:52 +0200)]
Build Hadrian with -Werror in the 'ghc-in-ghci' CI job
John Ericson [Thu, 4 Apr 2019 17:38:53 +0000 (13:38 -0400)]
Move cGHC_UNLIT_PGM to be "unlit command" in settings
The bulk of the work was done in #712, making settings be make/Hadrian
controlled. This commit then just moves the unlit command rules in
make/Hadrian from the `Config.hs` generator to the `settings` generator
in each build system.
I think this is a good change because the crucial benefit is *settings*
don't affect the build: ghc gets one baby step closer to being a regular
cabal executable, and make/Hadrian just maintains settings as part of
bootstrapping.
John Ericson [Wed, 3 Apr 2019 20:31:59 +0000 (16:31 -0400)]
Remove settings.in
It is no longer needed
John Ericson [Wed, 3 Apr 2019 13:32:05 +0000 (09:32 -0400)]
Generate settings by make/hadrian instead of configure
This allows it to eventually become stage-specific
Sebastian Graf [Thu, 7 Feb 2019 14:34:07 +0000 (15:34 +0100)]
Compute demand signatures assuming idArity
This does four things:
1. Look at `idArity` instead of manifest lambdas to decide whether to use LetUp
2. Compute the strictness signature in LetDown assuming at least `idArity`
incoming arguments
3. Remove the special case for trivial RHSs, which is subsumed by 2
4. Don't perform the W/W split when doing so would eta expand a binding.
Otherwise we would eta expand PAPs, causing unnecessary churn in the
Simplifier.
NoFib Results
--------------------------------------------------------------------------------
Program Allocs Instrs
--------------------------------------------------------------------------------
fannkuch-redux +0.3% 0.0%
gg -0.0% -0.1%
maillist +0.2% +0.2%
minimax 0.0% +0.8%
pretty 0.0% -0.1%
reptile -0.0% -1.2%
--------------------------------------------------------------------------------
Min -0.0% -1.2%
Max +0.3% +0.8%
Geometric Mean +0.0% -0.0%
Ben Gamari [Fri, 12 Apr 2019 20:59:50 +0000 (16:59 -0400)]
ghci: Ensure that system libffi include path is searched
Previously hsc2hs failed when building against a system FFI.
Wojciech Baranowski [Wed, 24 Apr 2019 19:03:26 +0000 (22:03 +0300)]
Use pp_item
Wojciech Baranowski [Wed, 24 Apr 2019 18:54:42 +0000 (21:54 +0300)]
Suggest only local candidates from global env
Wojciech Baranowski [Wed, 24 Apr 2019 13:59:08 +0000 (16:59 +0300)]
Comment on 'candidates' function
Wojciech Baranowski [Tue, 23 Apr 2019 08:44:57 +0000 (11:44 +0300)]
osa1's patch: consistent suggestion message
Wojciech Baranowski [Sat, 13 Apr 2019 09:31:13 +0000 (12:31 +0300)]
Print suggestions in a single message
Wojciech Baranowski [Sun, 7 Apr 2019 16:25:05 +0000 (19:25 +0300)]
rename: hadle type signatures with typos
When encountering type signatures for unknown names, suggest similar
alternatives.
This fixes issue #16504
Ben Gamari [Thu, 25 Apr 2019 21:13:58 +0000 (17:13 -0400)]
gitlab-ci: Reintroduce DWARF-enabled bindists
It seems that this was inadvertently dropped in
1285d6b95fbae7858abbc4722bc2301d7fe40425.
Ben Gamari [Wed, 24 Apr 2019 17:10:54 +0000 (13:10 -0400)]
Update autoconf scripts
Scripts taken from autoconf
a8d79c3130da83c7cacd6fee31b9acc53799c406
Ben Gamari [Wed, 24 Apr 2019 17:16:51 +0000 (13:16 -0400)]
update-autoconf: Initial commit
Ömer Sinan Ağacan [Mon, 22 Apr 2019 06:58:56 +0000 (09:58 +0300)]
Minor RTS refactoring:
- Remove redundant casting in evacuate_static_object
- Remove redundant parens in STATIC_LINK
- Fix a typo in GC.c
Vladislav Zavialov [Tue, 26 Mar 2019 17:49:26 +0000 (20:49 +0300)]
checkPattern error hint is PV context
There is a hint added to error messages reported in checkPattern.
Instead of passing it manually, we put it in a ReaderT environment inside PV.
Vladislav Zavialov [Mon, 25 Mar 2019 10:33:32 +0000 (13:33 +0300)]
Introduce MonadP, make PV a newtype
Previously we defined type PV = P,
this had the downside that if we wanted to change PV,
we would have to modify P as well.
Now PV is free to evolve independently from P.
The common operations addError, addFatalError, getBit, addAnnsAt,
were abstracted into a class called MonadP.
Ben Gamari [Wed, 24 Apr 2019 16:16:10 +0000 (12:16 -0400)]
gitlab-ci: source-tarball job should have no dependencies
Alexandre Baldé [Tue, 9 Apr 2019 00:19:16 +0000 (01:19 +0100)]
Fix error message for './configure' regarding '--with-ghc' [skip ci]
Fraser Tweedale [Mon, 8 Apr 2019 07:27:06 +0000 (17:27 +1000)]
osReserveHeapMemory: handle signed rlim_t
rlim_t is a signed type on FreeBSD, and the build fails with a
sign-compare error. Add explicit (unsigned) cast to handle this
case.
Vladislav Zavialov [Fri, 19 Apr 2019 14:55:01 +0000 (17:55 +0300)]
Stop misusing EWildPat in pattern match coverage checking
EWildPat is a constructor of HsExpr used in the parser to represent
wildcards in ambiguous positions:
* in expression context, EWildPat is turned into hsHoleExpr (see rnExpr)
* in pattern context, EWildPat is turned into WildPat (see checkPattern)
Since EWildPat exists solely for the needs of the parser, we could
remove it by improving the parser.
However, EWildPat has also been used for a different purpose since
8a50610: to represent patterns that the coverage checker cannot handle.
Not only this is a misuse of EWildPat, it also stymies the removal of
EWildPat.
Alp Mestanogullari [Wed, 17 Apr 2019 15:14:08 +0000 (17:14 +0200)]
Hadrian: use the testsuite driver's config.haddock arg more correctly
4 haddock tests assume that .haddock files have been produced, by using the
'req_haddock' modifier. The testsuite driver assumes that this condition is
satisfied if 'config.haddock' is non-empty, but before this patch Hadrian was
always passing the path to where the haddock executable should be, regardless
of whether it is actually there or not.
Instead, we now pass an empty config.haddock when we can't find all of
<build root>/docs/html/libraries/<pkg>/<pkg>.haddock>, where <pkg> ranges over
array, base, ghc-prim, process and template-haskell, and pass the path
to haddock when all those file exists. This has the (desired) effect of skipping
the 4 tests (marked as 'missing library') when the docs haven't been built,
and running the haddock tests when they have.
Matthew Pickering [Wed, 17 Apr 2019 16:56:56 +0000 (17:56 +0100)]
Correct off by one error in ghci +c
Fixes #16569
Artem Pyanykh [Tue, 16 Apr 2019 16:30:16 +0000 (19:30 +0300)]
testsuite: fix ifdef lint errors under tests/rts/linker
Artem Pyanykh [Tue, 16 Apr 2019 16:10:31 +0000 (19:10 +0300)]
testsuite: move tests related to linker under tests/rts/linker
Andrew Martin [Tue, 16 Apr 2019 13:03:46 +0000 (09:03 -0400)]
[skip ci] correct the docs for casArray a little more. clarify that the returned element may be two different things
Andrew Martin [Sat, 13 Apr 2019 18:25:57 +0000 (14:25 -0400)]
[skip ci] correct formatting of casArray# in docs for casSmallArray#
Andrew Martin [Fri, 12 Apr 2019 12:45:36 +0000 (08:45 -0400)]
[skip ci] say "machine words" instead of "Int units" in the primops docs
Andrew Martin [Thu, 11 Apr 2019 01:11:03 +0000 (21:11 -0400)]
improve docs for casArray and casSmallArray
Ben Gamari [Sat, 6 Apr 2019 16:38:09 +0000 (12:38 -0400)]
users-guide: Add libraries section to 8.10.1 release notes
Ben Gamari [Sat, 6 Apr 2019 16:26:38 +0000 (12:26 -0400)]
users-guide: Add pretty to package list
Ben Gamari [Fri, 19 Apr 2019 04:16:57 +0000 (00:16 -0400)]
gitlab-ci: Do not build profiled libraries on 32-bit Windows
Due to #15934.
Ben Gamari [Thu, 11 Apr 2019 22:22:51 +0000 (18:22 -0400)]
gitlab-ci: Add centos7 release job
Ben Gamari [Fri, 12 Apr 2019 15:10:48 +0000 (11:10 -0400)]
gitlab-ci: Only run release notes lint on release tags
Ben Gamari [Sat, 20 Apr 2019 15:44:22 +0000 (11:44 -0400)]
gitlab-ci: Allow doc-tarball job to fail
Due to allowed failure of Windows job.
Ben Gamari [Sat, 20 Apr 2019 15:17:10 +0000 (11:17 -0400)]
gitlab-ci: Improve error message on failure of doc-tarball job
Previously the failure was quite nondescript.
Andrey Mokhov [Thu, 18 Apr 2019 22:52:17 +0000 (23:52 +0100)]
Hadrian: Drop old/unused CI scripts
Alec Theriault [Thu, 18 Apr 2019 19:53:56 +0000 (12:53 -0700)]
Haddock: support strict GADT args with docs
Rather than massaging the output of the parser to re-arrange docs and
bangs, it is simpler to patch the two places in which the strictness
info is needed (to accept that the `HsBangTy` may be inside an
`HsDocTy`).
Fixes #16585.
Vladislav Zavialov [Thu, 18 Apr 2019 21:36:00 +0000 (00:36 +0300)]
Tagless final encoding of ExpCmdI in the parser
Before this change, we used a roundabout encoding:
1. a GADT (ExpCmdG)
2. a class to pass it around (ExpCmdI)
3. helpers to match on it (ecHsApp, ecHsIf, ecHsCase, ...)
It is more straightforward to turn these helpers into class methods,
removing the need for a GADT.
klebinger.andreas@gmx.at [Mon, 15 Apr 2019 22:36:26 +0000 (00:36 +0200)]
Don't indent single alternative case expressions for STG.
Makes the width of STG dumps slightly saner.
Especially for things like unboxing.
Fixes #16580
Michal Terepeta [Sun, 14 Apr 2019 19:21:17 +0000 (21:21 +0200)]
StgCmmPrim: remove an unnecessary instruction in doNewArrayOp
Previously we would generate a local variable pointing after the array
header and use it to initialize the array elements. But we already use
stores with offset, so it's easy to just add the header to those offsets
during compilation and avoid generating the local variable (which would
become a LEA instruction when using native codegen; LLVM already
optimizes it away).
Signed-off-by: Michal Terepeta <michal.terepeta@gmail.com>
Alec Theriault [Wed, 17 Apr 2019 20:55:39 +0000 (13:55 -0700)]
Add test case for #16384
Now that `TExp` accepts unlifted types, #16384 is fixed. Since the real
issue there was GHC letting through an ill-kinded type which
`-dcore-lint` rightly rejected, a reasonable regression test is that
the program from #16384 can now be accepted without `-dcore-lint`
complaining.
Alec Theriault [Wed, 17 Apr 2019 15:07:52 +0000 (08:07 -0700)]
TH: make `Lift` and `TExp` levity-polymorphic
Besides the obvious benefits of being able to manipulate `TExp`'s of
unboxed types, this also simplified `-XDeriveLift` all while making
it more capable.
* `ghc-prim` is explicitly depended upon by `template-haskell`
* The following TH things are parametrized over `RuntimeRep`:
- `TExp(..)`
- `unTypeQ`
- `unsafeTExpCoerce`
- `Lift(..)`
* The following instances have been added to `Lift`:
- `Int#`, `Word#`, `Float#`, `Double#`, `Char#`, `Addr#`
- unboxed tuples of lifted types up to arity 7
- unboxed sums of lifted types up to arity 7
Ideally we would have levity-polymorphic _instances_ of unboxed
tuples and sums.
* The code generated by `-XDeriveLift` uses expression quotes
instead of generating large amounts of TH code and having
special hard-coded cases for some unboxed types.
Alp Mestanogullari [Wed, 17 Apr 2019 13:03:06 +0000 (15:03 +0200)]
Hadrian: fix the value we pass to the test driver for config.compiler_debugged
We used to pass YES/NO, while that particular field is set to True/False. This
happens to fix an unexpected pass, T9208.
Alp Mestanogullari [Fri, 12 Apr 2019 17:47:12 +0000 (19:47 +0200)]
Hadrian: fix ghcDebugged and document it
Sylvain Henry [Mon, 8 Apr 2019 14:07:17 +0000 (16:07 +0200)]
Gitlab: allow execution of CI pipeline from the web interface
[skip ci]
klebinger.andreas@gmx.at [Mon, 15 Apr 2019 21:48:02 +0000 (23:48 +0200)]
Add an Outputable instance for SDoc with ppr = id.
When printf debugging this can be helpful.