[commit: ghc] wip/ttypeable's head updated: testsuite: Bump base version (78d7d9a)

git at git.haskell.org git at git.haskell.org
Mon Jun 6 11:13:21 UTC 2016


Repository : ssh://git@git.haskell.org/ghc

Branch 'wip/ttypeable' now includes:

     46f9a47 DriverPipeline: Fix 'unused arguments' warnings from Clang
     b5565f1 Fix #11711.
     c5ed41c typechecker: fix trac issue #11708
     3fe87aa Fix #11716.
     f4f315a Fix #11512 by getting visibility right for methods
     220a0b9 Add test for #9646
     3ddfcc9 PrelRules: Fix constant folding for WordRemOp
     2841cca Mark GHC.Real.even and odd as INLINEABLE
     c095ec5 Ensure T11702 always runs with optasm
     c0f628d Revert "Add test for #11473"
     cb7ecda Fix duplicate T11334 test
     08d254b Fix T9646
     7186a01 Dwarf: Add support for labels in unwind expressions
     ba95f22 prof: Fix heap census for large ARR_WORDS (#11627)
     b735e99 DsExpr: Don't build/foldr huge lists
     289d57a Add test for incompatible flags (issue #11580)
     cb3456d base: Rework System.CPUTime
     e6a44f2 T11145: Fix expected output
     286c65f base: Fix CPUTime on Windows
     3ade8bc Delete a misleading comment in TyCon
     2cb5577 Remove unnecessary Ord instance for ConLike
     c37a583 Remove unused substTyWithBinders functions
     af2f7f9 Fix exponential algorithm in pure unifier.
     01b29eb TypeApplications does not imply AllowAmbiguousTypes
     0706a10 Add two small optimizations. (#11196)
     1701255 Fix #11635 / #11719.
     0b89064 Make equality print better. (#11712)
     f8ab575 Rename test for #11334 to 11334b, fixing conflict
     3e1b882 Prevent eager unification with type families.
     9477093 Comment a suspicious zonk in TcFlatten.
     35e9379 Track specified/invisible more carefully.
     5c0c751 Zonk before calling splitDepVarsOfType.
     d978c5e Fix #11723 and #11724.
     e19e58c Improve panicking output
     1934f7f stgMallocBytes: Tolerate malloc(0) returning a NULL ptr
     2d6d907 Comments (only) in TcFlatten
     6f0e41d PPC NCG: Emit more portable `fcmpu 0, ...` instead of `fcmpu cr0, ...`
     685398e Use the correct in-scope set in coercionKind
     0beb82c Avoid running afoul of the zipTvSubst check.
     7e74079 Comment fix
     7d5ff3d Move applyTysX near piResultTys
     db9e4eb Move DFunUnfolding generation to TcInstDcls
     e57b9ff Fix regression test for #11145.
     2ddfb75 base: Fix ClockGetTime on OS X
     da3b29b Ensure T9646 dump-simpl output is cleaned
     8048d51 ErrUtils: Add timings to compiler phases
     997312b Add `PatSynSigSkol` and modify `PatSynCtxt`
     2708c22 Close ticky profiling file stream after printing (#9405)
     03a1bb4 Add unicode syntax for banana brackets
     6c2c853 Various ticky-related work
     9f9345e Create empty dump files (fixes #10320)
     0db0594 DsExpr: Rip out static/dynamic check in list desugaring
     8335cc7 Add expected output for T9405
     ef653f1 Revert "Various ticky-related work"
     1448f8a Show: Restore redundant parentheses around records
     371608f Default RuntimeRep variables unless -fprint-explicit-runtime-reps
     0bd0c31 Defer inlining of Eq for primitive types
     2b5929c Comments only
     cb08f8d Tidy up handling of coercion variables
     343349d Avoid local label syntax for assembler on AIX
     2cebbe6 users_guide: Fix various issues
     8ff6518 users-guide: Add -Wredundant-constraints to flags reference
     173a5d8 users_guide: small improvements on pattern synonyms.
     2414952 Add option `no-keep-hi-files` and `no-keep-o-files` (fixes #4114)
     df26b95 Add NCG support for AIX/ppc32
     4dc8835 Remove code-duplication in the PPC NCG
     26f86f3 base: Fix GHC.Word and GHC.Int on 32-bit platforms
     84dd9d0 An extra traceTc in tcExpr for ExprWithSig
     356e5e0 Do not eta-reduce across Ticks in CorePrep
     12372ba CorePrep: refactoring to reduce duplication
     067335a A raft of comments about TyBinders
     b416630f Test Trac #11728
     da4bc0c Document implicit quantification better
     454585c More clarification in docs for implicit quantification
     4e98b4f DynFlags: Initialize unsafeGlobalDynFlags enough to be useful
     e8d3567 Panic: Try outputting SDocs
     d0787a2 testsuite: Identify framework failures in testsuite summary
     1b4d120 DWARF: Add debugging information chapter to users guide
     882179d RTS: Fix & refactor "portable inline" macros
     4da8e73 Fix #11754 by adding an additional check.
     12a76be Check for rep poly on wildcard binders.
     9f73e46 Clarify Note [Kind coercions in Unify]
     06cd26b Remove now obsolete LD_STAGE0 hack
     c7b32ad Remove now pointless INLINE_ME macro
     61df7f8 Fix AIX/ppc codegen in `-prof` compilation mode
     0bca3f3 Scrap IRIX support
     f911358 Scrap DEC OSF/1 support
     ffc802e Drop Xcode 4.1 hack and fix ignored CC var issue
     afc48f8 Autoconf: detect and set CFLAGS/CPPFLAGS needed for C99 mode
     49b9d80 Do not test for existence of the executable
     eb25381 Update bytestring submodule to latest snapshot
     cd3fbff Remove obsolete --with-hc flag from ./configure
     91b96e1 fix compilation failure on Solaris 11
     a658ad9 Reenable external-json linters
     0f0c138 base: Document caveats about Control.Concurrent.Chan
     415b706 users-guide: Provide more depth in table-of-contents
     eb8bc4d users-guide: Wibbles
     aa61174 users-guide: Add references to various issues in bugs section
     7393532 Use a correct substitution in tcInstType
     a49228e Build correct substitution in instDFunType
     4a93e4f Use the correct substitution in lintCoercion
     5097f38 Add Data.Functor.Classes instances for Proxy (trac issue #11756)
     b0ab8db base: Add comment noting import loop
     be2a7ba cleanup POSIX/XOPEN defines for switch to C99
     85e6997 Remove all mentions of IND_OLDGEN outside of docs/rts
     30b9061 Be more explicit about closure types in ticky-ticky-report
     38c7714 Ticky: Do not count every entry twice
     8af1d08 Typo in Note name
     80d4fdf SpecConstr: Transport strictness data to specialization’s argument’s binders
     e6e17a0 Rename isNopSig to isTopSig
     c8138c8 Do not print DmdType in Core output
     cf768ec Tes suite output updates
     d5d6804 rename: Disallow type signatures in patterns in plain Haskell
     ae6a56e users-guide/rel-notes: Note broken-ness of ImpredicativeTypes
     eb6b709 base: Fix haddock typo
     cb9a1e6 Add testcase for #11770
     a76e6f5 Typos in non-code
     1757dd8 Don't recompute some free vars in lintCoercion
     3d245bf Do not claim that -O2 does not do better than -O
     973633a Comments only in Unify.hs
     7aa4c52 rts/posix/Itimer.c: Handle EINTR when reading timerfd
     d1179c4 ghc-prim: Delay inlining of {gt,ge,lt,le}Int to phase 1
     c0e3e63 Defer inlining of Ord methods
     58bbb40 ghc-prim: Mark unpackCStringUtf8# and unpackNBytes# as NOINLINE
     e9c2555 Don't require -hide-all-packages for MIN_VERSION_* macros
     bc953fc Add -f(no-)version-macro to explicitly control macros.
     24d7615 Kill the magic of Any
     8f66bac Comments only
     1f68da1 Minor refactoring in mkExport
     2e5e822 Comments only
     bdd9042 Refactor in TcMatches
     174d3a5 Small refactor of TcMType.tauifyExpType
     0ad2021 Make SigSkol take TcType not ExpType
     9fc65bb Refactor error generation for pattern synonyms
     28fe0ee Demand Analyzer: Do not set OneShot information
     da260a5 Revert accidental change to collectTyAndValBinders
     6ea42c7 Revert "Demand Analyzer: Do not set OneShot information"
     3806891 Make the example for -M work
     72bd7f7 Improve printing of pattern synonym types
     f2a2b79 Deeply instantiate in :type
     90d7d60 rts: Make StablePtr derefs thread-safe (#10296)
     b3ecd04 Elaborate test for #11376
     9b6820c Bump binary submodule
     7407a66 Don't infer CallStacks
     2f3b803 Use exprCtOrigin in tcRnExpr
     1e6ec12 Fix misattribution of `-Wunused-local-binds` warnings
     351f976 T10272, T4340: Add 32-bit output
     726cbc2 T10870: Skip on 32-bit architectures
     1a8d61c testsuite: Update 32-bit performance numbers
     2265c84 Core pretty printer: Omit wild case binders
     5b986a4 CSE code cleanup and improvement
     0f58d34 Demand Analyzer: Do not set OneShot information (second try)
     c9e8f80 Set tct_closed to TopLevel for closed bindings.
     eda273b runtime: replace hw.ncpu with hw.logicalcpu for Mac OS X
     27528b3 Adjust performance numbers
     06b7ce2 testsuite: One more 32-bit performance slip
     6b6beba Fix installation of static sphinx assets
     535896e rts: Fix parsing of profiler selectors
     2bcf0c3 Revert "testsuite: One more 32-bit performance slip"
     eca8648 GHC.Base: Use thenIO in instance Applicative IO
     f0af351 Remove obsolete comment about the implementation of foldl
     f9d26e5 Fix a comment: triple -> tuple
     485608d Refactor comments about shutdown
     c4a7520 Provide an optimized replicateM_ implementation #11795
     90d66de Add doc to (<=<) comparing its type to (.)
     f3beed3 Remove left-over shell-tools.c
     6d7fda5 Remove spurious STG_UNUSED annotation
     2f82da7 Fix Template Haskell bug reported in #11809.
     d2e05c6 Reduce default for -fmax-pmcheck-iterations from 1e7 to 2e6
     5a1add1 Export zonkEvBinds from TcHsSyn.
     470d4d5 Fix suggestions for unbound variables (#11680)
     cf5ff08 Bump haddock submodule
     ad532de base: Fix "since" annotation on GHC.ExecutionStack
     7443e5c Remove the instantiation check when deriving Generic(1)
     378091c RtsFlags: Un-constify temporary buffer
     8987ce0 Typos in Note
     90538d8 Change runtime linker to perform lazy loading of symbols/sections
     46e8f19 Fix a closed type family error message
     02a5c58 Filter out invisible kind arguments during TH reification
     8b57cac Added (more) missing instances for Identity and Const
     aadde2b Deriving Functor-like classes should unify kind variables
     2ef35d8 Use `@since` annotation in GHC.ExecutionStack
     c6e579b Add linker notes
     83eb4fd Small simplification (#11777)
     5c4cd0e Cache the size of part_list/scavd_list (#11783)
     f4446c5 Allocate blocks in the GC in batches
     b1084fd Fix #11811.
     dd99f2e Fix #11797.
     0b6dcf6 Fix #11814 by throwing more stuff into InScopeSets
     d81cdc2 Teach lookupLocalRdrEnv about Exacts. (#11813)
     49560ba Fix commented out debugging code in ByteCodeGen
     227a29d Fix typos: tyars -> tyvars
     20f9056 Remove some old commented out code in StgLint
     3a34b5c Add a test case for #11731.
     f4fd98c Add a final demand analyzer run right before TidyCore
     928d747 Kill some unnecessary varSetElems
     2acfaae Comments only
     e24b3b1 Adjust error check for class method types
     31e4974 Remove some gratitious varSetElemsWellScoped
     8d66765 Increase an InScopeSet for a substitution
     aaaa61c users-guide: Note change in LLVM support policy
     10c6df0 utils: Provide CallStack to expectJust
     116088d testsuite: Add T11824
     cb0d29b testsuite: Add test for #11827
     9d063b6 Linker: Fix signedness mismatch
     933abfa rel-notes: Add note about UndecidableSuperClasses and #11762
     54e67c1 Remove dead function SimplUtils.countValArgs
     f0e331b Comments only, on Type.topSortTyVars
     a7ee2d4 Improve TcFlatten.flattenTyVar
     e9ad489 libdw: More precise version check
     d77981e rts/RetainerProfile: Remove unused local
     bf17fd0 deriveConstants: Verify sanity of nm
     f4e6591 Bump haddock submodule
     865602e Rework CC/CC_STAGE0 handling in `configure.ac`
     3f3ad75 Update `directory` submodule to v1.2.6.0 release
     4cbae1b Update array submodule to v0.5.1.1 release tag
     97f2b16 Add Windows import library support to the Runtime Linker
     04b70cd Add TemplateHaskell support for Overlapping pragmas
     89b6674 TH: Tweak Haddock language
     7a1c073 users-guide: Fix typo
     07dc330 validate: Note existence of config_args variable
     7005b9f Add flag to control number of missing patterns in warnings
     36a0b6d Check CCS tree for pointers into shared object during checkUnload
     177aec6 Linker: Clean up #if USE_MMAP usage
     a392208 Resolve symlinks when attempting to find GHC's lib folder on Windows
     93d85af Update `directory` submodule to v1.2.6.1 release
     dd920e4 Silence unused-import warning introduced by 93d85af9fec968b
     8a75bb5 Update haskeline submodule to 0.7.2.3 release
     3dac53f Make it easy to get hyperlinked sources
     10d808c relnotes: Add note about #11744 and workaround
     87114ae Use stdint types to define SIZEOF and ALIGNMENT of INTx/WORDx
     32ddd96 Remove obsolete/redundant FLEXIBLE_ARRAY macro
     350ffc3 rts: Limit maximum backtrace depth
     d1ce35d rts: Don't use strndup
     8556f56 Update `directory` submodule to v1.2.6.2 release
     a3c37c3 Remove unused import of emptyNameEnv
     d59939a Define TyCoRep.ppSuggestExplicitKinds, and use it
     17eb241 Refactor computing dependent type vars
     8136a5c Tighten checking for associated type instances
     9de405d Kill dead TauTvFlavour, and move code around
     81e2279 Update hsc2hs submodule
     91ee509 Mark GHC.Stack.Types Trustworthy
     96e1bb4 Update deepseq submodule to latest 1.4.2.0 snapshot
     ff290b8 Update binary submodule to 0.8.3.0 release
     15b7e87 Update `pretty` submodule to v1.1.3.3 release
     81b14c1 Update unix submodule to v2.7.2.0 release
     7f71dbe Bump haddock submodule
     81aa3d1 Reduce use of instances in hs-boot files
     871f684 Define NameSet.intersectFVs
     7319b80 Tighten up imports, white space
     353d8ae SCC analysis for instances as well as types/classes
     61191de Fix two buglets in 17eb241 noticed by Richard
     cdcf014 Tighten up imports on TcTyClsDecls
     687c778 Kill unnecessary varSetElemsWellScoped in deriveTyData
     62943d2 Build a correct substitution in dataConInstPat
     55b1b85 Accept tcrun045 output
     2e33320 Rename FV related functions
     98a14ff Point to note about FV eta-expansion performance
     7c6585a Remove mysterious varSetElemsWellScoped in tidyFreeTyCoVars
     8c33cd4 testsuite: Bump max bytes used of T4029
     f02af79 Improve the behaviour of warnIf
     edf54d7 Do not use defaulting in ambiguity check
     9421b0c Warn about simplifiable class constraints
     251a376 Test Trac #3990
     26a1804 wibble to simplifiable
     24d3276 A little more debug tracing
     c2b7a3d Avoid double error on out-of-scope identifier
     970ff58 Simplify defaultKindVar and friends
     6ad2b42 Refactor free tyvars on LHS of rules
     ed4a228 Fix typos: alpah -> alpha
     4221cc2 Typo: veraibles -> variables
     a9076fc Remove unused tyCoVarsOfTelescope
     0f96686 Make benign non-determinism in pretty-printing more obvious
     03006f5 Get rid of varSetElemsWellScoped in abstractFloats
     28503fe deriveConstants: Fix nm-classic error message
     e8c04d4 Testsuite: Delete test for deprecated "packedstring"
     dadf82d Testsuite: fixup lots of tests
     2a83713 Testsuite: delete Roles9.stderr
     fd5212f Testsuite: delete unused concurrent/prog002/FileIO.hs
     c9bcaf3 Kill varSetElemsWellScoped in quantifyTyVars
     e68195a RTS: Add setInCallCapability()
     95f9334 GHCi: use real time instead of CPU time for :set -s
     d396996 Doc improvement for ApplicativeDo
     24864ba Use __builtin_clz() to implement log_2()
     0712f55 Just comments & reformatting
     2dc5b92 Kill varSetElems in TcErrors
     94320e1 Kill varSetElems try_tyvar_defaulting
     f13a8d2 Kill varSetElems in markNominal
     a48ebcc Implement the state hack without modifiyng OneShotInfo
     5adf8f3 Document -fmax-pmcheck-iterations a bit better
     a0e1051 Recommend more reliable recourse for broken nm
     57c636f Update nofib submodule to nofib master
     fa3ba06 Expand the comment on pprVarSet
     82538f6 Kill varSetElems in injImproveEqns
     af6dced Comments only
     a2abcf6 Minor improvement to error message
     1e86cab Comments only
     9ed57d6 Remove unused unifyType_
     4c746cb Add missing solveEqualities
     3dce4f2 Refactor RecordPatSynField, FieldLabel
     c4dd4ae Better documentation of -XConstrainedClassMethods
     c5b1014 Fix debug-only check in CoreLint
     546f24e Revert "Use __builtin_clz() to implement log_2()"
     3a53380 Kill unused foldOccSet
     196ce62 Testsuite: delete accidentally committed .stderr.normalised file
     89c6d07 Testsuite: add -ignore-dot-ghci to some ghci tests [skip ci]
     9dc34d3 Testsuite: fix T11223_simple_(unused_)duplicate_lib
     b0569e8 Testsuite: benign test fixes
     3c426b0 Add uniqSetAny and uniqSetAll and use them
     7312923 Kill mapUniqSet
     32c0aba Testsuite: delete -fesc tests
     e20b3ed Testsuite: delete T5054 and T5054_2 (#5054)
     bcfee21 rts/LdvProfile.c: Fix NULL dereference on shutdown
     f255f80 Linker: Fix implicit function declaration warning on OS X
     6e195f4 Remove unused foldFsEnv
     031de8b Remove unused foldNameEnv
     f99db38 Fix path to the new build system, now called Hadrian.
     0fa1d07 testsuite: fix up T11223's Makefile
     a2970f8 RTS: delete BlockedOnGA* + dead code
     c5919f7 Remove the incredibly hairy splitTelescopeTvs.
     7242582 Test #11484 in th/T11484
     00053ee Fix typo: Superclases -> Superclasses
     b725fe0 PPC NCG: Improve pointer de-tagging code
     c4259ff Testsuite: make CLEANUP=1 the default (#9758)
     2ae39ac Testsuite: accept new output for 2 partial-sigs tests
     2fe7a0a Fix reference to Note in TcCanonical
     cb05860 Comment typos: Mkae -> Make, Hsakell -> Haskell
     49bae46 Comment typo: unambigious -> unambiguous
     f69e707 Typos in DmdAnal
     e6627d1 Fix aggressive cleanup of T1407
     868d2c4 rts: Remove deprecated C type `lnat`
     eac6967 users-guide: Add index entry for "environment file"
     18676a4 Bump haddock submodule
     533037c Greater customization of GHCi prompt
     16a51a6 rts: Close livelock window due to rapid ticker enable/disable
     65e13f6 rts: Split up Itimer.c
     df9b772 Catch errors from timerfd_settime
     55f4009 Kill Itimer.h
     999c464 rts/itimer/pthread: Stop timer when ticker is stopped
     116d3fe Remove unused getScopedTyVarBinds
     1161932 Add T11747 as a test
     ecc0603 deriveConstants: Fix nm advice one last time
     a28611b Export constructors for IntPtr and WordPtr
     ea34f56 Remove unused equivClassesByUniq
     cd85dc8 Make sure record pattern synonym selectors are in scope in GHCi.
     db2bfe0 added docstring for '-fhistory-size' flag
     81d8a23 glasgow_exts.rst: fix quoting
     c5be5e2 docs/users_guide/glasgow_exts.rst: fix merge conflict
     fa86ac7 Make validDerivPred ignore non-visible arguments to a class type constructor
     36d29f7 StaticPointers: Allow closed vars in the static form.
     5f8c0b8 Revert "Revert "Use __builtin_clz() to implement log_1()""
     ef44606 Cleanups related to MAX_FREE_LIST
     0051ac1 Update libraries/hpc submodule to v0.6.0.3 release tag
     4466ae6 Update bytestring submodule to 0.10.8.0 release tag
     50e7055 Export oneShot from GHC.Exts
     f9d9375 Adjust testsuite output to bytestring-0.10.8.0
     76ee260 Allow limiting the number of GC threads (+RTS -qn<n>)
     f703fd6 Add +RTS -AL<size>
     1fa92ca schedulePushWork: avoid unnecessary wakeups
     dbcaa8c Don't STATIC_INLINE giveCapabilityToTask
     aa5e2dd Make 'make fast' work for the User Guide
     b75d194 Be more aggressive when checking constraints for custom type errors.
     4f2afe1 testsuite: Add test for #11959
     763610e base: Export runRW# from GHC.Exts
     ad4392c Kill non-deterministic foldUFM in TrieMap and TcAppMap
     db9de7e rts: Replace `nat` with `uint32_t`
     e340520 Comments only explaining export list parsing.
     94f2ee1 Explain linter optimization for StaticPtr checks.
     990ce8c Use tcExtendGlobalValEnv for default methods
     ecc1d58 Update Win32 submodule to v2.3.1.1 release tag
     018487e Fix pretty printing of IEThingWith
     fe190ae Remove trailing whitespace from 'testsuite/tests/module/all.T'
     633b099 Update time submodule to 1.6.0.1 release tag
     8e5776b rts/ProfHeap.c: Use `ssize_t` instead of `long`.
     dd3e847 Documentation for simplifyDeriv.
     260a564 Use stdint types for Stg{Word,Int}{8,16,32,64}
     2593e20 White space only
     76d9156 Emit wild-card constraints in the right place
     cc75a5d Comments only
     e1ff2b4 Fix partial sigs and pattern bindings interaction
     9dbf5f5 Tidy up partial-sig quantification
     bb296bf Error message wibbles, re partial type sigs
     0597493 Re-do the invariant for TcDepVars
     3ca7806 stg/Types.h: Fix comment and #include
     53f26f5 Forbid variables to be parents in import lists.
     e996e85 RdrHsSyn: Only suggest `type` qualification when appropriate
     ea3d1ef Fix a crash in requestSync()
     bff6e1b Comments only
     4ac0e81 Kill unnecessary cmpType in lhs_cmp_type
     b58b0e1 Make simplifyInstanceContexts deterministic
     a4717f5 Comments about static forms
     b21e8cc Comments only
     e7e5939 Add Outputable ShowHowMuch
     e24b50c Use partial-sig constraints as givens
     1a43783 Record that EqualityConstraint now works
     f6e58be Test Trac #11640
     7e28e47 Get rid of Traversable UniqFM and Foldable UniqFM
     402f201 Fix typos
     ab91b85 make accept for Make simplifyInstanceContexts deterministic
     e207198 Kill foldUFM in classifyTyCon
     8669c48 Document why closeOverKind is OK for determinism
     584ade6 RtsFlags: Make `mallocFailHook` const correct
     0efbf18 rts: Fix C compiler warnings on Windows
     9363f04 Handle promotion failures when scavenging a WEAK (#11108)
     0e71988 Remove some varSetElems in dsCmdStmt
     3edbd09 Document SCC determinism
     cfc5df4 Fix ASSERT failure and re-enable setnumcapabilities001
     2a0d00d Make random an "extra" package
     86a1f20 Remove a copy of System.Random and use reqlib('random')
     b5f85ce Remove stale comment.
     da105ca Don't prematurely force TyThing thunks with -ddump-if-trace.
     925b0ae Make absentError not depend on uniques
     eae3362 docs: add skeleton 8.2.1 release notes
     e217287 Bump haddock submodule
     c079de3 Add TH support for pattern synonyms (fixes #8761)
     e53f218 Fix deriveTyData's kind unification when two kind variables are unified
     b8e2565 Make Generic1 poly-kinded
     6971430 Allow putting Haddocks on derived instances
     01bc109 Document zonkTyCoVarsAndFV determinism
     6bf0eef Kill varEnvElts in specImports
     69c974f Use StgHalfWord instead of a CPP #if
     995cf0f rts: Make function pointer parameters `const` where possible
     0c0129b RtsUtils: Use `size_t` instead of `int` where appropriate
     7c0b595 Fix comments about scavenging WEAK objects
     5416fad Refactor some ppr functions to use pprUFM
     bd01bbb Test Trac #12039
     8e48d24 Bump haddock submodule
     e4834ed Fix a performance issue with -fprint-expanded-synonyms
     c974927 Update bytestring submodule to 0.10.8.1 release tag
     bf669a0 Bump haddock submodule
     2dbdc79 PPC NCG: Fix pretty printing of st[wd]ux instr.
     563a485 PPC: Implement SMP primitives using gcc built-ins
     d78faa1 testsuite/ImpSafe03: Normalize version of bytestring
     eed820b Move Extension type to ghc-boot-th
     21fe4ff Kill varSetElems in tcInferPatSynDecl
     d20d843 Another bump of haddock submodule
     7814420 Remove html_theme requirement of haddock docs
     4a037a9 Set `USE_MMAP` at configure time
     770d708 Add ghc-boot-th to rules/foreachLibrary
     dc94914 Document determinism in shortOutIndirections
     3f3dc23 Testsuite: run tests in /tmp after copying required files
     1a9ae4b Testsuite: delete old cleanup code (#11980)
     a9dd9b7 Testsuite: delete unused file [skip ci]
     c92cfbc Testsuite: don't skip concio001 and concio001_thr
     931b3c7 Delete libraries/ghci/GNUmakefile [skip ci]
     a54d87a rules: Fix name of ghc-boot-th library
     5d80d14 rules/build-prog: Ensure programs depend upon their transitive deps
     33c029d rts: More const correct-ness fixes
     b088c02 Testsuite: T10052 requires interpreter (#11730)
     3251743 Testsuite: don't warn when mk/ghcconfig_* hasn't been created yet
     77ee3a9 Update .mailmap [skip ci]
     fffe3a2 Make inert_model and inert_eqs deterministic sets
     f0f0ac8 Fix histograms for ticky code
     ba3e1fd Add a test for #11108
     39a2faa Rework parser to allow use with DynFlags
     310371f rts: Add isPinnedByteArray# primop
     f091218 CLabel: Catch #11155 during C-- pretty-printing
     9dd0481 Add (broken) test for #12063.
     5f1557e Failing test case for #12076.
     f18e8d8 rts: Add missing `const` from HashTable API
     6282bc3 Kill varSetElems in tidyFreeTyCoVars
     13e40f9 Kill varEnvElts in tcPragExpr
     72b677d Fix Trac #12051
     ad7f122 Improve pretty-printing of equalities
     f9e90bc Improve documentation for type wildcards
     0bfcfd0 Comments only
     d1efe86 Comments only
     358567a testsuite: Add expected output for T11108
     470def9 Testsuite: fix T11827 (#11827)
     296b8f1 Add libraries/ghci/GNUmakefile to .gitignore [skip ci]
     f0f3517 Remove use of caddr_t
     8abc193 Get types in osFreeMBlocks in sync with osGetMBlocks
     464b6f8 {,M}BLOCK_SIZE_W * sizeof(W_) -> {,M}BLOCK_SIZE
     2e6433a testsuite: Add a TypeRep test
     a88bb1b Give lifted primitive types a representation
     1ee47c1 Use the correct return type for Windows' send()/recv() (Fix #12010)
     809a3bf HACK: CoreLint: Kill unsaturated unlifted types check
     1333b6a TcSMonad: Introduce tcLookupId
     1b87cad Outputable: Refactor handling of CallStacks
     84b0f2e CoreLint: Improve debug output
     4b0ee4e Start implementing library side of TTypeable
     6b173f2 Fix rebase
     4c99c66 Add quick compatibility note
     5803a58 Fix warnings
     2dd3c5e Various fixes
     f8a4d5d Fix serialization
     33eb10c Implement Data.Typeable.funResultTy
     12cd07d Binary: More explicit pattern matching
     3b2ed2e More serialization
     e897633 Message: Import Data.Typeable.TypeRep
     6e10f55 TcInteract: Unused parameter
     58b2cf7 Fix a few TTypeRep references
     2f12211 Fix recursive fingerprints
     9c8dd2d Finally serialization is both general and correct
     6667e59 Break recursive loop in serialization
     8801237 Kill todo
     5012264 Fix up representation pretty-printer
     c9751b0 Another recursive serialization case
     3a56be1 TcTypeable: Don't generate bindings for special primitive tycons
     afb34f3 Move special tycons
     f60679d Internal things
     b347d60 Fix primitive types
     ae746a3 Fix pretty-printer
     c3dc056 Kill debugShow
     f3931e6 Inline space
     7a3f742 Accept easy test output
     7fd93c8 Add mkFunTy
     8960738 More test fixes
     54eb46f Fix T8132
     2c406cb Render TYPE 'PtrRepLifted as *
     0217f61 Internal: Rename type variable
     d8efe39 Implement withTypeable
     f5c4fd7 Bump base to 4.10.0
     d3ef4f2 Fix withTypeable
     324ea2d Bump base
     78d7d9a testsuite: Bump base version


More information about the ghc-commits mailing list