[Git][ghc/ghc][wip/T17923] 11 commits: Don't use non-portable operator "==" in configure.ac
Simon Peyton Jones
gitlab at gitlab.haskell.org
Wed Mar 18 15:15:33 UTC 2020
Simon Peyton Jones pushed to branch wip/T17923 at Glasgow Haskell Compiler / GHC
Commits:
e1aa4052 by PHO at 2020-03-17T11:36:09Z
Don't use non-portable operator "==" in configure.ac
The test operator "==" is a Bash extension and produces a wrong result
if /bin/sh is not Bash.
- - - - -
89f034dd by Maximilian Tagher at 2020-03-17T11:36:48Z
Document the units of -ddump-timings
Right now, in the output of -ddump-timings to a file, you can't tell what the units are:
```
CodeGen [TemplateTestImports]: alloc=22454880 time=14.597
```
I believe bytes/milliseconds are the correct units, but confirmation would be appreciated. I'm basing it off of this snippet from `withTiming'`:
```
when (verbosity dflags >= 2 && prtimings == PrintTimings)
$ liftIO $ logInfo dflags (defaultUserStyle dflags)
(text "!!!" <+> what <> colon <+> text "finished in"
<+> doublePrec 2 time
<+> text "milliseconds"
<> comma
<+> text "allocated"
<+> doublePrec 3 (realToFrac alloc / 1024 / 1024)
<+> text "megabytes")
```
which implies time is in milliseconds, and allocations in bytes (which divided by 1024 would be KB, and again would be MB)
- - - - -
beffa147 by Simon Peyton Jones at 2020-03-17T11:37:25Z
Implement mapTyCo like foldTyCo
This patch makes mapType use the successful idiom described
in TyCoRep
Note [Specialising foldType]
I have not yet changed any functions to use mapType, though there
may be some suitable candidates.
This patch should be a no-op in terms of functionality but,
because it inlines the mapper itself, I'm hoping that there may
be some modest perf improvements.
Metric Decrease:
T5631
T5642
T3064
T9020
T14683
hie002
haddock.Cabal
haddock.base
haddock.compiler
- - - - -
5800ebfe by Ömer Sinan Ağacan at 2020-03-17T11:38:08Z
Don't update ModDetails with CafInfos when opts are disabled
This is consistent with the interface file behavior where we omit
HsNoCafRefs annotations with -fomit-interface-pragmas (implied by -O0).
ModDetails and ModIface are just different representations of the same
thing, so they really need to be in sync. This patch does the right
thing and does not need too much explanation, but here's an example of a
problem not doing this causes in !2842:
-- MyInteger.hs
module MyInteger
( MyInteger (MyInteger)
, ToMyInteger (toMyInteger)
) where
newtype MyInteger = MyInteger Integer
class ToMyInteger a where
toMyInteger :: a -> MyInteger
instance ToMyInteger Integer where
toMyInteger = MyInteger {- . succ -}
-- Main.hs
module Main
( main
) where
import MyInteger (MyInteger (MyInteger), toMyInteger)
main :: IO ()
main = do
let (MyInteger i) = (id . toMyInteger) (41 :: Integer)
print i
If I build this with -O0, without this fix, we generate a ModDetails with
accurate LFInfo for toMyInteger (MyInteger.$fToMyIntegerInteger) which says that
it's a LFReEntrant with arity 1. This means in the use site (Main) we tag the
value:
R3 = MyInteger.$fToMyIntegerInteger_closure + 1;
R2 = GHC.Base.id_closure;
R1 = GHC.Base.._closure;
Sp = Sp - 16;
call stg_ap_ppp_fast(R4, R3, R2, R1) args: 24, res: 0, upd: 24;
Now we change the definition by uncommenting the `succ` part and it becomes a thunk:
MyInteger.$fToMyIntegerInteger [InlPrag=INLINE (sat-args=0)]
:: MyInteger.ToMyInteger GHC.Integer.Type.Integer
[GblId[DFunId(nt)]] =
{} \u [] $ctoMyInteger_rEA;
and its LFInfo is now LFThunk. This change in LFInfo makes a difference in the
use site: we can no longer tag it.
But becuase the interface fingerprint does not change (because ModIface does not
change) we don't rebuild Main and tag the thunk.
(1.2% increase in allocations when building T12545 on armv7 because we
generate more code without CafInfos)
Metric Increase:
T12545
- - - - -
5b632dad by Paavo at 2020-03-17T11:38:48Z
Add example for Data.Semigroup.diff
- - - - -
4d85d68b by Paavo at 2020-03-17T11:38:48Z
Clean up
- - - - -
75168d07 by Paavo at 2020-03-17T11:38:48Z
Make example collapsible
- - - - -
53ff2cd0 by Richard Eisenberg at 2020-03-17T13:46:57Z
Fix #17021 by checking more return kinds
All the details are in new Note [Datatype return kinds] in
TcTyClsDecls.
Test case: typecheck/should_fail/T17021{,b}
typecheck/should_compile/T17021a
Updates haddock submodule
- - - - -
528df8ec by Sylvain Henry at 2020-03-18T14:06:43Z
Modules: Core operations (#13009)
- - - - -
4e8a71c1 by Richard Eisenberg at 2020-03-18T14:07:19Z
Add release note about fix to #16502.
We thought we needed to update the manual, but the fix for #16502
actually brings the implementation in line with the manual. So we
just alert users of how to update their code.
- - - - -
27b11c5e by Simon Peyton Jones at 2020-03-18T15:15:18Z
Significant refactor of Lint
This refactoring of Lint was triggered by #17923, which is
fixed by this patch.
The main change is this. Instead of
lintType :: Type -> LintM LintedKind
we now have
lintType :: Type -> LintM LintedType
Previously, all of typeKind was effectively duplicate in lintType.
Moreover, since we have an ambient substitution, we still had to
apply the substition here and there, sometimes more than once. It
was all very tricky, in the end, and made my head hurt.
Now, lintType returns a fully linted type, with all substitutions
performed on it. This is much simpler.
The same thing is needed for Coercions. Instead of
lintCoercion :: OutCoercion
-> LintM (LintedKind, LintedKind,
LintedType, LintedType, Role)
we now have
lintCoercion :: Coercion -> LintM LintedCoercion
Much simpler! The code is shorter and less bug-prone.
There are a lot of knock on effects. But life is now better.
- - - - -
30 changed files:
- compiler/GHC/Core.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/Coercion/Axiom.hs
- compiler/GHC/Core/FamInstEnv.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Make.hs
- compiler/simplCore/CSE.hs → compiler/GHC/Core/Op/CSE.hs
- compiler/simplCore/CallArity.hs → compiler/GHC/Core/Op/CallArity.hs
- compiler/prelude/PrelRules.hs → compiler/GHC/Core/Op/ConstantFold.hs
- compiler/stranal/CprAnal.hs → compiler/GHC/Core/Op/CprAnal.hs
- compiler/stranal/DmdAnal.hs → compiler/GHC/Core/Op/DmdAnal.hs
- compiler/simplCore/Exitify.hs → compiler/GHC/Core/Op/Exitify.hs
- compiler/simplCore/FloatIn.hs → compiler/GHC/Core/Op/FloatIn.hs
- compiler/simplCore/FloatOut.hs → compiler/GHC/Core/Op/FloatOut.hs
- compiler/simplCore/LiberateCase.hs → compiler/GHC/Core/Op/LiberateCase.hs
- compiler/simplCore/CoreMonad.hs → compiler/GHC/Core/Op/Monad.hs
- compiler/simplCore/CoreMonad.hs-boot → compiler/GHC/Core/Op/Monad.hs-boot
- compiler/simplCore/OccurAnal.hs → compiler/GHC/Core/Op/OccurAnal.hs
- compiler/simplCore/SetLevels.hs → compiler/GHC/Core/Op/SetLevels.hs
- compiler/simplCore/Simplify.hs → compiler/GHC/Core/Op/Simplify.hs
- compiler/simplCore/SimplCore.hs → compiler/GHC/Core/Op/Simplify/Driver.hs
- compiler/simplCore/SimplEnv.hs → compiler/GHC/Core/Op/Simplify/Env.hs
- compiler/simplCore/SimplMonad.hs → compiler/GHC/Core/Op/Simplify/Monad.hs
- compiler/simplCore/SimplUtils.hs → compiler/GHC/Core/Op/Simplify/Utils.hs
- compiler/specialise/SpecConstr.hs → compiler/GHC/Core/Op/SpecConstr.hs
- compiler/specialise/Specialise.hs → compiler/GHC/Core/Op/Specialise.hs
- compiler/simplCore/SAT.hs → compiler/GHC/Core/Op/StaticArgs.hs
- compiler/GHC/Core/Op/Tidy.hs
- compiler/stranal/WorkWrap.hs → compiler/GHC/Core/Op/WorkWrap.hs
- compiler/stranal/WwLib.hs → compiler/GHC/Core/Op/WorkWrap/Lib.hs
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/compare/95ecfa58c2b106c5521a4f3738bc7a4b0ca02857...27b11c5efa8f3f265ed840701321aa6988f2915f
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/compare/95ecfa58c2b106c5521a4f3738bc7a4b0ca02857...27b11c5efa8f3f265ed840701321aa6988f2915f
You're receiving this email because of your account on gitlab.haskell.org.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20200318/e331bbab/attachment.html>
More information about the ghc-commits
mailing list