From git at git.haskell.org Fri Jul 1 09:17:12 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 1 Jul 2016 09:17:12 +0000 (UTC) Subject: [commit: ghc] master: Testsuite: be less strict about topHandler03's stderr (0afc41b) Message-ID: <20160701091712.177F73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0afc41b49e0ad227750421e5e2887ac9607c40fa/ghc >--------------------------------------------------------------- commit 0afc41b49e0ad227750421e5e2887ac9607c40fa Author: Thomas Miedema Date: Fri Jul 1 11:16:08 2016 +0200 Testsuite: be less strict about topHandler03's stderr Fixes #12343. >--------------------------------------------------------------- 0afc41b49e0ad227750421e5e2887ac9607c40fa libraries/base/tests/all.T | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/libraries/base/tests/all.T b/libraries/base/tests/all.T index df49172..64ecc88 100644 --- a/libraries/base/tests/all.T +++ b/libraries/base/tests/all.T @@ -143,6 +143,9 @@ test('CatEntail', normal, compile, ['']) test('T7653', high_memory_usage, compile_and_run, ['']) test('T7787', normal, compile_and_run, ['']) +def stderr_contains(pattern): + return normalise_errmsg_fun(lambda s: pattern if pattern in s else s) + test('topHandler01', when(opsys('mingw32'), skip), compile_and_run, ['']) test('topHandler02', [when(opsys('mingw32'), skip), @@ -150,7 +153,7 @@ test('topHandler02', signal_exit_code(2) ], compile_and_run, ['']) test('topHandler03', - [when(opsys('mingw32'), skip), + [when(opsys('mingw32'), skip), stderr_contains('Terminated'), signal_exit_code(15) ], compile_and_run, ['']) test('topHandler04', From git at git.haskell.org Fri Jul 1 12:08:42 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 1 Jul 2016 12:08:42 +0000 (UTC) Subject: [commit: ghc] master: Add NamedThing (GenLocated l e) instance (81b437b) Message-ID: <20160701120842.F00983A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/81b437bcc680745d5d50d731b978a1764f40ab36/ghc >--------------------------------------------------------------- commit 81b437bcc680745d5d50d731b978a1764f40ab36 Author: Ben Gamari Date: Fri Jul 1 12:23:27 2016 +0200 Add NamedThing (GenLocated l e) instance >--------------------------------------------------------------- 81b437bcc680745d5d50d731b978a1764f40ab36 compiler/basicTypes/Name.hs | 3 +++ 1 file changed, 3 insertions(+) diff --git a/compiler/basicTypes/Name.hs b/compiler/basicTypes/Name.hs index 24dc8aa..b0411b9 100644 --- a/compiler/basicTypes/Name.hs +++ b/compiler/basicTypes/Name.hs @@ -630,6 +630,9 @@ class NamedThing a where getOccName n = nameOccName (getName n) -- Default method +instance NamedThing e => NamedThing (GenLocated l e) where + getName = getName . unLoc + getSrcLoc :: NamedThing a => a -> SrcLoc getSrcSpan :: NamedThing a => a -> SrcSpan getOccString :: NamedThing a => a -> String From git at git.haskell.org Fri Jul 1 12:08:45 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 1 Jul 2016 12:08:45 +0000 (UTC) Subject: [commit: ghc] master: users-guide: Fix markup in release notes (c27ce26) Message-ID: <20160701120845.A00DF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c27ce26edc0ff72163d07d57b6c53e3d2d75cfef/ghc >--------------------------------------------------------------- commit c27ce26edc0ff72163d07d57b6c53e3d2d75cfef Author: Ben Gamari Date: Thu Jun 30 20:07:41 2016 +0200 users-guide: Fix markup in release notes >--------------------------------------------------------------- c27ce26edc0ff72163d07d57b6c53e3d2d75cfef docs/users_guide/8.2.1-notes.rst | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/docs/users_guide/8.2.1-notes.rst b/docs/users_guide/8.2.1-notes.rst index b671f6d..f19512c 100644 --- a/docs/users_guide/8.2.1-notes.rst +++ b/docs/users_guide/8.2.1-notes.rst @@ -27,7 +27,7 @@ Compiler - TODO FIXME. -- Old profiling flags -auto-all -auto -caf-all are deprecated +- Old profiling flags ``-auto-all``, ``-auto``, and ``-caf-all`` are deprecated and their usage provokes a compile-time warning. From git at git.haskell.org Fri Jul 1 12:08:49 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 1 Jul 2016 12:08:49 +0000 (UTC) Subject: [commit: ghc] master: Allow one type signature for multiple pattern synonyms (b412d82) Message-ID: <20160701120849.58D263A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b412d8230b20223beff797d6207868aea9fd2085/ghc >--------------------------------------------------------------- commit b412d8230b20223beff797d6207868aea9fd2085 Author: Matthew Pickering Date: Fri Jul 1 01:15:01 2016 +0200 Allow one type signature for multiple pattern synonyms This makes pattern synonym signatures more consistent with normal type signatures. Updates haddock submodule. Differential Revision: https://phabricator.haskell.org/D2083 >--------------------------------------------------------------- b412d8230b20223beff797d6207868aea9fd2085 compiler/deSugar/DsMeta.hs | 2 +- compiler/hsSyn/Convert.hs | 2 +- compiler/hsSyn/HsBinds.hs | 7 +++---- compiler/parser/Parser.y | 4 ++-- compiler/rename/RnBinds.hs | 12 ++++++------ compiler/typecheck/TcEnv.hs | 2 +- compiler/typecheck/TcSigs.hs | 7 ++++--- docs/users_guide/glasgow_exts.rst | 11 ++++++++--- testsuite/tests/patsyn/should_compile/T11727.hs | 7 +++++++ testsuite/tests/patsyn/should_compile/all.T | 1 + utils/haddock | 2 +- 11 files changed, 35 insertions(+), 22 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc b412d8230b20223beff797d6207868aea9fd2085 From git at git.haskell.org Fri Jul 1 12:08:52 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 1 Jul 2016 12:08:52 +0000 (UTC) Subject: [commit: ghc] master: rules/sphinx.mk: stop xelatex on error (6ba4197) Message-ID: <20160701120852.184793A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6ba4197e006b6d6bc2657141d4c10c91bd806cb3/ghc >--------------------------------------------------------------- commit 6ba4197e006b6d6bc2657141d4c10c91bd806cb3 Author: Markus Rothe Date: Sun Jun 26 11:28:36 2016 +0200 rules/sphinx.mk: stop xelatex on error This avoids the interactive prompt of xelatex on error. >--------------------------------------------------------------- 6ba4197e006b6d6bc2657141d4c10c91bd806cb3 rules/sphinx.mk | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/rules/sphinx.mk b/rules/sphinx.mk index f3c46b4..4929f3c 100644 --- a/rules/sphinx.mk +++ b/rules/sphinx.mk @@ -58,12 +58,12 @@ pdf : pdf_$1 ifneq "$$(BINDIST)" "YES" $1/$2.pdf: $1/conf.py $$($1_RST_SOURCES) $(SPHINXBUILD) -b latex -d $1/.doctrees-pdf $(SPHINXOPTS) $1 $1/build-pdf/$2 - cd $1/build-pdf/$2 ; xelatex $2.tex - cd $1/build-pdf/$2 ; xelatex $2.tex - cd $1/build-pdf/$2 ; xelatex $2.tex + cd $1/build-pdf/$2 ; xelatex -halt-on-error $2.tex + cd $1/build-pdf/$2 ; xelatex -halt-on-error $2.tex + cd $1/build-pdf/$2 ; xelatex -halt-on-error $2.tex cd $1/build-pdf/$2 ; makeindex $2.idx - cd $1/build-pdf/$2 ; xelatex $2.tex - cd $1/build-pdf/$2 ; xelatex $2.tex + cd $1/build-pdf/$2 ; xelatex -halt-on-error $2.tex + cd $1/build-pdf/$2 ; xelatex -halt-on-error $2.tex cp $1/build-pdf/$2/$2.pdf $1/$2.pdf endif From git at git.haskell.org Fri Jul 1 12:22:23 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 1 Jul 2016 12:22:23 +0000 (UTC) Subject: [commit: ghc] master: Remove unused oc->isImportLib (#12230) (ee8d1fa) Message-ID: <20160701122223.7F03E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ee8d1facb20ab579c44bf4cd7d5fd807d547b6ad/ghc >--------------------------------------------------------------- commit ee8d1facb20ab579c44bf4cd7d5fd807d547b6ad Author: Simon Marlow Date: Wed Jun 29 21:48:43 2016 +0100 Remove unused oc->isImportLib (#12230) Summary: This field is never set, but it was being tested and used to decide whether to resolve an object or not. This caused non-deterministic crashes when using the RTS linker (see #12230). I suspect this is not the correct fix, but putting it up so that Phyx can tell us what the right fix should be. Test Plan: validate Reviewers: austin, Phyx, bgamari, erikd Subscribers: erikd, thomie, ezyang Differential Revision: https://phabricator.haskell.org/D2371 GHC Trac Issues: #12230 >--------------------------------------------------------------- ee8d1facb20ab579c44bf4cd7d5fd807d547b6ad rts/Linker.c | 4 +--- rts/LinkerInternals.h | 5 ----- 2 files changed, 1 insertion(+), 8 deletions(-) diff --git a/rts/Linker.c b/rts/Linker.c index f7ac748..b41bc1a 100644 --- a/rts/Linker.c +++ b/rts/Linker.c @@ -1703,9 +1703,7 @@ void freeObjectCode (ObjectCode *oc) * Sets the initial status of a fresh ObjectCode */ static void setOcInitialStatus(ObjectCode* oc) { - if (oc->isImportLib == HS_BOOL_TRUE) { - oc->status = OBJECT_DONT_RESOLVE; - } else if (oc->archiveMemberName == NULL) { + if (oc->archiveMemberName == NULL) { oc->status = OBJECT_NEEDED; } else { oc->status = OBJECT_LOADED; diff --git a/rts/LinkerInternals.h b/rts/LinkerInternals.h index 5686863..729cf1d 100644 --- a/rts/LinkerInternals.h +++ b/rts/LinkerInternals.h @@ -160,11 +160,6 @@ typedef struct _ObjectCode { ForeignExportStablePtr *stable_ptrs; - /* Indicates whether if the .o file comes from - an import library. In which case we shouldn't - execute code from it. */ - HsBool isImportLib; - /* Holds the list of symbols in the .o file which require extra information.*/ HashTable *extraInfos; From git at git.haskell.org Fri Jul 1 12:22:26 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 1 Jul 2016 12:22:26 +0000 (UTC) Subject: [commit: ghc] master: Linker: some extra debugging / logging (6377757) Message-ID: <20160701122226.296DA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6377757918c1e7f63638d6f258cad8d5f02bb6a7/ghc >--------------------------------------------------------------- commit 6377757918c1e7f63638d6f258cad8d5f02bb6a7 Author: Simon Marlow Date: Wed Jun 29 21:50:18 2016 +0100 Linker: some extra debugging / logging >--------------------------------------------------------------- 6377757918c1e7f63638d6f258cad8d5f02bb6a7 rts/Linker.c | 25 +++++++++++++++++++++++++ 1 file changed, 25 insertions(+) diff --git a/rts/Linker.c b/rts/Linker.c index b41bc1a..894a31d 100644 --- a/rts/Linker.c +++ b/rts/Linker.c @@ -1465,6 +1465,27 @@ void ghci_enquire(SymbolAddr* addr) } } } + +void ghci_find(SymbolAddr *addr); +void ghci_find(SymbolAddr *addr) +{ + ObjectCode *oc; + uint32_t i; + + for (oc = objects; oc != NULL; oc = oc->next) { + for (i = 0; i < (uint32_t)oc->n_sections; i++) { + Section *section = &oc->sections[i]; + if (addr > section->start && + (StgWord)addr < (StgWord)section->start+section->size) { + debugBelch("%p is in %" PATH_FMT, addr, + oc->archiveMemberName ? + oc->archiveMemberName : oc->fileName); + debugBelch(", section %d, offset %lx\n", i, + (StgWord)addr - (StgWord)section->start); + } + } + } +} #endif #if RTS_LINKER_USE_MMAP @@ -2537,6 +2558,10 @@ int ocTryLoad (ObjectCode* oc) { } } + IF_DEBUG(linker, debugBelch("Resolving %" PATH_FMT "\n", + oc->archiveMemberName ? + oc->archiveMemberName : oc->fileName)); + # if defined(OBJFORMAT_ELF) r = ocResolve_ELF ( oc ); # elif defined(OBJFORMAT_PEi386) From git at git.haskell.org Fri Jul 1 12:40:43 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 1 Jul 2016 12:40:43 +0000 (UTC) Subject: [commit: ghc] master: Remove uniqSetToList (cbfeff4) Message-ID: <20160701124043.3993C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/cbfeff4b3caade8092c13f0f71371e6525ece9ac/ghc >--------------------------------------------------------------- commit cbfeff4b3caade8092c13f0f71371e6525ece9ac Author: Bartosz Nitka Date: Fri Jul 1 04:58:39 2016 -0700 Remove uniqSetToList This documents nondeterminism in code generation and removes the nondeterministic ufmToList function. In the future someone will have to use nonDetEltsUFM (with proper explanation) or pprUFM. >--------------------------------------------------------------- cbfeff4b3caade8092c13f0f71371e6525ece9ac compiler/llvmGen/LlvmCodeGen/Base.hs | 5 ++++- compiler/nativeGen/RegAlloc/Graph/ArchBase.hs | 13 +++++++++---- compiler/nativeGen/RegAlloc/Graph/Main.hs | 21 +++++++++++++-------- compiler/nativeGen/RegAlloc/Graph/Spill.hs | 10 +++++++--- compiler/nativeGen/RegAlloc/Graph/SpillClean.hs | 6 ++++-- compiler/nativeGen/RegAlloc/Graph/SpillCost.hs | 11 ++++++++--- compiler/nativeGen/RegAlloc/Linear/Main.hs | 8 +++++--- compiler/nativeGen/RegAlloc/Liveness.hs | 24 +++++++++++++++--------- compiler/utils/GraphColor.hs | 6 ++++-- compiler/utils/GraphOps.hs | 18 +++++++++++------- compiler/utils/GraphPpr.hs | 9 ++++++--- compiler/utils/UniqSet.hs | 3 --- 12 files changed, 86 insertions(+), 48 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc cbfeff4b3caade8092c13f0f71371e6525ece9ac From git at git.haskell.org Fri Jul 1 14:26:17 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 1 Jul 2016 14:26:17 +0000 (UTC) Subject: [commit: ghc] master: Document some benign nondeterminism (0d522b8) Message-ID: <20160701142617.4C11C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0d522b80bc9d3cfc2b23a3a4d9092e08f006054e/ghc >--------------------------------------------------------------- commit 0d522b80bc9d3cfc2b23a3a4d9092e08f006054e Author: Bartosz Nitka Date: Fri Jul 1 07:29:08 2016 -0700 Document some benign nondeterminism >--------------------------------------------------------------- 0d522b80bc9d3cfc2b23a3a4d9092e08f006054e compiler/main/TidyPgm.hs | 10 ++++++++-- 1 file changed, 8 insertions(+), 2 deletions(-) diff --git a/compiler/main/TidyPgm.hs b/compiler/main/TidyPgm.hs index aed985d..c02c786 100644 --- a/compiler/main/TidyPgm.hs +++ b/compiler/main/TidyPgm.hs @@ -57,6 +57,7 @@ import Maybes import UniqSupply import ErrUtils (Severity(..)) import Outputable +import UniqFM import SrcLoc import qualified ErrUtils as Err @@ -484,7 +485,10 @@ tidyVectInfo (_, var_env) info@(VectInfo { vectInfoVar = vars -- we only export mappings whose domain and co-domain is exported (otherwise, the iface is -- inconsistent) tidy_vars = mkVarEnv [ (tidy_var, (tidy_var, tidy_var_v)) - | (var, var_v) <- varEnvElts vars + | (var, var_v) <- nonDetEltsUFM vars + -- It's OK to use nonDetEltsUFM here because we + -- immediately forget the ordering by creating + -- a new env , let tidy_var = lookup_var var tidy_var_v = lookup_var var_v , isExternalId tidy_var && isExportedId tidy_var @@ -658,7 +662,9 @@ chooseExternalIds hsc_env mod omit_prags expose_all binds implicit_binds imp_id_ isJust $ collectStaticPtrSatArgs e rule_rhs_vars = mapUnionVarSet ruleRhsFreeVars imp_id_rules - vect_var_vs = mkVarSet [var_v | (var, var_v) <- nameEnvElts vect_vars, isGlobalId var] + vect_var_vs = mkVarSet [var_v | (var, var_v) <- nonDetEltsUFM vect_vars, isGlobalId var] + -- It's OK to use nonDetEltsUFM here because we immediately forget the + -- ordering by creating a set flatten_binds = flattenBinds binds binders = map fst flatten_binds From git at git.haskell.org Fri Jul 1 15:22:11 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 1 Jul 2016 15:22:11 +0000 (UTC) Subject: [commit: ghc] master: Kill varEnvElts in seqDmdEnv (0ab63cf) Message-ID: <20160701152211.DC1333A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0ab63cf48580abbfe15ece934aec093203f29ed2/ghc >--------------------------------------------------------------- commit 0ab63cf48580abbfe15ece934aec093203f29ed2 Author: Bartosz Nitka Date: Fri Jul 1 06:50:55 2016 -0700 Kill varEnvElts in seqDmdEnv GHC Trac: #4012 >--------------------------------------------------------------- 0ab63cf48580abbfe15ece934aec093203f29ed2 compiler/basicTypes/Demand.hs | 3 +-- compiler/utils/UniqFM.hs | 8 +++++++- 2 files changed, 8 insertions(+), 3 deletions(-) diff --git a/compiler/basicTypes/Demand.hs b/compiler/basicTypes/Demand.hs index 9165782..8dc7f3b 100644 --- a/compiler/basicTypes/Demand.hs +++ b/compiler/basicTypes/Demand.hs @@ -1306,8 +1306,7 @@ seqDmdType (DmdType env ds res) = seqDmdEnv env `seq` seqDemandList ds `seq` seqDmdResult res `seq` () seqDmdEnv :: DmdEnv -> () -seqDmdEnv env = seqDemandList (varEnvElts env) - +seqDmdEnv env = seqEltsUFM seqDemandList env splitDmdTy :: DmdType -> (Demand, DmdType) -- Split off one function argument diff --git a/compiler/utils/UniqFM.hs b/compiler/utils/UniqFM.hs index 261dd1c..bb9d95c 100644 --- a/compiler/utils/UniqFM.hs +++ b/compiler/utils/UniqFM.hs @@ -54,7 +54,7 @@ module UniqFM ( intersectUFM_C, disjointUFM, nonDetFoldUFM, foldUFM, nonDetFoldUFM_Directly, - anyUFM, allUFM, + anyUFM, allUFM, seqEltsUFM, mapUFM, mapUFM_Directly, elemUFM, elemUFM_Directly, filterUFM, filterUFM_Directly, partitionUFM, @@ -292,6 +292,12 @@ anyUFM p (UFM m) = M.fold ((||) . p) False m allUFM :: (elt -> Bool) -> UniqFM elt -> Bool allUFM p (UFM m) = M.fold ((&&) . p) True m +seqEltsUFM :: ([elt] -> ()) -> UniqFM elt -> () +seqEltsUFM seqList = seqList . nonDetEltsUFM + -- It's OK to use nonDetEltsUFM here because the type guarantees that + -- the only interesting thing this function can do is to force the + -- elements. + -- See Note [Deterministic UniqFM] to learn about nondeterminism. -- If you use this please provide a justification why it doesn't introduce -- nondeterminism. From git at git.haskell.org Mon Jul 4 12:06:34 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 4 Jul 2016 12:06:34 +0000 (UTC) Subject: [commit: ghc] wip/T10613: DmdAnal: Remember why “Many” things are many, even through ifaces (bdbafb7) Message-ID: <20160704120634.A0FCB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10613 Link : http://ghc.haskell.org/trac/ghc/changeset/bdbafb7ebc01dcdf8ed6e7c2a139c4cd37a52a71/ghc >--------------------------------------------------------------- commit bdbafb7ebc01dcdf8ed6e7c2a139c4cd37a52a71 Author: Joachim Breitner Date: Mon Jul 4 10:16:07 2016 +0200 DmdAnal: Remember why “Many” things are many, even through ifaces >--------------------------------------------------------------- bdbafb7ebc01dcdf8ed6e7c2a139c4cd37a52a71 compiler/basicTypes/Demand.hs | 8 ++++++-- 1 file changed, 6 insertions(+), 2 deletions(-) diff --git a/compiler/basicTypes/Demand.hs b/compiler/basicTypes/Demand.hs index 58a3209..c8d42b0 100644 --- a/compiler/basicTypes/Demand.hs +++ b/compiler/basicTypes/Demand.hs @@ -69,6 +69,7 @@ import UniqFM import Util import BasicTypes import Binary +import FastString import Maybes ( orElse ) import Type ( Type, isUnliftedType ) @@ -2066,12 +2067,15 @@ instance Binary ArgStr where instance Binary Count where put_ bh One = do putByte bh 0 - put_ bh (Many _) = do putByte bh 1 + put_ bh (Many mr) = do + putByte bh 1 + put_ bh (map mkFastString mr) get bh = do h <- getByte bh case h of 0 -> return One - _ -> return (Many ["iface"]) + _ -> do mr <- get bh + return (Many (map unpackFS mr)) instance Binary ArgUse where put_ bh Abs = do From git at git.haskell.org Mon Jul 4 12:06:37 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 4 Jul 2016 12:06:37 +0000 (UTC) Subject: [commit: ghc] wip/T10613: ENTER must not short-circuit COUNTING_IND (e201031) Message-ID: <20160704120637.524D33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10613 Link : http://ghc.haskell.org/trac/ghc/changeset/e20103101fb89f946cbf95f7111903d0755e189e/ghc >--------------------------------------------------------------- commit e20103101fb89f946cbf95f7111903d0755e189e Author: Joachim Breitner Date: Mon Jul 4 13:40:01 2016 +0200 ENTER must not short-circuit COUNTING_IND >--------------------------------------------------------------- e20103101fb89f946cbf95f7111903d0755e189e includes/Cmm.h | 1 - 1 file changed, 1 deletion(-) diff --git a/includes/Cmm.h b/includes/Cmm.h index 4fd5910..3b9a5a6 100644 --- a/includes/Cmm.h +++ b/includes/Cmm.h @@ -288,7 +288,6 @@ (TO_W_( %INFO_TYPE(%STD_INFO(info)) )) { \ case \ IND, \ - COUNTING_IND, \ IND_STATIC: \ { \ x = StgInd_indirectee(x); \ From git at git.haskell.org Mon Jul 4 12:06:40 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 4 Jul 2016 12:06:40 +0000 (UTC) Subject: [commit: ghc] wip/T10613: Add perl script to aggreate numbers for the demand analysis paper (36c4c7b) Message-ID: <20160704120640.4A02F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10613 Link : http://ghc.haskell.org/trac/ghc/changeset/36c4c7baf5f9a30b9e651917cbbc327a7f3f4941/ghc >--------------------------------------------------------------- commit 36c4c7baf5f9a30b9e651917cbbc327a7f3f4941 Author: Joachim Breitner Date: Mon Jul 4 13:49:22 2016 +0200 Add perl script to aggreate numbers for the demand analysis paper Don't worry, this is not intended to enter the master. >--------------------------------------------------------------- 36c4c7baf5f9a30b9e651917cbbc327a7f3f4941 card-count.pl | 166 ++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 166 insertions(+) diff --git a/card-count.pl b/card-count.pl new file mode 100755 index 0000000..49a43ae --- /dev/null +++ b/card-count.pl @@ -0,0 +1,166 @@ +#!/usr/bin/perl + +use strict; +use warnings; + + +my $reading = 0; + +# key: 1 <=> single entry (first static then dynamic) +my %thunk_counts = ( + 0 => {0 => 0, 1 => 0, 2=>0 }, + 1 => {0 => 0, 1 => 0, 2=>0 }, + ); +my %dyn_thunk_counts = ( + 0 => {0 => 0, 1 => 0, 2=>0 }, + 1 => {0 => 0, 1 => 0, 2=>0 }, + ); +my %fun_counts = ( + 0 => {0 => 0, 1 => 0, 2=>0 }, + 1 => {0 => 0, 1 => 0, 2=>0 }, + ); + +my %reason_counts = (); +my %unique_reason_counts = (); + +my @interesting; + +while (<>) { + if ($reading and /^$/) {$reading = 0}; + if (not $reading and /^----------------/) {$reading = 1; next;}; + next unless $reading; + + if (m/^ + \s+ + (?\d+)\s+ + (?\d+)\s+ + (?\d+)\s+ + (?\d+)\s+ + (?\d+)\s+ + (?\d+)\s+ + (?\d+)\s+ + (?.*) + /nx) + { + my %vals = %+; + + + # ignore constructors + next if $vals{rest} =~ m/\(con\)/; + + + # ignore never allocated things + next if $vals{nalloc} == 0; + + # ignore static or dead entries + #next if $vals{single} + $vals{multiple} == 0; + + my ($flags) = ($vals{rest} =~ m/\((?:thk|fun)(.*)\)/); + my ($manyreasons) = ($flags =~ m/\((.*)\)/); + $manyreasons ||= ""; + my @manyreasons = split ",",$manyreasons; + + my $thk = $vals{rest} =~ m/\(thk/; + my $static_se = $flags =~ m/,se/ ? 1 : 0; + my $boring = 0; + my $dynamic_se = $vals{multiple} == 0 ? 1 : 0; + my $dynamic_dead = ($vals{single} + $vals{multiple} == 0) ? 1 : 0; + + if ($thk) { + $thunk_counts{$static_se}{$dynamic_se + $dynamic_dead}++; + $dyn_thunk_counts{$static_se}{$dynamic_se + $dynamic_dead} += $vals{nalloc}; + } else { + $fun_counts{$static_se}{$dynamic_se + $dynamic_dead}++; + } + + if ($thk and $dynamic_se and not $static_se and not $boring) { + $reason_counts{$_} += $vals{nalloc} for @manyreasons; + if (@manyreasons > 1) { + $unique_reason_counts{various} += $vals{nalloc}; + } else { + $unique_reason_counts{$manyreasons[0]} += $vals{nalloc}; + } + push @interesting, { n => $vals{single}, desc => $vals{rest}}; + } + } else { + print "Could not parse $_" + } +} + +sub print_table { + my ($title, $tab) = @_; + + printf <<__END__, +%s: + | Static s.e. | Normal | Sum +Dynamic dead | %12d | %12d | %12d (Proportion: %4.1f%%) +Dynamic s.e. | %12d | %12d | %12d (Proportion: %4.1f%%) +Multi entries | %12d | %12d | %12d +Sum | %12d | %12d | %12d + +__END__ + $title, + $tab->{1}{2}, + $tab->{0}{2}, + $tab->{1}{2} + $tab->{0}{2}, + ($tab->{1}{2} + $tab->{0}{2}) ? ($tab->{1}{2} / ($tab->{1}{2} + $tab->{0}{2}) * 100) : 0, + $tab->{1}{1}, + $tab->{0}{1}, + $tab->{1}{1} + $tab->{0}{1}, + ($tab->{1}{1} + $tab->{0}{1}) ? ($tab->{1}{1} / ($tab->{1}{1} + $tab->{0}{1}) * 100) : 0, + $tab->{1}{0}, + $tab->{0}{0}, + $tab->{1}{0} + $tab->{0}{0}, + $tab->{1}{2} + $tab->{1}{1} + $tab->{1}{0}, + $tab->{0}{2} + $tab->{0}{1} + $tab->{0}{0}, + $tab->{1}{2} + $tab->{0}{2} + $tab->{1}{1} + $tab->{0}{1} + $tab->{1}{0} + $tab->{0}{0}; + +} + +print_table ("Thunks (counted per info table)", \%thunk_counts); +print_table ("Thunks (counted per dynamically allocated instance)", \%dyn_thunk_counts); +print_table ("Functions", \%fun_counts); + + at interesting = sort { $b->{n} <=> $a->{n} } @interesting; + +# srsly? should have used Haskell... +sub max ($$) { $_[$_[0] < $_[1]] } +sub min ($$) { $_[$_[0] > $_[1]] } + + +printf <<__END__; +Interesting missed opportunities: +__END__ + +for (@interesting[0..min(10,$#interesting)]) { + printf "%10d: %s\n", $_->{n}, $_->{desc}; +} + +my $total = $dyn_thunk_counts{0}{1} + $dyn_thunk_counts{0}{2}; + +my @reason_counts = (); +push @reason_counts, { reason => $_, n => $reason_counts{$_} } foreach keys %reason_counts ; + at reason_counts = sort { $b->{n} <=> $a->{n} } @reason_counts; + +printf <<__END__; +Most common reasons +__END__ + +for (@reason_counts[0..min(99,$#reason_counts)]) { + printf "%10d: (%4.1f%%) %s\n", $_->{n}, $_->{n} / $total * 100, $_->{reason}; +} + + +my @unique_reason_counts = (); +push @unique_reason_counts, { reason => $_, n => $unique_reason_counts{$_} } foreach keys %unique_reason_counts ; + at unique_reason_counts = sort { $b->{n} <=> $a->{n} } @unique_reason_counts; + +printf <<__END__; +Most common unique reasons +__END__ + +for (@unique_reason_counts[0..min(99,$#unique_reason_counts)]) { + printf "%10d: (%4.1f%%) %s\n", $_->{n}, $_->{n} / $total * 100, $_->{reason}; +} + + From git at git.haskell.org Mon Jul 4 12:13:20 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 4 Jul 2016 12:13:20 +0000 (UTC) Subject: [commit: ghc] master: Fix 32-bit build failures (01f449f) Message-ID: <20160704121320.3C92E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/01f449f4ffd2c4f23bfe5698b9f1b98a86276900/ghc >--------------------------------------------------------------- commit 01f449f4ffd2c4f23bfe5698b9f1b98a86276900 Author: Simon Marlow Date: Mon Jul 4 10:56:04 2016 +0100 Fix 32-bit build failures >--------------------------------------------------------------- 01f449f4ffd2c4f23bfe5698b9f1b98a86276900 rts/Linker.c | 11 +++++++---- 1 file changed, 7 insertions(+), 4 deletions(-) diff --git a/rts/Linker.c b/rts/Linker.c index 894a31d..40ea8de 100644 --- a/rts/Linker.c +++ b/rts/Linker.c @@ -1477,10 +1477,13 @@ void ghci_find(SymbolAddr *addr) Section *section = &oc->sections[i]; if (addr > section->start && (StgWord)addr < (StgWord)section->start+section->size) { - debugBelch("%p is in %" PATH_FMT, addr, - oc->archiveMemberName ? - oc->archiveMemberName : oc->fileName); - debugBelch(", section %d, offset %lx\n", i, + debugBelch("%p is in ", addr); + if (oc->archiveMemberName) { + debugBelch("%s", oc->archiveMemberName); + } else { + debugBelch("%" PATH_FMT, oc->fileName); + } + debugBelch(", section %d, offset %" FMT_Word "\n", i, (StgWord)addr - (StgWord)section->start); } } From git at git.haskell.org Mon Jul 4 13:47:35 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 4 Jul 2016 13:47:35 +0000 (UTC) Subject: [commit: ghc] master: MkCore: Fix some note names (9031382) Message-ID: <20160704134735.347793A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9031382038e9c2dc753c297f0589a9148ac4f8b0/ghc >--------------------------------------------------------------- commit 9031382038e9c2dc753c297f0589a9148ac4f8b0 Author: Ömer Sinan Ağacan Date: Mon Jul 4 13:51:27 2016 +0000 MkCore: Fix some note names >--------------------------------------------------------------- 9031382038e9c2dc753c297f0589a9148ac4f8b0 compiler/coreSyn/MkCore.hs | 14 +++++++------- 1 file changed, 7 insertions(+), 7 deletions(-) diff --git a/compiler/coreSyn/MkCore.hs b/compiler/coreSyn/MkCore.hs index 7d9ef14..d9a7a21 100644 --- a/compiler/coreSyn/MkCore.hs +++ b/compiler/coreSyn/MkCore.hs @@ -323,17 +323,17 @@ Usually we want the former, but occasionally the latter. -} -- | Build a small tuple holding the specified variables --- One-tuples are flattened; see Note [Flattening of one-tuples] +-- One-tuples are flattened; see Note [Flattening one-tuples] mkCoreVarTup :: [Id] -> CoreExpr mkCoreVarTup ids = mkCoreTup (map Var ids) -- | Build the type of a small tuple that holds the specified variables --- One-tuples are flattened; see Note [Flattening of one-tuples] +-- One-tuples are flattened; see Note [Flattening one-tuples] mkCoreVarTupTy :: [Id] -> Type mkCoreVarTupTy ids = mkBoxedTupleTy (map idType ids) -- | Build a small tuple holding the specified expressions --- One-tuples are flattened; see NOte [Flattening of one-tuples] +-- One-tuples are flattened; see Note [Flattening one-tuples] mkCoreTup :: [CoreExpr] -> CoreExpr mkCoreTup [] = Var unitDataConId mkCoreTup [c] = c @@ -357,7 +357,7 @@ mkCoreTupBoxity Boxed exps = mkCoreTup exps mkCoreTupBoxity Unboxed exps = mkCoreUbxTup (map exprType exps) exps -- | Build a big tuple holding the specified variables --- One-tuples are flattened; see Note [Flattening of one-tuples] +-- One-tuples are flattened; see Note [Flattening one-tuples] mkBigCoreVarTup :: [Id] -> CoreExpr mkBigCoreVarTup ids = mkBigCoreTup (map Var ids) @@ -369,17 +369,17 @@ mkBigCoreVarTup1 [id] = mkCoreConApps (tupleDataCon Boxed 1) mkBigCoreVarTup1 ids = mkBigCoreTup (map Var ids) -- | Build the type of a big tuple that holds the specified variables --- One-tuples are flattened; see Note [Flattening of one-tuples] +-- One-tuples are flattened; see Note [Flattening one-tuples] mkBigCoreVarTupTy :: [Id] -> Type mkBigCoreVarTupTy ids = mkBigCoreTupTy (map idType ids) -- | Build a big tuple holding the specified expressions --- One-tuples are flattened; see Note [Flattening of one-tuples] +-- One-tuples are flattened; see Note [Flattening one-tuples] mkBigCoreTup :: [CoreExpr] -> CoreExpr mkBigCoreTup = mkChunkified mkCoreTup -- | Build the type of a big tuple that holds the specified type of thing --- One-tuples are flattened; see Note [Flattening of one-tuples] +-- One-tuples are flattened; see Note [Flattening one-tuples] mkBigCoreTupTy :: [Type] -> Type mkBigCoreTupTy = mkChunkified mkBoxedTupleTy From git at git.haskell.org Mon Jul 4 14:58:41 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 4 Jul 2016 14:58:41 +0000 (UTC) Subject: [commit: ghc] branch 'wip/T12354' created Message-ID: <20160704145841.186393A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/T12354 Referencing: 5eebc7467746c5417d2c8815b88fac40d7e20963 From git at git.haskell.org Mon Jul 4 14:58:43 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 4 Jul 2016 14:58:43 +0000 (UTC) Subject: [commit: ghc] wip/T12354: Experiment with demand analysis for sum types (#12364) (5eebc74) Message-ID: <20160704145843.DBA123A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T12354 Link : http://ghc.haskell.org/trac/ghc/changeset/5eebc7467746c5417d2c8815b88fac40d7e20963/ghc >--------------------------------------------------------------- commit 5eebc7467746c5417d2c8815b88fac40d7e20963 Author: Joachim Breitner Date: Mon Jul 4 17:00:53 2016 +0200 Experiment with demand analysis for sum types (#12364) This works towards demand information for sum types. At the moment, it is mostly a hack, but stage1 compiles, and small programs run. So lets see how well it fares on perf.haskell.org. >--------------------------------------------------------------- 5eebc7467746c5417d2c8815b88fac40d7e20963 compiler/basicTypes/Demand.hs | 123 +++++++++++++++++++++++------------------- compiler/stranal/DmdAnal.hs | 78 +++++++++++++++++++-------- compiler/stranal/WwLib.hs | 3 ++ 3 files changed, 125 insertions(+), 79 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 5eebc7467746c5417d2c8815b88fac40d7e20963 From git at git.haskell.org Mon Jul 4 19:27:46 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 4 Jul 2016 19:27:46 +0000 (UTC) Subject: [commit: ghc] master: base: Add release date to changelog (a6819a0) Message-ID: <20160704192746.AA0423A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a6819a088efe689ccfb760b762f9b7a27b88e452/ghc >--------------------------------------------------------------- commit a6819a088efe689ccfb760b762f9b7a27b88e452 Author: Ben Gamari Date: Sat May 7 09:30:20 2016 +0200 base: Add release date to changelog >--------------------------------------------------------------- a6819a088efe689ccfb760b762f9b7a27b88e452 libraries/base/changelog.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index 3b44ded..5a2e90f 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -12,7 +12,7 @@ * `New modules `Data.Bifoldable` and `Data.Bitraversable` (previously defined in the `bifunctors` package) (#10448) -## 4.9.0.0 *TBA* +## 4.9.0.0 *May 2016* * Bundled with GHC 8.0 From git at git.haskell.org Mon Jul 4 21:31:27 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 4 Jul 2016 21:31:27 +0000 (UTC) Subject: [commit: ghc] master: users-guide: Remove static field type from rts-flag (3b2deca) Message-ID: <20160704213127.F20F03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3b2deca1d8213278b11feb57651262464d4daeeb/ghc >--------------------------------------------------------------- commit 3b2deca1d8213278b11feb57651262464d4daeeb Author: Ben Gamari Date: Fri Jul 1 14:56:01 2016 +0200 users-guide: Remove static field type from rts-flag This was introduced by a cut-and-paste error. >--------------------------------------------------------------- 3b2deca1d8213278b11feb57651262464d4daeeb docs/users_guide/conf.py | 1 - 1 file changed, 1 deletion(-) diff --git a/docs/users_guide/conf.py b/docs/users_guide/conf.py index b2311c4..046b3c8 100644 --- a/docs/users_guide/conf.py +++ b/docs/users_guide/conf.py @@ -172,7 +172,6 @@ def setup(app): indextemplate='pair: %s; RTS option', doc_field_types=[ Field('since', label='Introduced in GHC version', names=['since']), - Field('static') ]) def increase_python_stack(): From git at git.haskell.org Mon Jul 4 21:31:31 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 4 Jul 2016 21:31:31 +0000 (UTC) Subject: [commit: ghc] master: testsuite: Add testcase for #12355 (afec447) Message-ID: <20160704213131.1910F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/afec447cde1f97438bbc5bf7a31000e948c721eb/ghc >--------------------------------------------------------------- commit afec447cde1f97438bbc5bf7a31000e948c721eb Author: Ben Gamari Date: Fri Jul 1 14:29:54 2016 +0200 testsuite: Add testcase for #12355 Test Plan: Validate Reviewers: austin, osa1 Reviewed By: osa1 Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2377 GHC Trac Issues: #12355 >--------------------------------------------------------------- afec447cde1f97438bbc5bf7a31000e948c721eb testsuite/tests/codeGen/should_compile/T12355.hs | 7 +++++++ testsuite/tests/codeGen/should_compile/all.T | 1 + 2 files changed, 8 insertions(+) diff --git a/testsuite/tests/codeGen/should_compile/T12355.hs b/testsuite/tests/codeGen/should_compile/T12355.hs new file mode 100644 index 0000000..9ad9ebe --- /dev/null +++ b/testsuite/tests/codeGen/should_compile/T12355.hs @@ -0,0 +1,7 @@ +{-# LANGUAGE GHCForeignImportPrim, UnliftedFFITypes, MagicHash #-} + +module Lib where + +import GHC.Prim + +foreign import prim f1 :: Int# -> Int# diff --git a/testsuite/tests/codeGen/should_compile/all.T b/testsuite/tests/codeGen/should_compile/all.T index 57ae5eb..2fac947 100644 --- a/testsuite/tests/codeGen/should_compile/all.T +++ b/testsuite/tests/codeGen/should_compile/all.T @@ -37,3 +37,4 @@ test('T10667', [ when((arch('powerpc64') or arch('powerpc64le')), expect_broken(11261))], compile, ['-g']) test('T12115', normal, compile, ['']) +test('T12355', expect_broken(12355), compile, ['']) From git at git.haskell.org Mon Jul 4 21:31:34 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 4 Jul 2016 21:31:34 +0000 (UTC) Subject: [commit: ghc] master: Treat duplicate pattern synonym signatures as an error (2a3af15) Message-ID: <20160704213134.44F783A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2a3af15270d1c04745b1c42e61bf4d5f6dbc8ad5/ghc >--------------------------------------------------------------- commit 2a3af15270d1c04745b1c42e61bf4d5f6dbc8ad5 Author: Seraphime Kirkovski Date: Fri Jul 1 14:30:10 2016 +0200 Treat duplicate pattern synonym signatures as an error Fixes issue T12165 by banning duplicate pattern synonyms signatures. This seems to me the best solution because: 1) it is coherent with the way we treat other duplicate signatures 2) the typechecker currently doesn't try to apply a second signature to a pattern to see if it matches, probably because it assumes there is no more than one signature per object. Test Plan: ./validate Reviewers: goldfire, austin, mpickering, bgamari Reviewed By: mpickering, bgamari Subscribers: mpickering, thomie Differential Revision: https://phabricator.haskell.org/D2361 GHC Trac Issues: #12165 >--------------------------------------------------------------- 2a3af15270d1c04745b1c42e61bf4d5f6dbc8ad5 compiler/rename/RnBinds.hs | 2 ++ testsuite/tests/patsyn/should_fail/T12165.hs | 6 ++++++ testsuite/tests/patsyn/should_fail/T12165.stderr | 5 +++++ testsuite/tests/patsyn/should_fail/all.T | 1 + 4 files changed, 14 insertions(+) diff --git a/compiler/rename/RnBinds.hs b/compiler/rename/RnBinds.hs index f6c18b4..2e4f4db 100644 --- a/compiler/rename/RnBinds.hs +++ b/compiler/rename/RnBinds.hs @@ -988,6 +988,7 @@ findDupSigs sigs expand_sig sig@(InlineSig n _) = [(n,sig)] expand_sig sig@(TypeSig ns _) = [(n,sig) | n <- ns] expand_sig sig@(ClassOpSig _ ns _) = [(n,sig) | n <- ns] + expand_sig sig@(PatSynSig ns _ ) = [(n,sig) | n <- ns] expand_sig _ = [] matching_sig (L _ n1,sig1) (L _ n2,sig2) = n1 == n2 && mtch sig1 sig2 @@ -995,6 +996,7 @@ findDupSigs sigs mtch (InlineSig {}) (InlineSig {}) = True mtch (TypeSig {}) (TypeSig {}) = True mtch (ClassOpSig d1 _ _) (ClassOpSig d2 _ _) = d1 == d2 + mtch (PatSynSig _ _) (PatSynSig _ _) = True mtch _ _ = False -- Warn about multiple MINIMAL signatures diff --git a/testsuite/tests/patsyn/should_fail/T12165.hs b/testsuite/tests/patsyn/should_fail/T12165.hs new file mode 100644 index 0000000..0fbf964 --- /dev/null +++ b/testsuite/tests/patsyn/should_fail/T12165.hs @@ -0,0 +1,6 @@ +{-# LANGUAGE PatternSynonyms #-} +module ShouldFail where + +pattern P :: a -> b -> Maybe (a,b) +pattern P :: foo => bar => blah -> urgh +pattern P x y = Just (x, y) diff --git a/testsuite/tests/patsyn/should_fail/T12165.stderr b/testsuite/tests/patsyn/should_fail/T12165.stderr new file mode 100644 index 0000000..881e469 --- /dev/null +++ b/testsuite/tests/patsyn/should_fail/T12165.stderr @@ -0,0 +1,5 @@ + +T12165.hs:5:9: error: + Duplicate pattern synonym signatures for ‘P’ + at T12165.hs:4:9 + T12165.hs:5:9 diff --git a/testsuite/tests/patsyn/should_fail/all.T b/testsuite/tests/patsyn/should_fail/all.T index 658a5c0..fe0922c 100644 --- a/testsuite/tests/patsyn/should_fail/all.T +++ b/testsuite/tests/patsyn/should_fail/all.T @@ -31,3 +31,4 @@ test('T11053', normal, compile, ['-fwarn-missing-pattern-synonym-signatures']) test('T10426', normal, compile_fail, ['']) test('T11265', normal, compile_fail, ['']) test('T11667', normal, compile_fail, ['']) +test('T12165', normal, compile_fail, ['']) From git at git.haskell.org Mon Jul 4 21:31:36 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 4 Jul 2016 21:31:36 +0000 (UTC) Subject: [commit: ghc] master: CallArity: Use not . null instead of length > 0 (331febf) Message-ID: <20160704213136.E2E283A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/331febf084bb696061f550bbd76875104e427f3a/ghc >--------------------------------------------------------------- commit 331febf084bb696061f550bbd76875104e427f3a Author: Ben Gamari Date: Mon Jul 4 14:36:24 2016 +0200 CallArity: Use not . null instead of length > 0 Test Plan: Validate Reviewers: austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2381 >--------------------------------------------------------------- 331febf084bb696061f550bbd76875104e427f3a compiler/simplCore/CallArity.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/simplCore/CallArity.hs b/compiler/simplCore/CallArity.hs index e172aef..fda28a8 100644 --- a/compiler/simplCore/CallArity.hs +++ b/compiler/simplCore/CallArity.hs @@ -510,7 +510,7 @@ callArityAnal arity int (Let bind e) -- Which bindings should we look at? -- See Note [Which variables are interesting] isInteresting :: Var -> Bool -isInteresting v = 0 < length (typeArity (idType v)) +isInteresting v = not $ null (typeArity (idType v)) interestingBinds :: CoreBind -> [Var] interestingBinds = filter isInteresting . bindersOf From git at git.haskell.org Mon Jul 4 21:31:39 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 4 Jul 2016 21:31:39 +0000 (UTC) Subject: [commit: ghc] master: users-guide: Note multiple pattern signature change in relnotes (bf7cbe7) Message-ID: <20160704213139.9C7563A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/bf7cbe78058c1848dedc2cbf0699ac4a41057ab7/ghc >--------------------------------------------------------------- commit bf7cbe78058c1848dedc2cbf0699ac4a41057ab7 Author: Ben Gamari Date: Fri Jul 1 14:27:00 2016 +0200 users-guide: Note multiple pattern signature change in relnotes >--------------------------------------------------------------- bf7cbe78058c1848dedc2cbf0699ac4a41057ab7 docs/users_guide/8.2.1-notes.rst | 3 +++ docs/users_guide/glasgow_exts.rst | 3 +++ 2 files changed, 6 insertions(+) diff --git a/docs/users_guide/8.2.1-notes.rst b/docs/users_guide/8.2.1-notes.rst index f19512c..0a9963f 100644 --- a/docs/users_guide/8.2.1-notes.rst +++ b/docs/users_guide/8.2.1-notes.rst @@ -22,6 +22,9 @@ Language - TODO FIXME. +- Pattern synonym signatures can now be applied to multiple patterns, just like + value-level binding signatures. See :ref:`patsyn-typing` for details. + Compiler ~~~~~~~~ diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst index 6cf9883..8a35899 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -4256,6 +4256,9 @@ A module which imports ``MyNum(..)`` from ``Example`` and then re-exports ``Example``. A more complete specification can be found on the :ghc-wiki:`wiki. ` + +.. _patsyn-typing: + Typing of pattern synonyms -------------------------- From git at git.haskell.org Mon Jul 4 21:31:42 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 4 Jul 2016 21:31:42 +0000 (UTC) Subject: [commit: ghc] master: Enum: Ensure that operations on Word fuse (0bd7c4b) Message-ID: <20160704213142.4C7A93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0bd7c4b4240a27d4e26290741394b31b48db7671/ghc >--------------------------------------------------------------- commit 0bd7c4b4240a27d4e26290741394b31b48db7671 Author: Ben Gamari Date: Mon Jul 4 14:36:44 2016 +0200 Enum: Ensure that operations on Word fuse Test Plan: Validate, verify fusion Reviewers: austin, hvr Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2376 GHC Trac Issues: #12354 >--------------------------------------------------------------- 0bd7c4b4240a27d4e26290741394b31b48db7671 libraries/base/GHC/Enum.hs | 152 ++++++++++++++++++++++++++++++++++++++++----- 1 file changed, 138 insertions(+), 14 deletions(-) diff --git a/libraries/base/GHC/Enum.hs b/libraries/base/GHC/Enum.hs index e09d2a9..a8b6600 100644 --- a/libraries/base/GHC/Enum.hs +++ b/libraries/base/GHC/Enum.hs @@ -614,26 +614,150 @@ instance Enum Word where | x <= maxIntWord = I# (word2Int# x#) | otherwise = fromEnumError "Word" x - enumFrom n = map integerToWordX [wordToIntegerX n .. wordToIntegerX (maxBound :: Word)] - enumFromTo n1 n2 = map integerToWordX [wordToIntegerX n1 .. wordToIntegerX n2] - enumFromThenTo n1 n2 m = map integerToWordX [wordToIntegerX n1, wordToIntegerX n2 .. wordToIntegerX m] - enumFromThen n1 n2 = map integerToWordX [wordToIntegerX n1, wordToIntegerX n2 .. wordToIntegerX limit] - where - limit :: Word - limit | n2 >= n1 = maxBound - | otherwise = minBound + {-# INLINE enumFrom #-} + enumFrom (W# x#) = eftWord x# maxWord# + where !(W# maxWord#) = maxBound + -- Blarg: technically I guess enumFrom isn't strict! + + {-# INLINE enumFromTo #-} + enumFromTo (W# x) (W# y) = eftWord x y + + {-# INLINE enumFromThen #-} + enumFromThen (W# x1) (W# x2) = efdWord x1 x2 + + {-# INLINE enumFromThenTo #-} + enumFromThenTo (W# x1) (W# x2) (W# y) = efdtWord x1 x2 y maxIntWord :: Word -- The biggest word representable as an Int maxIntWord = W# (case maxInt of I# i -> int2Word# i) --- For some reason integerToWord and wordToInteger (GHC.Integer.Type) --- work over Word# -integerToWordX :: Integer -> Word -integerToWordX i = W# (integerToWord i) +----------------------------------------------------- +-- eftWord and eftWordFB deal with [a..b], which is the +-- most common form, so we take a lot of care +-- In particular, we have rules for deforestation + +{-# RULES +"eftWord" [~1] forall x y. eftWord x y = build (\ c n -> eftWordFB c n x y) +"eftWordList" [1] eftWordFB (:) [] = eftWord + #-} + +-- The Enum rules for Word work much the same way that they do for Int. +-- See Note [How the Enum rules work]. -wordToIntegerX :: Word -> Integer -wordToIntegerX (W# x#) = wordToInteger x# +{-# NOINLINE [1] eftWord #-} +eftWord :: Word# -> Word# -> [Word] +-- [x1..x2] +eftWord x0 y | isTrue# (x0 `gtWord#` y) = [] + | otherwise = go x0 + where + go x = W# x : if isTrue# (x `eqWord#` y) + then [] + else go (x `plusWord#` 1##) + +{-# INLINE [0] eftWordFB #-} +eftWordFB :: (Word -> r -> r) -> r -> Word# -> Word# -> r +eftWordFB c n x0 y | isTrue# (x0 `gtWord#` y) = n + | otherwise = go x0 + where + go x = W# x `c` if isTrue# (x `eqWord#` y) + then n + else go (x `plusWord#` 1##) + -- Watch out for y=maxBound; hence ==, not > + -- Be very careful not to have more than one "c" + -- so that when eftInfFB is inlined we can inline + -- whatever is bound to "c" + + +----------------------------------------------------- +-- efdWord and efdtWord deal with [a,b..] and [a,b..c]. +-- The code is more complicated because of worries about Word overflow. + +-- See Note [How the Enum rules work] +{-# RULES +"efdtWord" [~1] forall x1 x2 y. + efdtWord x1 x2 y = build (\ c n -> efdtWordFB c n x1 x2 y) +"efdtWordUpList" [1] efdtWordFB (:) [] = efdtWord + #-} + +efdWord :: Word# -> Word# -> [Word] +-- [x1,x2..maxWord] +efdWord x1 x2 + | isTrue# (x2 `geWord#` x1) = case maxBound of W# y -> efdtWordUp x1 x2 y + | otherwise = case minBound of W# y -> efdtWordDn x1 x2 y + +{-# NOINLINE [1] efdtWord #-} +efdtWord :: Word# -> Word# -> Word# -> [Word] +-- [x1,x2..y] +efdtWord x1 x2 y + | isTrue# (x2 `geWord#` x1) = efdtWordUp x1 x2 y + | otherwise = efdtWordDn x1 x2 y + +{-# INLINE [0] efdtWordFB #-} +efdtWordFB :: (Word -> r -> r) -> r -> Word# -> Word# -> Word# -> r +efdtWordFB c n x1 x2 y + | isTrue# (x2 `geWord#` x1) = efdtWordUpFB c n x1 x2 y + | otherwise = efdtWordDnFB c n x1 x2 y + +-- Requires x2 >= x1 +efdtWordUp :: Word# -> Word# -> Word# -> [Word] +efdtWordUp x1 x2 y -- Be careful about overflow! + | isTrue# (y `ltWord#` x2) = if isTrue# (y `ltWord#` x1) then [] else [W# x1] + | otherwise = -- Common case: x1 <= x2 <= y + let !delta = x2 `minusWord#` x1 -- >= 0 + !y' = y `minusWord#` delta -- x1 <= y' <= y; hence y' is representable + + -- Invariant: x <= y + -- Note that: z <= y' => z + delta won't overflow + -- so we are guaranteed not to overflow if/when we recurse + go_up x | isTrue# (x `gtWord#` y') = [W# x] + | otherwise = W# x : go_up (x `plusWord#` delta) + in W# x1 : go_up x2 + +-- Requires x2 >= x1 +efdtWordUpFB :: (Word -> r -> r) -> r -> Word# -> Word# -> Word# -> r +efdtWordUpFB c n x1 x2 y -- Be careful about overflow! + | isTrue# (y `ltWord#` x2) = if isTrue# (y `ltWord#` x1) then n else W# x1 `c` n + | otherwise = -- Common case: x1 <= x2 <= y + let !delta = x2 `minusWord#` x1 -- >= 0 + !y' = y `minusWord#` delta -- x1 <= y' <= y; hence y' is representable + + -- Invariant: x <= y + -- Note that: z <= y' => z + delta won't overflow + -- so we are guaranteed not to overflow if/when we recurse + go_up x | isTrue# (x `gtWord#` y') = W# x `c` n + | otherwise = W# x `c` go_up (x `plusWord#` delta) + in W# x1 `c` go_up x2 + +-- Requires x2 <= x1 +efdtWordDn :: Word# -> Word# -> Word# -> [Word] +efdtWordDn x1 x2 y -- Be careful about underflow! + | isTrue# (y `gtWord#` x2) = if isTrue# (y `gtWord#` x1) then [] else [W# x1] + | otherwise = -- Common case: x1 >= x2 >= y + let !delta = x2 `minusWord#` x1 -- <= 0 + !y' = y `minusWord#` delta -- y <= y' <= x1; hence y' is representable + + -- Invariant: x >= y + -- Note that: z >= y' => z + delta won't underflow + -- so we are guaranteed not to underflow if/when we recurse + go_dn x | isTrue# (x `ltWord#` y') = [W# x] + | otherwise = W# x : go_dn (x `plusWord#` delta) + in W# x1 : go_dn x2 + +-- Requires x2 <= x1 +efdtWordDnFB :: (Word -> r -> r) -> r -> Word# -> Word# -> Word# -> r +efdtWordDnFB c n x1 x2 y -- Be careful about underflow! + | isTrue# (y `gtWord#` x2) = if isTrue# (y `gtWord#` x1) then n else W# x1 `c` n + | otherwise = -- Common case: x1 >= x2 >= y + let !delta = x2 `minusWord#` x1 -- <= 0 + !y' = y `minusWord#` delta -- y <= y' <= x1; hence y' is representable + + -- Invariant: x >= y + -- Note that: z >= y' => z + delta won't underflow + -- so we are guaranteed not to underflow if/when we recurse + go_dn x | isTrue# (x `ltWord#` y') = W# x `c` n + | otherwise = W# x `c` go_dn (x `plusWord#` delta) + in W# x1 `c` go_dn x2 ------------------------------------------------------------------------ -- Integer From git at git.haskell.org Mon Jul 4 21:57:12 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 4 Jul 2016 21:57:12 +0000 (UTC) Subject: [commit: ghc] wip/T12354: Change type of UData to [[ArgUse]] (1c24ab8) Message-ID: <20160704215712.682963A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T12354 Link : http://ghc.haskell.org/trac/ghc/changeset/1c24ab8add3ac4d47eba2c5efeeaaf3d282e15b3/ghc >--------------------------------------------------------------- commit 1c24ab8add3ac4d47eba2c5efeeaaf3d282e15b3 Author: Joachim Breitner Date: Tue Jul 5 00:00:16 2016 +0200 Change type of UData to [[ArgUse]] it is cleaner than flattening the list of arguments into one, and then doing strange splicying arithmetic. The current patch compiles, but yields weird lint errors. Clearly stuff is still amiss. >--------------------------------------------------------------- 1c24ab8add3ac4d47eba2c5efeeaaf3d282e15b3 compiler/basicTypes/Demand.hs | 104 ++++++++++++++++++++++++------------------ compiler/stranal/DmdAnal.hs | 17 +++---- compiler/stranal/WwLib.hs | 2 +- 3 files changed, 67 insertions(+), 56 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 1c24ab8add3ac4d47eba2c5efeeaaf3d282e15b3 From git at git.haskell.org Tue Jul 5 07:37:23 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 5 Jul 2016 07:37:23 +0000 (UTC) Subject: [commit: ghc] master: Revert "Fix 32-bit build failures" (18e71e4) Message-ID: <20160705073723.D9B973A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/18e71e460488785e520aa83d1de291c23e9f0042/ghc >--------------------------------------------------------------- commit 18e71e460488785e520aa83d1de291c23e9f0042 Author: Simon Marlow Date: Tue Jul 5 08:40:52 2016 +0100 Revert "Fix 32-bit build failures" This reverts commit 01f449f4ffd2c4f23bfe5698b9f1b98a86276900. >--------------------------------------------------------------- 18e71e460488785e520aa83d1de291c23e9f0042 rts/Linker.c | 11 ++++------- 1 file changed, 4 insertions(+), 7 deletions(-) diff --git a/rts/Linker.c b/rts/Linker.c index 40ea8de..894a31d 100644 --- a/rts/Linker.c +++ b/rts/Linker.c @@ -1477,13 +1477,10 @@ void ghci_find(SymbolAddr *addr) Section *section = &oc->sections[i]; if (addr > section->start && (StgWord)addr < (StgWord)section->start+section->size) { - debugBelch("%p is in ", addr); - if (oc->archiveMemberName) { - debugBelch("%s", oc->archiveMemberName); - } else { - debugBelch("%" PATH_FMT, oc->fileName); - } - debugBelch(", section %d, offset %" FMT_Word "\n", i, + debugBelch("%p is in %" PATH_FMT, addr, + oc->archiveMemberName ? + oc->archiveMemberName : oc->fileName); + debugBelch(", section %d, offset %lx\n", i, (StgWord)addr - (StgWord)section->start); } } From git at git.haskell.org Tue Jul 5 07:37:26 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 5 Jul 2016 07:37:26 +0000 (UTC) Subject: [commit: ghc] master: Revert "Linker: some extra debugging / logging" (890ec98) Message-ID: <20160705073726.811503A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/890ec98cdf144ed7e1efd53c528187deee27b783/ghc >--------------------------------------------------------------- commit 890ec98cdf144ed7e1efd53c528187deee27b783 Author: Simon Marlow Date: Tue Jul 5 08:41:14 2016 +0100 Revert "Linker: some extra debugging / logging" This reverts commit 6377757918c1e7f63638d6f258cad8d5f02bb6a7. >--------------------------------------------------------------- 890ec98cdf144ed7e1efd53c528187deee27b783 rts/Linker.c | 25 ------------------------- 1 file changed, 25 deletions(-) diff --git a/rts/Linker.c b/rts/Linker.c index 894a31d..b41bc1a 100644 --- a/rts/Linker.c +++ b/rts/Linker.c @@ -1465,27 +1465,6 @@ void ghci_enquire(SymbolAddr* addr) } } } - -void ghci_find(SymbolAddr *addr); -void ghci_find(SymbolAddr *addr) -{ - ObjectCode *oc; - uint32_t i; - - for (oc = objects; oc != NULL; oc = oc->next) { - for (i = 0; i < (uint32_t)oc->n_sections; i++) { - Section *section = &oc->sections[i]; - if (addr > section->start && - (StgWord)addr < (StgWord)section->start+section->size) { - debugBelch("%p is in %" PATH_FMT, addr, - oc->archiveMemberName ? - oc->archiveMemberName : oc->fileName); - debugBelch(", section %d, offset %lx\n", i, - (StgWord)addr - (StgWord)section->start); - } - } - } -} #endif #if RTS_LINKER_USE_MMAP @@ -2558,10 +2537,6 @@ int ocTryLoad (ObjectCode* oc) { } } - IF_DEBUG(linker, debugBelch("Resolving %" PATH_FMT "\n", - oc->archiveMemberName ? - oc->archiveMemberName : oc->fileName)); - # if defined(OBJFORMAT_ELF) r = ocResolve_ELF ( oc ); # elif defined(OBJFORMAT_PEi386) From git at git.haskell.org Tue Jul 5 07:48:07 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 5 Jul 2016 07:48:07 +0000 (UTC) Subject: [commit: ghc] branch 'wip/T12357' created Message-ID: <20160705074807.B0C3D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/T12357 Referencing: d3a8db6e7a20e8ea3b80c67c8cdfc31ea761d684 From git at git.haskell.org Tue Jul 5 07:48:10 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 5 Jul 2016 07:48:10 +0000 (UTC) Subject: [commit: ghc] wip/T12357: FastString: Lazily unpack strings (c003779) Message-ID: <20160705074810.631813A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T12357 Link : http://ghc.haskell.org/trac/ghc/changeset/c0037797a5e0e8a42b70cdd077d20b22b2e19d7e/ghc >--------------------------------------------------------------- commit c0037797a5e0e8a42b70cdd077d20b22b2e19d7e Author: Ben Gamari Date: Mon Jul 4 19:58:06 2016 -0400 FastString: Lazily unpack strings Previously we would eagerly build a [Char] of the full string contents, resulting in unnecessarily high allocations in cases where only a short bit at the beginning of the string is called for. See #12357 for motivation. >--------------------------------------------------------------- c0037797a5e0e8a42b70cdd077d20b22b2e19d7e compiler/utils/Encoding.hs | 17 +++++++++++++++++ compiler/utils/FastString.hs | 4 +--- 2 files changed, 18 insertions(+), 3 deletions(-) diff --git a/compiler/utils/Encoding.hs b/compiler/utils/Encoding.hs index ae727d2..d959671 100644 --- a/compiler/utils/Encoding.hs +++ b/compiler/utils/Encoding.hs @@ -18,6 +18,7 @@ module Encoding ( utf8CharStart, utf8DecodeChar, utf8DecodeString, + utf8DecodeStringLazy, utf8EncodeChar, utf8EncodeString, utf8EncodedLength, @@ -32,6 +33,9 @@ import Foreign import Data.Char import Numeric import ExtsCompat46 +import qualified Data.ByteString as BS +import qualified Data.ByteString.Unsafe as BS +import System.IO.Unsafe ( unsafeInterleaveIO ) -- ----------------------------------------------------------------------------- -- UTF-8 @@ -110,6 +114,19 @@ utf8CharStart p = go p then go (p `plusPtr` (-1)) else return p +utf8DecodeStringLazy :: BS.ByteString -> IO [Char] +utf8DecodeStringLazy bs + = unpack bs + where + unpack bs + | BS.null bs = return [] + | otherwise = + BS.unsafeUseAsCString bs $ \ptr -> + case utf8DecodeChar (castPtr ptr) of + (c, nBytes) -> do + chs <- unsafeInterleaveIO $ unpack (BS.drop nBytes bs) + return (c : chs) + utf8DecodeString :: Ptr Word8 -> Int -> IO [Char] utf8DecodeString ptr len = unpack ptr diff --git a/compiler/utils/FastString.hs b/compiler/utils/FastString.hs index 40c3882..21cbfeb 100644 --- a/compiler/utils/FastString.hs +++ b/compiler/utils/FastString.hs @@ -482,9 +482,7 @@ nullFS f = BS.null (fs_bs f) -- | Unpacks and decodes the FastString unpackFS :: FastString -> String -unpackFS (FastString _ _ bs _) = - inlinePerformIO $ BS.unsafeUseAsCStringLen bs $ \(ptr, len) -> - utf8DecodeString (castPtr ptr) len +unpackFS (FastString _ _ bs _) = inlinePerformIO $ utf8DecodeStringLazy bs -- | Gives the UTF-8 encoded bytes corresponding to a 'FastString' bytesFS :: FastString -> [Word8] From git at git.haskell.org Tue Jul 5 07:48:13 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 5 Jul 2016 07:48:13 +0000 (UTC) Subject: [commit: ghc] wip/T12357: Encoding: Attempt at reducing allocations (33ff4c1) Message-ID: <20160705074813.182893A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T12357 Link : http://ghc.haskell.org/trac/ghc/changeset/33ff4c10a824c08657a94bd9841f1ef57eeef419/ghc >--------------------------------------------------------------- commit 33ff4c10a824c08657a94bd9841f1ef57eeef419 Author: Ben Gamari Date: Mon Jul 4 20:09:07 2016 -0400 Encoding: Attempt at reducing allocations >--------------------------------------------------------------- 33ff4c10a824c08657a94bd9841f1ef57eeef419 compiler/utils/Encoding.hs | 13 +++++++------ 1 file changed, 7 insertions(+), 6 deletions(-) diff --git a/compiler/utils/Encoding.hs b/compiler/utils/Encoding.hs index d959671..6028397 100644 --- a/compiler/utils/Encoding.hs +++ b/compiler/utils/Encoding.hs @@ -115,17 +115,18 @@ utf8CharStart p = go p else return p utf8DecodeStringLazy :: BS.ByteString -> IO [Char] -utf8DecodeStringLazy bs - = unpack bs +utf8DecodeStringLazy !bs + = unpack 0 where - unpack bs - | BS.null bs = return [] + unpack !offset + | BS.null bs' = return [] | otherwise = - BS.unsafeUseAsCString bs $ \ptr -> + BS.unsafeUseAsCString bs' $ \ptr -> case utf8DecodeChar (castPtr ptr) of (c, nBytes) -> do - chs <- unsafeInterleaveIO $ unpack (BS.drop nBytes bs) + chs <- unsafeInterleaveIO $ unpack (offset + nBytes) return (c : chs) + where !bs' = BS.drop offset bs utf8DecodeString :: Ptr Word8 -> Int -> IO [Char] utf8DecodeString ptr len From git at git.haskell.org Tue Jul 5 07:48:15 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 5 Jul 2016 07:48:15 +0000 (UTC) Subject: [commit: ghc] wip/T12357: Try fusing away unpackFS (6a317ee) Message-ID: <20160705074815.B449A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T12357 Link : http://ghc.haskell.org/trac/ghc/changeset/6a317ee95b04e3fdb4b4be6f710221aeb20d4ee9/ghc >--------------------------------------------------------------- commit 6a317ee95b04e3fdb4b4be6f710221aeb20d4ee9 Author: Ben Gamari Date: Mon Jul 4 20:19:41 2016 -0400 Try fusing away unpackFS >--------------------------------------------------------------- 6a317ee95b04e3fdb4b4be6f710221aeb20d4ee9 compiler/utils/Encoding.hs | 17 ++++++++--------- compiler/utils/FastString.hs | 3 ++- 2 files changed, 10 insertions(+), 10 deletions(-) diff --git a/compiler/utils/Encoding.hs b/compiler/utils/Encoding.hs index 6028397..8da8831 100644 --- a/compiler/utils/Encoding.hs +++ b/compiler/utils/Encoding.hs @@ -35,7 +35,7 @@ import Numeric import ExtsCompat46 import qualified Data.ByteString as BS import qualified Data.ByteString.Unsafe as BS -import System.IO.Unsafe ( unsafeInterleaveIO ) +import System.IO.Unsafe ( unsafePerformIO ) -- ----------------------------------------------------------------------------- -- UTF-8 @@ -114,19 +114,18 @@ utf8CharStart p = go p then go (p `plusPtr` (-1)) else return p -utf8DecodeStringLazy :: BS.ByteString -> IO [Char] +utf8DecodeStringLazy :: BS.ByteString -> [Char] utf8DecodeStringLazy !bs - = unpack 0 + = build (unpack 0) where - unpack !offset - | BS.null bs' = return [] + unpack !offset cons nil + | BS.null bs' = nil | otherwise = - BS.unsafeUseAsCString bs' $ \ptr -> + unsafePerformIO $ BS.unsafeUseAsCString bs' $ \ptr -> case utf8DecodeChar (castPtr ptr) of - (c, nBytes) -> do - chs <- unsafeInterleaveIO $ unpack (offset + nBytes) - return (c : chs) + (c, nBytes) -> return $ c `cons` unpack (offset + nBytes) cons nil where !bs' = BS.drop offset bs +{-# INLINEABLE utf8DecodeStringLazy #-} utf8DecodeString :: Ptr Word8 -> Int -> IO [Char] utf8DecodeString ptr len diff --git a/compiler/utils/FastString.hs b/compiler/utils/FastString.hs index 21cbfeb..32330f2 100644 --- a/compiler/utils/FastString.hs +++ b/compiler/utils/FastString.hs @@ -482,7 +482,8 @@ nullFS f = BS.null (fs_bs f) -- | Unpacks and decodes the FastString unpackFS :: FastString -> String -unpackFS (FastString _ _ bs _) = inlinePerformIO $ utf8DecodeStringLazy bs +unpackFS (FastString _ _ bs _) = utf8DecodeStringLazy bs +{-# INLINEABLE unpackFS #-} -- | Gives the UTF-8 encoded bytes corresponding to a 'FastString' bytesFS :: FastString -> [Word8] From git at git.haskell.org Tue Jul 5 07:48:18 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 5 Jul 2016 07:48:18 +0000 (UTC) Subject: [commit: ghc] wip/T12357: FastString: Reduce allocations of concatFS (e3db922) Message-ID: <20160705074818.5CA0E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T12357 Link : http://ghc.haskell.org/trac/ghc/changeset/e3db922012d73a29e6574e35b2e20f7285f4c550/ghc >--------------------------------------------------------------- commit e3db922012d73a29e6574e35b2e20f7285f4c550 Author: Ben Gamari Date: Mon Jul 4 20:33:57 2016 -0400 FastString: Reduce allocations of concatFS Instead of unpacking and then repacking we simply concatenate all of the individual ByteStrings. >--------------------------------------------------------------- e3db922012d73a29e6574e35b2e20f7285f4c550 compiler/utils/FastString.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/utils/FastString.hs b/compiler/utils/FastString.hs index 32330f2..f58a5b5 100644 --- a/compiler/utils/FastString.hs +++ b/compiler/utils/FastString.hs @@ -512,7 +512,7 @@ appendFS fs1 fs2 = mkFastStringByteString (fastStringToByteString fs2) concatFS :: [FastString] -> FastString -concatFS ls = mkFastString (Prelude.concat (map unpackFS ls)) -- ToDo: do better +concatFS = mkFastStringByteString . BS.concat . map fs_bs headFS :: FastString -> Char headFS (FastString _ 0 _ _) = panic "headFS: Empty FastString" From git at git.haskell.org Tue Jul 5 07:48:21 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 5 Jul 2016 07:48:21 +0000 (UTC) Subject: [commit: ghc] wip/T12357: TysWiredIn: Use map lookup for built-in OccNames (3f45691) Message-ID: <20160705074821.06AB03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T12357 Link : http://ghc.haskell.org/trac/ghc/changeset/3f45691eadd7254eb23baa625beb4a0d8216f858/ghc >--------------------------------------------------------------- commit 3f45691eadd7254eb23baa625beb4a0d8216f858 Author: Ben Gamari Date: Mon Jul 4 21:09:55 2016 -0400 TysWiredIn: Use map lookup for built-in OccNames >--------------------------------------------------------------- 3f45691eadd7254eb23baa625beb4a0d8216f858 compiler/prelude/TysWiredIn.hs | 52 ++++++++++++++++++++---------------------- 1 file changed, 25 insertions(+), 27 deletions(-) diff --git a/compiler/prelude/TysWiredIn.hs b/compiler/prelude/TysWiredIn.hs index 5ab8654..abec6ff 100644 --- a/compiler/prelude/TysWiredIn.hs +++ b/compiler/prelude/TysWiredIn.hs @@ -95,6 +95,7 @@ import TyCon import Class ( Class, mkClass ) import TypeRep import RdrName +import UniqFM import Name import NameSet ( NameSet, mkNameSet, elemNameSet ) import BasicTypes ( Arity, RecFlag(..), Boxity(..), @@ -364,39 +365,36 @@ Note [How tuples work] See also Note [Known-key names] in PrelNames are not serialised into interface files using OccNames at all. -} -isBuiltInOcc_maybe :: OccName -> Maybe Name --- Built in syntax isn't "in scope" so these OccNames --- map to wired-in Names with BuiltInSyntax -isBuiltInOcc_maybe occ - = case occNameString occ of - "[]" -> choose_ns listTyConName nilDataConName - ":" -> Just consDataConName - "[::]" -> Just parrTyConName - "()" -> tup_name Boxed 0 - "(##)" -> tup_name Unboxed 0 - '(':',':rest -> parse_tuple Boxed 2 rest - '(':'#':',':rest -> parse_tuple Unboxed 2 rest - _other -> Nothing +builtInOccNames :: UniqFM (OccName -> Name) +builtInOccNames = listToUFM $ + [ (fsLit "[]", choose_ns listTyConName nilDataConName) + , (fsLit ":" , const consDataConName) + , (fsLit "[::]", const parrTyConName) + , (fsLit "()", tup_name Boxed 0) + , (fsLit "(##)", tup_name Unboxed 0) + ] ++ + [ (fsLit $ "("++replicate n ','++")", tup_name Boxed (n+1)) | n <- [1..62] ] ++ + [ (fsLit $ "(#"++replicate n ','++"#)", tup_name Unboxed (n+1)) | n <- [1..62] ] where - ns = occNameSpace occ - - parse_tuple sort n rest - | (',' : rest2) <- rest = parse_tuple sort (n+1) rest2 - | tail_matches sort rest = tup_name sort n - | otherwise = Nothing - - tail_matches Boxed ")" = True - tail_matches Unboxed "#)" = True - tail_matches _ _ = False + choose_ns :: Name -> Name -> OccName -> Name + choose_ns tc dc occ + | isTcClsNameSpace ns = tc + | isDataConNameSpace ns = dc + | otherwise = pprPanic "tup_name" (ppr occ) + where ns = occNameSpace occ tup_name boxity arity = choose_ns (getName (tupleTyCon boxity arity)) (getName (tupleDataCon boxity arity)) - choose_ns tc dc - | isTcClsNameSpace ns = Just tc - | isDataConNameSpace ns = Just dc - | otherwise = pprPanic "tup_name" (ppr occ) + +isBuiltInOcc_maybe :: OccName -> Maybe Name +-- Built in syntax isn't "in scope" so these OccNames +-- map to wired-in Names with BuiltInSyntax +isBuiltInOcc_maybe occ + = case lookupUFM builtInOccNames occ of + Just f -> Just (f occ) + Nothing -> Nothing mkTupleOcc :: NameSpace -> Boxity -> Arity -> OccName mkTupleOcc ns sort ar = mkOccName ns str From git at git.haskell.org Tue Jul 5 07:48:23 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 5 Jul 2016 07:48:23 +0000 (UTC) Subject: [commit: ghc] wip/T12357: FastString: Add unpackFSLazy (11f802e) Message-ID: <20160705074823.AB0113A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T12357 Link : http://ghc.haskell.org/trac/ghc/changeset/11f802e20c674f5d19b68e95e79cadd2ff1ab600/ghc >--------------------------------------------------------------- commit 11f802e20c674f5d19b68e95e79cadd2ff1ab600 Author: Ben Gamari Date: Mon Jul 4 21:13:32 2016 -0400 FastString: Add unpackFSLazy >--------------------------------------------------------------- 11f802e20c674f5d19b68e95e79cadd2ff1ab600 compiler/utils/FastString.hs | 8 +++++++- 1 file changed, 7 insertions(+), 1 deletion(-) diff --git a/compiler/utils/FastString.hs b/compiler/utils/FastString.hs index f58a5b5..7f29eee 100644 --- a/compiler/utils/FastString.hs +++ b/compiler/utils/FastString.hs @@ -52,6 +52,7 @@ module FastString -- ** Deconstruction unpackFS, -- :: FastString -> String + unpackFSLazy, -- :: FastString -> String bytesFS, -- :: FastString -> [Word8] -- ** Encoding @@ -482,7 +483,12 @@ nullFS f = BS.null (fs_bs f) -- | Unpacks and decodes the FastString unpackFS :: FastString -> String -unpackFS (FastString _ _ bs _) = utf8DecodeStringLazy bs +unpackFS (FastString _ _ bs _) = + inlinePerformIO $ BS.unsafeUseAsCStringLen bs $ \(ptr, len) -> + utf8DecodeString (castPtr ptr) len + +unpackFSLazy :: FastString -> String +unpackFSLazy (FastString _ _ bs _) = utf8DecodeStringLazy bs {-# INLINEABLE unpackFS #-} -- | Gives the UTF-8 encoded bytes corresponding to a 'FastString' From git at git.haskell.org Tue Jul 5 07:48:26 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 5 Jul 2016 07:48:26 +0000 (UTC) Subject: [commit: ghc] wip/T12357: Revert "FastString: Reduce allocations of concatFS" (cdd1889) Message-ID: <20160705074826.56CD03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T12357 Link : http://ghc.haskell.org/trac/ghc/changeset/cdd1889903b6dd453acddeb1f9a741e21a4c5e51/ghc >--------------------------------------------------------------- commit cdd1889903b6dd453acddeb1f9a741e21a4c5e51 Author: Ben Gamari Date: Mon Jul 4 21:13:42 2016 -0400 Revert "FastString: Reduce allocations of concatFS" This reverts commit e3db922012d73a29e6574e35b2e20f7285f4c550. This didn't seem to help, need to work out why. >--------------------------------------------------------------- cdd1889903b6dd453acddeb1f9a741e21a4c5e51 compiler/utils/FastString.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/utils/FastString.hs b/compiler/utils/FastString.hs index 7f29eee..211d503 100644 --- a/compiler/utils/FastString.hs +++ b/compiler/utils/FastString.hs @@ -518,7 +518,7 @@ appendFS fs1 fs2 = mkFastStringByteString (fastStringToByteString fs2) concatFS :: [FastString] -> FastString -concatFS = mkFastStringByteString . BS.concat . map fs_bs +concatFS ls = mkFastString (Prelude.concat (map unpackFS ls)) -- ToDo: do better headFS :: FastString -> Char headFS (FastString _ 0 _ _) = panic "headFS: Empty FastString" From git at git.haskell.org Tue Jul 5 07:48:28 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 5 Jul 2016 07:48:28 +0000 (UTC) Subject: [commit: ghc] wip/T12357: Add SCC on builtInOccNames map (d3a8db6) Message-ID: <20160705074828.EF9013A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T12357 Link : http://ghc.haskell.org/trac/ghc/changeset/d3a8db6e7a20e8ea3b80c67c8cdfc31ea761d684/ghc >--------------------------------------------------------------- commit d3a8db6e7a20e8ea3b80c67c8cdfc31ea761d684 Author: Ben Gamari Date: Mon Jul 4 21:24:34 2016 -0400 Add SCC on builtInOccNames map >--------------------------------------------------------------- d3a8db6e7a20e8ea3b80c67c8cdfc31ea761d684 compiler/prelude/TysWiredIn.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/prelude/TysWiredIn.hs b/compiler/prelude/TysWiredIn.hs index abec6ff..86c942d 100644 --- a/compiler/prelude/TysWiredIn.hs +++ b/compiler/prelude/TysWiredIn.hs @@ -366,7 +366,7 @@ Note [How tuples work] See also Note [Known-key names] in PrelNames -} builtInOccNames :: UniqFM (OccName -> Name) -builtInOccNames = listToUFM $ +builtInOccNames = {-# SCC builtInOccNames #-}listToUFM $ [ (fsLit "[]", choose_ns listTyConName nilDataConName) , (fsLit ":" , const consDataConName) , (fsLit "[::]", const parrTyConName) From git at git.haskell.org Tue Jul 5 07:49:31 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 5 Jul 2016 07:49:31 +0000 (UTC) Subject: [commit: ghc] branch 'wip/T12357' deleted Message-ID: <20160705074931.725283A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Deleted branch: wip/T12357 From git at git.haskell.org Tue Jul 5 07:52:35 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 5 Jul 2016 07:52:35 +0000 (UTC) Subject: [commit: ghc] branch 'wip/T12357-concat' created Message-ID: <20160705075235.71D743A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/T12357-concat Referencing: 84b135695d79c2c416b7746ebad8f39f9d2ab57e From git at git.haskell.org Tue Jul 5 07:52:38 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 5 Jul 2016 07:52:38 +0000 (UTC) Subject: [commit: ghc] wip/T12357-concat: FastString: Reduce allocations of concatFS (84b1356) Message-ID: <20160705075238.2201F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T12357-concat Link : http://ghc.haskell.org/trac/ghc/changeset/84b135695d79c2c416b7746ebad8f39f9d2ab57e/ghc >--------------------------------------------------------------- commit 84b135695d79c2c416b7746ebad8f39f9d2ab57e Author: Ben Gamari Date: Mon Jul 4 20:33:57 2016 -0400 FastString: Reduce allocations of concatFS Instead of unpacking and then repacking we simply concatenate all of the individual ByteStrings. >--------------------------------------------------------------- 84b135695d79c2c416b7746ebad8f39f9d2ab57e compiler/utils/FastString.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/utils/FastString.hs b/compiler/utils/FastString.hs index 40c3882..407c185 100644 --- a/compiler/utils/FastString.hs +++ b/compiler/utils/FastString.hs @@ -513,7 +513,7 @@ appendFS fs1 fs2 = mkFastStringByteString (fastStringToByteString fs2) concatFS :: [FastString] -> FastString -concatFS ls = mkFastString (Prelude.concat (map unpackFS ls)) -- ToDo: do better +concatFS = mkFastStringByteString . BS.concat . map fs_bs headFS :: FastString -> Char headFS (FastString _ 0 _ _) = panic "headFS: Empty FastString" From git at git.haskell.org Tue Jul 5 08:00:11 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 5 Jul 2016 08:00:11 +0000 (UTC) Subject: [commit: ghc] branch 'wip/T12357-unpack' created Message-ID: <20160705080011.E5EA63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/T12357-unpack Referencing: 6a317ee95b04e3fdb4b4be6f710221aeb20d4ee9 From git at git.haskell.org Tue Jul 5 08:00:14 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 5 Jul 2016 08:00:14 +0000 (UTC) Subject: [commit: ghc] wip/T12357-unpack: FastString: Lazily unpack strings (c003779) Message-ID: <20160705080014.922633A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T12357-unpack Link : http://ghc.haskell.org/trac/ghc/changeset/c0037797a5e0e8a42b70cdd077d20b22b2e19d7e/ghc >--------------------------------------------------------------- commit c0037797a5e0e8a42b70cdd077d20b22b2e19d7e Author: Ben Gamari Date: Mon Jul 4 19:58:06 2016 -0400 FastString: Lazily unpack strings Previously we would eagerly build a [Char] of the full string contents, resulting in unnecessarily high allocations in cases where only a short bit at the beginning of the string is called for. See #12357 for motivation. >--------------------------------------------------------------- c0037797a5e0e8a42b70cdd077d20b22b2e19d7e compiler/utils/Encoding.hs | 17 +++++++++++++++++ compiler/utils/FastString.hs | 4 +--- 2 files changed, 18 insertions(+), 3 deletions(-) diff --git a/compiler/utils/Encoding.hs b/compiler/utils/Encoding.hs index ae727d2..d959671 100644 --- a/compiler/utils/Encoding.hs +++ b/compiler/utils/Encoding.hs @@ -18,6 +18,7 @@ module Encoding ( utf8CharStart, utf8DecodeChar, utf8DecodeString, + utf8DecodeStringLazy, utf8EncodeChar, utf8EncodeString, utf8EncodedLength, @@ -32,6 +33,9 @@ import Foreign import Data.Char import Numeric import ExtsCompat46 +import qualified Data.ByteString as BS +import qualified Data.ByteString.Unsafe as BS +import System.IO.Unsafe ( unsafeInterleaveIO ) -- ----------------------------------------------------------------------------- -- UTF-8 @@ -110,6 +114,19 @@ utf8CharStart p = go p then go (p `plusPtr` (-1)) else return p +utf8DecodeStringLazy :: BS.ByteString -> IO [Char] +utf8DecodeStringLazy bs + = unpack bs + where + unpack bs + | BS.null bs = return [] + | otherwise = + BS.unsafeUseAsCString bs $ \ptr -> + case utf8DecodeChar (castPtr ptr) of + (c, nBytes) -> do + chs <- unsafeInterleaveIO $ unpack (BS.drop nBytes bs) + return (c : chs) + utf8DecodeString :: Ptr Word8 -> Int -> IO [Char] utf8DecodeString ptr len = unpack ptr diff --git a/compiler/utils/FastString.hs b/compiler/utils/FastString.hs index 40c3882..21cbfeb 100644 --- a/compiler/utils/FastString.hs +++ b/compiler/utils/FastString.hs @@ -482,9 +482,7 @@ nullFS f = BS.null (fs_bs f) -- | Unpacks and decodes the FastString unpackFS :: FastString -> String -unpackFS (FastString _ _ bs _) = - inlinePerformIO $ BS.unsafeUseAsCStringLen bs $ \(ptr, len) -> - utf8DecodeString (castPtr ptr) len +unpackFS (FastString _ _ bs _) = inlinePerformIO $ utf8DecodeStringLazy bs -- | Gives the UTF-8 encoded bytes corresponding to a 'FastString' bytesFS :: FastString -> [Word8] From git at git.haskell.org Tue Jul 5 08:00:17 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 5 Jul 2016 08:00:17 +0000 (UTC) Subject: [commit: ghc] wip/T12357-unpack: Encoding: Attempt at reducing allocations (33ff4c1) Message-ID: <20160705080017.41EFE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T12357-unpack Link : http://ghc.haskell.org/trac/ghc/changeset/33ff4c10a824c08657a94bd9841f1ef57eeef419/ghc >--------------------------------------------------------------- commit 33ff4c10a824c08657a94bd9841f1ef57eeef419 Author: Ben Gamari Date: Mon Jul 4 20:09:07 2016 -0400 Encoding: Attempt at reducing allocations >--------------------------------------------------------------- 33ff4c10a824c08657a94bd9841f1ef57eeef419 compiler/utils/Encoding.hs | 13 +++++++------ 1 file changed, 7 insertions(+), 6 deletions(-) diff --git a/compiler/utils/Encoding.hs b/compiler/utils/Encoding.hs index d959671..6028397 100644 --- a/compiler/utils/Encoding.hs +++ b/compiler/utils/Encoding.hs @@ -115,17 +115,18 @@ utf8CharStart p = go p else return p utf8DecodeStringLazy :: BS.ByteString -> IO [Char] -utf8DecodeStringLazy bs - = unpack bs +utf8DecodeStringLazy !bs + = unpack 0 where - unpack bs - | BS.null bs = return [] + unpack !offset + | BS.null bs' = return [] | otherwise = - BS.unsafeUseAsCString bs $ \ptr -> + BS.unsafeUseAsCString bs' $ \ptr -> case utf8DecodeChar (castPtr ptr) of (c, nBytes) -> do - chs <- unsafeInterleaveIO $ unpack (BS.drop nBytes bs) + chs <- unsafeInterleaveIO $ unpack (offset + nBytes) return (c : chs) + where !bs' = BS.drop offset bs utf8DecodeString :: Ptr Word8 -> Int -> IO [Char] utf8DecodeString ptr len From git at git.haskell.org Tue Jul 5 08:00:19 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 5 Jul 2016 08:00:19 +0000 (UTC) Subject: [commit: ghc] wip/T12357-unpack: Try fusing away unpackFS (6a317ee) Message-ID: <20160705080019.E5A7C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T12357-unpack Link : http://ghc.haskell.org/trac/ghc/changeset/6a317ee95b04e3fdb4b4be6f710221aeb20d4ee9/ghc >--------------------------------------------------------------- commit 6a317ee95b04e3fdb4b4be6f710221aeb20d4ee9 Author: Ben Gamari Date: Mon Jul 4 20:19:41 2016 -0400 Try fusing away unpackFS >--------------------------------------------------------------- 6a317ee95b04e3fdb4b4be6f710221aeb20d4ee9 compiler/utils/Encoding.hs | 17 ++++++++--------- compiler/utils/FastString.hs | 3 ++- 2 files changed, 10 insertions(+), 10 deletions(-) diff --git a/compiler/utils/Encoding.hs b/compiler/utils/Encoding.hs index 6028397..8da8831 100644 --- a/compiler/utils/Encoding.hs +++ b/compiler/utils/Encoding.hs @@ -35,7 +35,7 @@ import Numeric import ExtsCompat46 import qualified Data.ByteString as BS import qualified Data.ByteString.Unsafe as BS -import System.IO.Unsafe ( unsafeInterleaveIO ) +import System.IO.Unsafe ( unsafePerformIO ) -- ----------------------------------------------------------------------------- -- UTF-8 @@ -114,19 +114,18 @@ utf8CharStart p = go p then go (p `plusPtr` (-1)) else return p -utf8DecodeStringLazy :: BS.ByteString -> IO [Char] +utf8DecodeStringLazy :: BS.ByteString -> [Char] utf8DecodeStringLazy !bs - = unpack 0 + = build (unpack 0) where - unpack !offset - | BS.null bs' = return [] + unpack !offset cons nil + | BS.null bs' = nil | otherwise = - BS.unsafeUseAsCString bs' $ \ptr -> + unsafePerformIO $ BS.unsafeUseAsCString bs' $ \ptr -> case utf8DecodeChar (castPtr ptr) of - (c, nBytes) -> do - chs <- unsafeInterleaveIO $ unpack (offset + nBytes) - return (c : chs) + (c, nBytes) -> return $ c `cons` unpack (offset + nBytes) cons nil where !bs' = BS.drop offset bs +{-# INLINEABLE utf8DecodeStringLazy #-} utf8DecodeString :: Ptr Word8 -> Int -> IO [Char] utf8DecodeString ptr len diff --git a/compiler/utils/FastString.hs b/compiler/utils/FastString.hs index 21cbfeb..32330f2 100644 --- a/compiler/utils/FastString.hs +++ b/compiler/utils/FastString.hs @@ -482,7 +482,8 @@ nullFS f = BS.null (fs_bs f) -- | Unpacks and decodes the FastString unpackFS :: FastString -> String -unpackFS (FastString _ _ bs _) = inlinePerformIO $ utf8DecodeStringLazy bs +unpackFS (FastString _ _ bs _) = utf8DecodeStringLazy bs +{-# INLINEABLE unpackFS #-} -- | Gives the UTF-8 encoded bytes corresponding to a 'FastString' bytesFS :: FastString -> [Word8] From git at git.haskell.org Tue Jul 5 08:00:28 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 5 Jul 2016 08:00:28 +0000 (UTC) Subject: [commit: ghc] branch 'wip/T12357-built-in-map' created Message-ID: <20160705080028.1070E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/T12357-built-in-map Referencing: 1d9ff38e6ef32209f158144ade9e13b82cb410e7 From git at git.haskell.org Tue Jul 5 08:00:30 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 5 Jul 2016 08:00:30 +0000 (UTC) Subject: [commit: ghc] wip/T12357-built-in-map: TysWiredIn: Use map lookup for built-in OccNames (1d9ff38) Message-ID: <20160705080030.C1E883A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T12357-built-in-map Link : http://ghc.haskell.org/trac/ghc/changeset/1d9ff38e6ef32209f158144ade9e13b82cb410e7/ghc >--------------------------------------------------------------- commit 1d9ff38e6ef32209f158144ade9e13b82cb410e7 Author: Ben Gamari Date: Mon Jul 4 21:09:55 2016 -0400 TysWiredIn: Use map lookup for built-in OccNames >--------------------------------------------------------------- 1d9ff38e6ef32209f158144ade9e13b82cb410e7 compiler/prelude/TysWiredIn.hs | 52 ++++++++++++++++++++---------------------- 1 file changed, 25 insertions(+), 27 deletions(-) diff --git a/compiler/prelude/TysWiredIn.hs b/compiler/prelude/TysWiredIn.hs index 5ab8654..abec6ff 100644 --- a/compiler/prelude/TysWiredIn.hs +++ b/compiler/prelude/TysWiredIn.hs @@ -95,6 +95,7 @@ import TyCon import Class ( Class, mkClass ) import TypeRep import RdrName +import UniqFM import Name import NameSet ( NameSet, mkNameSet, elemNameSet ) import BasicTypes ( Arity, RecFlag(..), Boxity(..), @@ -364,39 +365,36 @@ Note [How tuples work] See also Note [Known-key names] in PrelNames are not serialised into interface files using OccNames at all. -} -isBuiltInOcc_maybe :: OccName -> Maybe Name --- Built in syntax isn't "in scope" so these OccNames --- map to wired-in Names with BuiltInSyntax -isBuiltInOcc_maybe occ - = case occNameString occ of - "[]" -> choose_ns listTyConName nilDataConName - ":" -> Just consDataConName - "[::]" -> Just parrTyConName - "()" -> tup_name Boxed 0 - "(##)" -> tup_name Unboxed 0 - '(':',':rest -> parse_tuple Boxed 2 rest - '(':'#':',':rest -> parse_tuple Unboxed 2 rest - _other -> Nothing +builtInOccNames :: UniqFM (OccName -> Name) +builtInOccNames = listToUFM $ + [ (fsLit "[]", choose_ns listTyConName nilDataConName) + , (fsLit ":" , const consDataConName) + , (fsLit "[::]", const parrTyConName) + , (fsLit "()", tup_name Boxed 0) + , (fsLit "(##)", tup_name Unboxed 0) + ] ++ + [ (fsLit $ "("++replicate n ','++")", tup_name Boxed (n+1)) | n <- [1..62] ] ++ + [ (fsLit $ "(#"++replicate n ','++"#)", tup_name Unboxed (n+1)) | n <- [1..62] ] where - ns = occNameSpace occ - - parse_tuple sort n rest - | (',' : rest2) <- rest = parse_tuple sort (n+1) rest2 - | tail_matches sort rest = tup_name sort n - | otherwise = Nothing - - tail_matches Boxed ")" = True - tail_matches Unboxed "#)" = True - tail_matches _ _ = False + choose_ns :: Name -> Name -> OccName -> Name + choose_ns tc dc occ + | isTcClsNameSpace ns = tc + | isDataConNameSpace ns = dc + | otherwise = pprPanic "tup_name" (ppr occ) + where ns = occNameSpace occ tup_name boxity arity = choose_ns (getName (tupleTyCon boxity arity)) (getName (tupleDataCon boxity arity)) - choose_ns tc dc - | isTcClsNameSpace ns = Just tc - | isDataConNameSpace ns = Just dc - | otherwise = pprPanic "tup_name" (ppr occ) + +isBuiltInOcc_maybe :: OccName -> Maybe Name +-- Built in syntax isn't "in scope" so these OccNames +-- map to wired-in Names with BuiltInSyntax +isBuiltInOcc_maybe occ + = case lookupUFM builtInOccNames occ of + Just f -> Just (f occ) + Nothing -> Nothing mkTupleOcc :: NameSpace -> Boxity -> Arity -> OccName mkTupleOcc ns sort ar = mkOccName ns str From git at git.haskell.org Tue Jul 5 08:25:27 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 5 Jul 2016 08:25:27 +0000 (UTC) Subject: [commit: ghc] branch 'wip/T12364' created Message-ID: <20160705082527.E35563A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/T12364 Referencing: 1c24ab8add3ac4d47eba2c5efeeaaf3d282e15b3 From git at git.haskell.org Tue Jul 5 08:25:29 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 5 Jul 2016 08:25:29 +0000 (UTC) Subject: [commit: ghc] branch 'wip/T12354' deleted Message-ID: <20160705082529.E46803A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Deleted branch: wip/T12354 From git at git.haskell.org Tue Jul 5 08:29:37 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 5 Jul 2016 08:29:37 +0000 (UTC) Subject: [commit: ghc] wip/T12364: Do not optimize UData [[Abs], [Abs]] to UHead (83995cb) Message-ID: <20160705082937.D9C693A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T12364 Link : http://ghc.haskell.org/trac/ghc/changeset/83995cb2e1d0e7125cb10d4202ad26da6541a042/ghc >--------------------------------------------------------------- commit 83995cb2e1d0e7125cb10d4202ad26da6541a042 Author: Joachim Breitner Date: Tue Jul 5 10:33:09 2016 +0200 Do not optimize UData [[Abs],[Abs]] to UHead as the "constructor tag" is, in a way, a used component. >--------------------------------------------------------------- 83995cb2e1d0e7125cb10d4202ad26da6541a042 compiler/basicTypes/Demand.hs | 9 ++++++--- 1 file changed, 6 insertions(+), 3 deletions(-) diff --git a/compiler/basicTypes/Demand.hs b/compiler/basicTypes/Demand.hs index 07fb39a..3ee02f1 100644 --- a/compiler/basicTypes/Demand.hs +++ b/compiler/basicTypes/Demand.hs @@ -389,9 +389,12 @@ mkUCall :: Count -> UseDmd -> UseDmd mkUCall c a = UCall c a mkUData :: [[ArgUse]] -> UseDmd -mkUData ux - | all (all (== Abs)) ux = UHead - | otherwise = UData ux +mkUData [ux] | all (== Abs) ux = UHead + -- Sum types are not UHead (which is assumed to be the demand type of a seq), + -- As although the components may possibly not be used, the information _which_ + -- constructor is used is important. +mkUData uss | all null uss = Used +mkUData uss = UData uss lubCount :: Count -> Count -> Count lubCount _ Many = Many From git at git.haskell.org Tue Jul 5 10:12:12 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 5 Jul 2016 10:12:12 +0000 (UTC) Subject: [commit: ghc] branch 'wip/T12357' created Message-ID: <20160705101212.4B4663A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/T12357 Referencing: 40d994105a27cc7c1e680bdecadc3dc12ed6c24e From git at git.haskell.org Tue Jul 5 10:12:15 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 5 Jul 2016 10:12:15 +0000 (UTC) Subject: [commit: ghc] wip/T12357: FastString: Add IsString instance (bb98a13) Message-ID: <20160705101215.158193A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T12357 Link : http://ghc.haskell.org/trac/ghc/changeset/bb98a13329850eaa48f1cfb90d54ada5337062a4/ghc >--------------------------------------------------------------- commit bb98a13329850eaa48f1cfb90d54ada5337062a4 Author: Ben Gamari Date: Tue Jul 5 06:06:29 2016 -0400 FastString: Add IsString instance >--------------------------------------------------------------- bb98a13329850eaa48f1cfb90d54ada5337062a4 compiler/utils/FastString.hs | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/compiler/utils/FastString.hs b/compiler/utils/FastString.hs index 407c185..2031b16 100644 --- a/compiler/utils/FastString.hs +++ b/compiler/utils/FastString.hs @@ -109,6 +109,7 @@ import ExtsCompat46 import System.IO import System.IO.Unsafe ( unsafePerformIO ) import Data.Data +import Data.String import Data.IORef ( IORef, newIORef, readIORef, atomicModifyIORef' ) import Data.Maybe ( isJust ) import Data.Char @@ -197,6 +198,9 @@ instance Ord FastString where | otherwise = y compare a b = cmpFS a b +instance IsString FastString where + fromString = fsLit + instance Show FastString where show fs = show (unpackFS fs) From git at git.haskell.org Tue Jul 5 10:12:17 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 5 Jul 2016 10:12:17 +0000 (UTC) Subject: [commit: ghc] wip/T12357: FastString: Reduce allocations of concatFS (78339b0) Message-ID: <20160705101217.B133A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T12357 Link : http://ghc.haskell.org/trac/ghc/changeset/78339b06f9ac8ae56e4b8fe11c54bc3a5c81362f/ghc >--------------------------------------------------------------- commit 78339b06f9ac8ae56e4b8fe11c54bc3a5c81362f Author: Ben Gamari Date: Mon Jul 4 20:33:57 2016 -0400 FastString: Reduce allocations of concatFS Instead of unpacking and then repacking we simply concatenate all of the individual ByteStrings. >--------------------------------------------------------------- 78339b06f9ac8ae56e4b8fe11c54bc3a5c81362f compiler/utils/FastString.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/utils/FastString.hs b/compiler/utils/FastString.hs index 40c3882..407c185 100644 --- a/compiler/utils/FastString.hs +++ b/compiler/utils/FastString.hs @@ -513,7 +513,7 @@ appendFS fs1 fs2 = mkFastStringByteString (fastStringToByteString fs2) concatFS :: [FastString] -> FastString -concatFS ls = mkFastString (Prelude.concat (map unpackFS ls)) -- ToDo: do better +concatFS = mkFastStringByteString . BS.concat . map fs_bs headFS :: FastString -> Char headFS (FastString _ 0 _ _) = panic "headFS: Empty FastString" From git at git.haskell.org Tue Jul 5 10:12:20 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 5 Jul 2016 10:12:20 +0000 (UTC) Subject: [commit: ghc] wip/T12357: OccName: Avoid re-encoding OccNames (40d9941) Message-ID: <20160705101220.5F0F03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T12357 Link : http://ghc.haskell.org/trac/ghc/changeset/40d994105a27cc7c1e680bdecadc3dc12ed6c24e/ghc >--------------------------------------------------------------- commit 40d994105a27cc7c1e680bdecadc3dc12ed6c24e Author: Ben Gamari Date: Tue Jul 5 05:27:57 2016 -0400 OccName: Avoid re-encoding OccNames Previously we would form derived OccNames by first decoding the name being derived from, manipulating it in [Char] form, and then re-encoding. This is all very wasteful as we essentially always just want to concatenate. >--------------------------------------------------------------- 40d994105a27cc7c1e680bdecadc3dc12ed6c24e compiler/basicTypes/OccName.hs | 34 ++++++++++++++++++---------------- 1 file changed, 18 insertions(+), 16 deletions(-) diff --git a/compiler/basicTypes/OccName.hs b/compiler/basicTypes/OccName.hs index c3f0c9f..394c2b2 100644 --- a/compiler/basicTypes/OccName.hs +++ b/compiler/basicTypes/OccName.hs @@ -3,7 +3,9 @@ (c) The GRASP/AQUA Project, Glasgow University, 1992-1998 -} -{-# LANGUAGE DeriveDataTypeable, BangPatterns #-} +{-# LANGUAGE DeriveDataTypeable #-} +{-# LANGUAGE BangPatterns #-} +{-# LANGUAGE OverloadedStrings #-} -- | -- #name_types# @@ -585,11 +587,12 @@ NB: The string must already be encoded! -} mk_deriv :: NameSpace - -> String -- Distinguishes one sort of derived name from another - -> String + -> FastString -- ^ A prefix which distinguishes one sort of derived name + -- from another + -> [FastString] -- ^ The name we are deriving from in pieces which will + -- be concatenated -> OccName - -mk_deriv occ_sp sys_prefix str = mkOccName occ_sp (sys_prefix ++ str) +mk_deriv occ_sp sys_prefix str = mkOccNameFS occ_sp (concatFS $ sys_prefix : str) isDerivedOccName :: OccName -> Bool isDerivedOccName occ = @@ -642,11 +645,10 @@ mkGenOcc2 = mk_simple_deriv varName "$gto" mkGenD = mk_simple_deriv tcName "D1" mkGenC :: OccName -> Int -> OccName -mkGenC occ m = mk_deriv tcName ("C1_" ++ show m) (occNameString occ) +mkGenC occ m = mk_deriv tcName "C1_" [fsLit (show m), occNameFS occ] mkGenS :: OccName -> Int -> Int -> OccName -mkGenS occ m n = mk_deriv tcName ("S1_" ++ show m ++ "_" ++ show n) - (occNameString occ) +mkGenS occ m n = mk_deriv tcName "S1_" [fsLit (show m), "_", fsLit (show n), occNameFS occ] mkGenR = mk_simple_deriv tcName "Rep_" mkGen1R = mk_simple_deriv tcName "Rep1_" @@ -675,12 +677,12 @@ mkPDatasTyConOcc = mk_simple_deriv_with tcName "VPs:" mkPDataDataConOcc = mk_simple_deriv_with dataName "VPD:" mkPDatasDataConOcc = mk_simple_deriv_with dataName "VPDs:" -mk_simple_deriv :: NameSpace -> String -> OccName -> OccName -mk_simple_deriv sp px occ = mk_deriv sp px (occNameString occ) +mk_simple_deriv :: NameSpace -> FastString -> OccName -> OccName +mk_simple_deriv sp px occ = mk_deriv sp px [occNameFS occ] -mk_simple_deriv_with :: NameSpace -> String -> Maybe String -> OccName -> OccName -mk_simple_deriv_with sp px Nothing occ = mk_deriv sp px (occNameString occ) -mk_simple_deriv_with sp px (Just with) occ = mk_deriv sp (px ++ with ++ "_") (occNameString occ) +mk_simple_deriv_with :: NameSpace -> FastString -> Maybe String -> OccName -> OccName +mk_simple_deriv_with sp px Nothing occ = mk_deriv sp px [occNameFS occ] +mk_simple_deriv_with sp px (Just with) occ = mk_deriv sp px [fsLit with, fsLit "_", occNameFS occ] -- Data constructor workers are made by setting the name space -- of the data constructor OccName (which should be a DataName) @@ -689,19 +691,19 @@ mkDataConWorkerOcc datacon_occ = setOccNameSpace varName datacon_occ mkSuperDictAuxOcc :: Int -> OccName -> OccName mkSuperDictAuxOcc index cls_tc_occ - = mk_deriv varName "$cp" (show index ++ occNameString cls_tc_occ) + = mk_deriv varName "$cp" [fsLit $ show index, occNameFS cls_tc_occ] mkSuperDictSelOcc :: Int -- ^ Index of superclass, e.g. 3 -> OccName -- ^ Class, e.g. @Ord@ -> OccName -- ^ Derived 'Occname', e.g. @$p3Ord@ mkSuperDictSelOcc index cls_tc_occ - = mk_deriv varName "$p" (show index ++ occNameString cls_tc_occ) + = mk_deriv varName "$p" [fsLit $ show index, occNameFS cls_tc_occ] mkLocalOcc :: Unique -- ^ Unique to combine with the 'OccName' -> OccName -- ^ Local name, e.g. @sat@ -> OccName -- ^ Nice unique version, e.g. @$L23sat@ mkLocalOcc uniq occ - = mk_deriv varName ("$L" ++ show uniq) (occNameString occ) + = mk_deriv varName "$L" [fsLit $ show uniq, occNameFS occ] -- The Unique might print with characters -- that need encoding (e.g. 'z'!) From git at git.haskell.org Tue Jul 5 11:37:28 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 5 Jul 2016 11:37:28 +0000 (UTC) Subject: [commit: ghc] master: Kill some varEnvElts (e10497b) Message-ID: <20160705113728.32F263A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e10497b9a3622265b88caa60590ed620ff3d33e2/ghc >--------------------------------------------------------------- commit e10497b9a3622265b88caa60590ed620ff3d33e2 Author: Bartosz Nitka Date: Tue Jul 5 03:37:06 2016 -0700 Kill some varEnvElts I was able to hide the nondeterminism in some specialized function, which I believe will be useful in other places. GHC Trac: #4012 >--------------------------------------------------------------- e10497b9a3622265b88caa60590ed620ff3d33e2 compiler/types/TyCoRep.hs | 28 +++++++++++++++++++++------- 1 file changed, 21 insertions(+), 7 deletions(-) diff --git a/compiler/types/TyCoRep.hs b/compiler/types/TyCoRep.hs index d4106c8..08ac9c9 100644 --- a/compiler/types/TyCoRep.hs +++ b/compiler/types/TyCoRep.hs @@ -1427,6 +1427,15 @@ tyCoVarsOfTypes :: [Type] -> TyCoVarSet tyCoVarsOfTypes tys = fvVarSet $ tyCoFVsOfTypes tys -- | Returns free variables of types, including kind variables as +-- a non-deterministic set. For type synonyms it does /not/ expand the +-- synonym. +tyCoVarsOfTypesSet :: TyVarEnv Type -> TyCoVarSet +-- See Note [Free variables of types] +tyCoVarsOfTypesSet tys = fvVarSet $ tyCoFVsOfTypes $ nonDetEltsUFM tys + -- It's OK to use nonDetEltsUFM here because we immediately forget the + -- ordering by returning a set + +-- | Returns free variables of types, including kind variables as -- a deterministic set. For type synonyms it does /not/ expand the -- synonym. tyCoVarsOfTypesDSet :: [Type] -> DTyCoVarSet @@ -1496,6 +1505,11 @@ tyCoFVsOfProv (HoleProv _) fv_cand in_scope acc = emptyFV fv_cand in_scop tyCoVarsOfCos :: [Coercion] -> TyCoVarSet tyCoVarsOfCos cos = fvVarSet $ tyCoFVsOfCos cos +tyCoVarsOfCosSet :: CoVarEnv Coercion -> TyCoVarSet +tyCoVarsOfCosSet cos = fvVarSet $ tyCoFVsOfCos $ nonDetEltsUFM cos + -- It's OK to use nonDetEltsUFM here because we immediately forget the + -- ordering by returning a set + tyCoFVsOfCos :: [Coercion] -> FV tyCoFVsOfCos [] fv_cand in_scope acc = emptyFV fv_cand in_scope acc tyCoFVsOfCos (co:cos) fv_cand in_scope acc = (tyCoFVsOfCo co `unionFV` tyCoFVsOfCos cos) fv_cand in_scope acc @@ -1755,8 +1769,8 @@ getTCvSubstRangeFVs :: TCvSubst -> VarSet getTCvSubstRangeFVs (TCvSubst _ tenv cenv) = unionVarSet tenvFVs cenvFVs where - tenvFVs = tyCoVarsOfTypes $ varEnvElts tenv - cenvFVs = tyCoVarsOfCos $ varEnvElts cenv + tenvFVs = tyCoVarsOfTypesSet tenv + cenvFVs = tyCoVarsOfCosSet cenv isInScope :: Var -> TCvSubst -> Bool isInScope v (TCvSubst in_scope _ _) = v `elemInScopeSet` in_scope @@ -2056,8 +2070,8 @@ isValidTCvSubst (TCvSubst in_scope tenv cenv) = (tenvFVs `varSetInScope` in_scope) && (cenvFVs `varSetInScope` in_scope) where - tenvFVs = tyCoVarsOfTypes $ varEnvElts tenv - cenvFVs = tyCoVarsOfCos $ varEnvElts cenv + tenvFVs = tyCoVarsOfTypesSet tenv + cenvFVs = tyCoVarsOfCosSet cenv -- | This checks if the substitution satisfies the invariant from -- Note [The substitution invariant]. @@ -2071,10 +2085,10 @@ checkValidSubst subst@(TCvSubst in_scope tenv cenv) tys cos a text "in_scope" <+> ppr in_scope $$ text "tenv" <+> ppr tenv $$ text "tenvFVs" - <+> ppr (tyCoVarsOfTypes $ varEnvElts tenv) $$ + <+> ppr (tyCoVarsOfTypesSet tenv) $$ text "cenv" <+> ppr cenv $$ text "cenvFVs" - <+> ppr (tyCoVarsOfCos $ varEnvElts cenv) $$ + <+> ppr (tyCoVarsOfCosSet cenv) $$ text "tys" <+> ppr tys $$ text "cos" <+> ppr cos ) ASSERT2( tysCosFVsInScope, @@ -2355,7 +2369,7 @@ substTyVarBndrCallback subst_fn subst@(TCvSubst in_scope tenv cenv) old_var new_env | no_change = delVarEnv tenv old_var | otherwise = extendVarEnv tenv old_var (TyVarTy new_var) - _no_capture = not (new_var `elemVarSet` tyCoVarsOfTypes (varEnvElts tenv)) + _no_capture = not (new_var `elemVarSet` tyCoVarsOfTypesSet tenv) -- Assertion check that we are not capturing something in the substitution old_ki = tyVarKind old_var From git at git.haskell.org Tue Jul 5 12:50:54 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 5 Jul 2016 12:50:54 +0000 (UTC) Subject: [commit: ghc] master: Check generic-default method for ambiguity (85aa6ef) Message-ID: <20160705125054.258CD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/85aa6ef09346e841abf4e089b24c7f783286cd74/ghc >--------------------------------------------------------------- commit 85aa6ef09346e841abf4e089b24c7f783286cd74 Author: Simon Peyton Jones Date: Fri Jul 1 22:33:33 2016 +0100 Check generic-default method for ambiguity Fixes Trac #7497 and #12151. In some earlier upheaval I introduced a bug in the ambiguity check for genreric-default method. This patch fixes it. But in fixing it I realised that the sourc-location of any such error message was bogus, so I fixed that too, which involved a slightly wider change; see the comments with TcMethInfo. >--------------------------------------------------------------- 85aa6ef09346e841abf4e089b24c7f783286cd74 compiler/iface/BuildTyCl.hs | 47 +++++++++++++++++----- compiler/iface/TcIface.hs | 4 +- compiler/typecheck/TcClassDcl.hs | 8 ++-- compiler/typecheck/TcTyClsDecls.hs | 16 +++++--- compiler/typecheck/TcTyDecls.hs | 19 ++++----- compiler/types/Class.hs | 10 +---- compiler/vectorise/Vectorise/Type/TyConDecl.hs | 9 +++++ testsuite/tests/typecheck/should_fail/T12151.hs | 10 +++++ .../tests/typecheck/should_fail/T12151.stderr | 12 ++++++ testsuite/tests/typecheck/should_fail/T7437.hs | 15 +++++++ testsuite/tests/typecheck/should_fail/T7437.stderr | 12 ++++++ testsuite/tests/typecheck/should_fail/all.T | 2 + 12 files changed, 125 insertions(+), 39 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 85aa6ef09346e841abf4e089b24c7f783286cd74 From git at git.haskell.org Tue Jul 5 12:50:56 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 5 Jul 2016 12:50:56 +0000 (UTC) Subject: [commit: ghc] master: Extra ASSERTs for nameModule (1267048) Message-ID: <20160705125056.C27373A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1267048e1785eb4f05834ec56e30107cda4828bd/ghc >--------------------------------------------------------------- commit 1267048e1785eb4f05834ec56e30107cda4828bd Author: Simon Peyton Jones Date: Mon Jul 4 18:34:12 2016 +0100 Extra ASSERTs for nameModule >--------------------------------------------------------------- 1267048e1785eb4f05834ec56e30107cda4828bd compiler/basicTypes/RdrName.hs | 2 +- compiler/main/HscTypes.hs | 3 ++- 2 files changed, 3 insertions(+), 2 deletions(-) diff --git a/compiler/basicTypes/RdrName.hs b/compiler/basicTypes/RdrName.hs index 592ee92..d6a8aa6 100644 --- a/compiler/basicTypes/RdrName.hs +++ b/compiler/basicTypes/RdrName.hs @@ -1142,7 +1142,7 @@ ppr_defn_site imp_spec name 2 (pprLoc loc) where loc = nameSrcSpan name - defining_mod = nameModule name + defining_mod = ASSERT2( isExternalName name, ppr name ) nameModule name same_module = importSpecModule imp_spec == moduleName defining_mod pp_mod | same_module = empty | otherwise = text "in" <+> quotes (ppr defining_mod) diff --git a/compiler/main/HscTypes.hs b/compiler/main/HscTypes.hs index a3352f4..b71e8ae 100644 --- a/compiler/main/HscTypes.hs +++ b/compiler/main/HscTypes.hs @@ -1650,7 +1650,8 @@ mkPrintUnqualified dflags env = QueryQualify qual_name -- Eg f = True; g = 0; f = False where is_name :: Name -> Bool - is_name name = nameModule name == mod && nameOccName name == occ + is_name name = ASSERT2( isExternalName name, ppr name ) + nameModule name == mod && nameOccName name == occ forceUnqualNames :: [Name] forceUnqualNames = From git at git.haskell.org Tue Jul 5 14:17:50 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 5 Jul 2016 14:17:50 +0000 (UTC) Subject: [commit: packages/dph] master: Prepare dph for a vectInfoVar type change (64eca66) Message-ID: <20160705141750.B276E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/dph On branch : master Link : http://git.haskell.org/packages/dph.git/commitdiff/64eca669f13f4d216af9024474a3fc73ce101793 >--------------------------------------------------------------- commit 64eca669f13f4d216af9024474a3fc73ce101793 Author: Bartosz Nitka Date: Tue Jul 5 07:20:23 2016 -0700 Prepare dph for a vectInfoVar type change vectInfoVar uses deterministic sets now, see Note [Deterministic UniqFM] for more details. >--------------------------------------------------------------- 64eca669f13f4d216af9024474a3fc73ce101793 dph-plugin/DPH/Core/Pretty.hs | 4 ++-- dph-plugin/DPH/Pass/Summon.hs | 4 ++-- 2 files changed, 4 insertions(+), 4 deletions(-) diff --git a/dph-plugin/DPH/Core/Pretty.hs b/dph-plugin/DPH/Core/Pretty.hs index 54bcd97..499adc3 100644 --- a/dph-plugin/DPH/Core/Pretty.hs +++ b/dph-plugin/DPH/Core/Pretty.hs @@ -17,7 +17,7 @@ import DataCon import Literal import Id import Unique -import qualified UniqFM as UFM +import qualified UniqDFM as UDFM -- Guts ----------------------------------------------------------------------- pprModGuts :: ModGuts -> Doc @@ -45,7 +45,7 @@ instance Pretty AvailInfo where -- | The VectInfo maps names to their vectorised versions. instance Pretty VectInfo where ppr vi - = ppr $ UFM.eltsUFM (vectInfoVar vi) + = ppr $ UDFM.eltsUDFM (vectInfoVar vi) -- Top Binds ------------------------------------------------------------------ diff --git a/dph-plugin/DPH/Pass/Summon.hs b/dph-plugin/DPH/Pass/Summon.hs index aea1d1a..9645cd6 100644 --- a/dph-plugin/DPH/Pass/Summon.hs +++ b/dph-plugin/DPH/Pass/Summon.hs @@ -21,7 +21,7 @@ import CoreMonad import Avail import Data.Maybe import Data.Set (Set) -import qualified UniqFM as UFM +import qualified UniqDFM as UDFM import qualified Data.Set as Set import Control.Monad import Debug.Trace @@ -35,7 +35,7 @@ passSummon guts let nsExported = [ n | Avail n <- mg_exports guts] let nsExported_vect = catMaybes - $ map (UFM.lookupUFM (vectInfoVar $ mg_vect_info guts)) + $ map (UDFM.lookupUDFM (vectInfoVar $ mg_vect_info guts)) $ nsExported -- Summon all of the vectorised things. From git at git.haskell.org Tue Jul 5 14:29:07 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 5 Jul 2016 14:29:07 +0000 (UTC) Subject: [commit: ghc] master: Use DVarEnv for vectInfoVar (55e43a6) Message-ID: <20160705142907.872923A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/55e43a6f9ef64cf31faca350f8bf86f5f5acb36a/ghc >--------------------------------------------------------------- commit 55e43a6f9ef64cf31faca350f8bf86f5f5acb36a Author: Bartosz Nitka Date: Tue Jul 5 06:23:54 2016 -0700 Use DVarEnv for vectInfoVar This makes sure that we don't introduce unnecessary nondeterminism from vectorization. Also updates dph submodule to reflect the change in types. GHC Trac: #4012 >--------------------------------------------------------------- 55e43a6f9ef64cf31faca350f8bf86f5f5acb36a compiler/basicTypes/VarEnv.hs | 14 ++++++++++++-- compiler/iface/MkIface.hs | 2 +- compiler/iface/TcIface.hs | 2 +- compiler/main/HscTypes.hs | 6 +++--- compiler/main/TidyPgm.hs | 29 ++++++++++++----------------- compiler/simplCore/SimplCore.hs | 4 ++-- compiler/vectorise/Vectorise/Env.hs | 16 +++++++++------- libraries/dph | 2 +- 8 files changed, 41 insertions(+), 34 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 55e43a6f9ef64cf31faca350f8bf86f5f5acb36a From git at git.haskell.org Tue Jul 5 15:20:10 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 5 Jul 2016 15:20:10 +0000 (UTC) Subject: [commit: ghc] master: Tidy up tidying (cbe30fd) Message-ID: <20160705152010.48B533A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/cbe30fda6d7c32415583654c8dfbfb74b1bde999/ghc >--------------------------------------------------------------- commit cbe30fda6d7c32415583654c8dfbfb74b1bde999 Author: Simon Peyton Jones Date: Tue Jul 5 13:49:02 2016 +0100 Tidy up tidying This is a tiny refactor, replacing an ad-hoc local function (TidyPgm.loookup_aux_id) with a solid global one (tidyVarOcc). >--------------------------------------------------------------- cbe30fda6d7c32415583654c8dfbfb74b1bde999 compiler/main/TidyPgm.hs | 10 ++-------- 1 file changed, 2 insertions(+), 8 deletions(-) diff --git a/compiler/main/TidyPgm.hs b/compiler/main/TidyPgm.hs index 915cd12..6ec1e02 100644 --- a/compiler/main/TidyPgm.hs +++ b/compiler/main/TidyPgm.hs @@ -350,7 +350,7 @@ tidyProgram hsc_env (ModGuts { mg_module = mod isExternalName (idName id)] ; type_env1 = extendTypeEnvWithIds type_env final_ids - ; tidy_cls_insts = map (tidyClsInstDFun (lookup_aux_id tidy_type_env)) cls_insts + ; tidy_cls_insts = map (tidyClsInstDFun (tidyVarOcc tidy_env)) cls_insts -- A DFunId will have a binding in tidy_binds, and so will now be in -- tidy_type_env, replete with IdInfo. Its name will be unchanged since -- it was born, but we want Global, IdInfo-rich (or not) DFunId in the @@ -367,7 +367,7 @@ tidyProgram hsc_env (ModGuts { mg_module = mod -- and then override the PatSyns in the type_env with the new tidy ones -- This is really the only reason we keep mg_patsyns at all; otherwise -- they could just stay in type_env - ; tidy_patsyns = map (tidyPatSynIds (lookup_aux_id tidy_type_env)) patsyns + ; tidy_patsyns = map (tidyPatSynIds (tidyVarOcc tidy_env)) patsyns ; type_env2 = extendTypeEnvWithPatSyns tidy_patsyns type_env1 ; tidy_type_env = tidyTypeEnv omit_prags type_env2 @@ -429,12 +429,6 @@ tidyProgram hsc_env (ModGuts { mg_module = mod where dflags = hsc_dflags hsc_env -lookup_aux_id :: TypeEnv -> Var -> Id -lookup_aux_id type_env id - = case lookupTypeEnv type_env (idName id) of - Just (AnId id') -> id' - _other -> pprPanic "lookup_aux_id" (ppr id) - tidyTypeEnv :: Bool -- Compiling without -O, so omit prags -> TypeEnv -> TypeEnv From git at git.haskell.org Tue Jul 5 15:20:13 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 5 Jul 2016 15:20:13 +0000 (UTC) Subject: [commit: ghc] master: Test Trac #12133 (6cedef0) Message-ID: <20160705152013.38ADC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6cedef01e00e95517a546a72592ba6ff07bac605/ghc >--------------------------------------------------------------- commit 6cedef01e00e95517a546a72592ba6ff07bac605 Author: Simon Peyton Jones Date: Tue Jul 5 16:23:01 2016 +0100 Test Trac #12133 >--------------------------------------------------------------- 6cedef01e00e95517a546a72592ba6ff07bac605 testsuite/tests/typecheck/should_compile/T12133.hs | 68 ++++++++++++++++++++++ testsuite/tests/typecheck/should_compile/all.T | 1 + 2 files changed, 69 insertions(+) diff --git a/testsuite/tests/typecheck/should_compile/T12133.hs b/testsuite/tests/typecheck/should_compile/T12133.hs new file mode 100644 index 0000000..f2502a7 --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T12133.hs @@ -0,0 +1,68 @@ +{-# LANGUAGE CPP #-} +{-# LANGUAGE ConstraintKinds #-} +{-# LANGUAGE GADTs #-} +{-# LANGUAGE ImplicitParams #-} +{-# LANGUAGE KindSignatures #-} +{-# LANGUAGE MagicHash #-} +{-# LANGUAGE RankNTypes #-} +{-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE TypeOperators #-} + +module T12133 where + +import GHC.Classes (IP(..)) +import GHC.Exts (Constraint) + +-- | From "Data.Constraint": +data Dict :: Constraint -> * where Dict :: a => Dict a + +newtype a :- b = Sub (a => Dict b) + +infixl 1 \\ -- required comment + +(\\) :: a => (b => r) -> (a :- b) -> r +r \\ Sub Dict = r + +-- | GHC 7.10.2 type checks this function but GHC 8.0.1 does not unless +-- you modify this example in one of the following ways: +-- +-- * uncomments the type signature for 'Sub' +-- +-- * flatten the nested pairs of constraints into a triple of constraints +-- +-- * replace 'IP sym ty' with 'c9', where 'c9' is a new constraint variable. +-- +-- The error message is listed below. +foo :: forall c1 c2 c3 sym ty + . (c1, c2) :- c3 + -> (c1, (IP sym ty, c2)) :- (IP sym ty, c3) +foo sp = ( Sub +-- :: ((c1, (IP sym ty, c2)) => Dict (IP sym ty, c3)) +-- -> (c1, ((IP sym ty), c2)) :- (IP sym ty, c3) + ) + ( (Dict \\ sp) :: Dict (IP sym ty, c3) ) + +{- Compiler error message: + +GHCi, version 8.0.1: http://www.haskell.org/ghc/ :? for help +[1 of 1] Compiling T ( t.hs, interpreted ) + +t.hs:44:13: error: + • Could not deduce: IP sym ty arising from a use of ‘Dict’ + from the context: (c1, (IP sym ty, c2)) + bound by a type expected by the context: + (c1, (IP sym ty, c2)) => Dict (IP sym ty, c3) + at t.hs:(40,10)-(44,49) + or from: c3 + bound by a type expected by the context: + c3 => Dict (IP sym ty, c3) + at t.hs:44:13-22 + • In the first argument of ‘(\\)’, namely ‘Dict’ + In the first argument of ‘Sub’, namely + ‘((Dict \\ sp) :: Dict (IP sym ty, c3))’ + In the expression: (Sub) ((Dict \\ sp) :: Dict (IP sym ty, c3)) + • Relevant bindings include + foo :: (c1, c2) :- c3 -> (c1, (IP sym ty, c2)) :- (IP sym ty, c3) + (bound at t.hs:40:1) +Failed, modules loaded: none. +-} \ No newline at end of file diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index 33d91d1..7333ffb 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -530,3 +530,4 @@ test('T11974', normal, compile, ['']) test('T12067', extra_clean(['T12067a.hi', 'T12067a.o']), multimod_compile, ['T12067', '-v0']) test('T12185', normal, compile, ['']) +test('T12133', normal, compile, ['']) From git at git.haskell.org Tue Jul 5 15:20:15 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 5 Jul 2016 15:20:15 +0000 (UTC) Subject: [commit: ghc] master: White space only (f2d36ea) Message-ID: <20160705152015.D85283A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f2d36ead6e094439a43866160010dac7f1f86ec6/ghc >--------------------------------------------------------------- commit f2d36ead6e094439a43866160010dac7f1f86ec6 Author: Simon Peyton Jones Date: Tue Jul 5 16:22:17 2016 +0100 White space only >--------------------------------------------------------------- f2d36ead6e094439a43866160010dac7f1f86ec6 compiler/basicTypes/BasicTypes.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/basicTypes/BasicTypes.hs b/compiler/basicTypes/BasicTypes.hs index a002207..7fe4cb9 100644 --- a/compiler/basicTypes/BasicTypes.hs +++ b/compiler/basicTypes/BasicTypes.hs @@ -993,11 +993,11 @@ The main effects of CONLIKE are: isConLike :: RuleMatchInfo -> Bool isConLike ConLike = True -isConLike _ = False +isConLike _ = False isFunLike :: RuleMatchInfo -> Bool isFunLike FunLike = True -isFunLike _ = False +isFunLike _ = False isEmptyInlineSpec :: InlineSpec -> Bool isEmptyInlineSpec EmptyInlineSpec = True From git at git.haskell.org Tue Jul 5 15:20:18 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 5 Jul 2016 15:20:18 +0000 (UTC) Subject: [commit: ghc] master: Delete out-of-date comment (5f79394) Message-ID: <20160705152018.828E13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5f79394f628259403edf612ef109d8c0f4d7e67a/ghc >--------------------------------------------------------------- commit 5f79394f628259403edf612ef109d8c0f4d7e67a Author: Simon Peyton Jones Date: Mon Jul 4 15:11:21 2016 +0100 Delete out-of-date comment >--------------------------------------------------------------- 5f79394f628259403edf612ef109d8c0f4d7e67a compiler/basicTypes/RdrName.hs | 3 --- 1 file changed, 3 deletions(-) diff --git a/compiler/basicTypes/RdrName.hs b/compiler/basicTypes/RdrName.hs index d6a8aa6..bfac741 100644 --- a/compiler/basicTypes/RdrName.hs +++ b/compiler/basicTypes/RdrName.hs @@ -323,9 +323,6 @@ instance Ord RdrName where -- It is keyed by OccName, because we never use it for qualified names -- We keep the current mapping, *and* the set of all Names in scope -- Reason: see Note [Splicing Exact names] in RnEnv --- The field lre_nwcs is used to keep names of type variables that should --- be replaced with named wildcards. --- See Note [Renaming named wild cards] in RnTypes data LocalRdrEnv = LRE { lre_env :: OccEnv Name , lre_in_scope :: NameSet } From git at git.haskell.org Tue Jul 5 15:20:21 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 5 Jul 2016 15:20:21 +0000 (UTC) Subject: [commit: ghc] master: Make unique auxiliary function names in deriving (895eefa) Message-ID: <20160705152021.DFD383A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/895eefa8447a2886e77fdedcbca8047263c88db7/ghc >--------------------------------------------------------------- commit 895eefa8447a2886e77fdedcbca8047263c88db7 Author: Simon Peyton Jones Date: Tue Jul 5 13:46:29 2016 +0100 Make unique auxiliary function names in deriving In deriving for Data, we make some auxiliary functions, but they didn't always get distinct names (Trac #12245). This patch fixes it by using the same mechanism as for dictionary functions, namely chooseUniqueOccTc. Some assocated refactoring came along for the ride. >--------------------------------------------------------------- 895eefa8447a2886e77fdedcbca8047263c88db7 compiler/basicTypes/OccName.hs | 21 +-- compiler/typecheck/TcDeriv.hs | 76 ++++------- compiler/typecheck/TcGenDeriv.hs | 151 ++++++++++++++-------- compiler/typecheck/TcGenGenerics.hs | 49 +++---- testsuite/tests/deriving/should_compile/T12245.hs | 12 ++ testsuite/tests/deriving/should_compile/all.T | 2 +- 6 files changed, 168 insertions(+), 143 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 895eefa8447a2886e77fdedcbca8047263c88db7 From git at git.haskell.org Tue Jul 5 16:40:07 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 5 Jul 2016 16:40:07 +0000 (UTC) Subject: [commit: ghc] master: Document codegen nondeterminism (27fc75b) Message-ID: <20160705164007.A22E53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/27fc75b2fea014006964eafe53b3ae17e058d75b/ghc >--------------------------------------------------------------- commit 27fc75b2fea014006964eafe53b3ae17e058d75b Author: Bartosz Nitka Date: Tue Jul 5 09:42:44 2016 -0700 Document codegen nondeterminism We don't care about bit-for-bit reproducibility, so I'm just documenting this as a possible source. GHC Trac: #4012 >--------------------------------------------------------------- 27fc75b2fea014006964eafe53b3ae17e058d75b compiler/stgSyn/CoreToStg.hs | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/compiler/stgSyn/CoreToStg.hs b/compiler/stgSyn/CoreToStg.hs index 273cbdb..2d9ca8c 100644 --- a/compiler/stgSyn/CoreToStg.hs +++ b/compiler/stgSyn/CoreToStg.hs @@ -43,6 +43,7 @@ import DynFlags import ForeignCall import Demand ( isUsedOnce ) import PrimOp ( PrimCall(..) ) +import UniqFM import Data.Maybe (isJust) import Control.Monad (liftM, ap) @@ -1002,7 +1003,10 @@ lookupFVInfo fvs id -- Non-top-level things only, both type variables and ids getFVs :: FreeVarsInfo -> [Var] -getFVs fvs = [id | (id, how_bound, _) <- varEnvElts fvs, +getFVs fvs = [id | (id, how_bound, _) <- nonDetEltsUFM fvs, + -- It's OK to use nonDetEltsUFM here because we're not aiming for + -- bit-for-bit determinism. + -- See Note [Unique Determinism and code generation] not (topLevelBound how_bound) ] getFVSet :: FreeVarsInfo -> VarSet From git at git.haskell.org Tue Jul 5 16:42:04 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 5 Jul 2016 16:42:04 +0000 (UTC) Subject: [commit: ghc] master: Kill varEnvElts in zonkEnvIds (18b782e) Message-ID: <20160705164204.560483A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/18b782e3209764c318da46b378b517749af14685/ghc >--------------------------------------------------------------- commit 18b782e3209764c318da46b378b517749af14685 Author: Bartosz Nitka Date: Tue Jul 5 09:01:34 2016 -0700 Kill varEnvElts in zonkEnvIds This localizes the nondeterminism that varEnvElts could have introduced, so that it's obvious that it's benign. Test Plan: ./validate Reviewers: simonpj, austin, bgamari Subscribers: thomie, simonmar Differential Revision: https://phabricator.haskell.org/D2390 GHC Trac Issues: #4012 >--------------------------------------------------------------- 18b782e3209764c318da46b378b517749af14685 compiler/main/HscTypes.hs | 5 ++++- compiler/typecheck/TcHsSyn.hs | 11 ++++++++--- compiler/typecheck/TcRnDriver.hs | 4 ++-- 3 files changed, 14 insertions(+), 6 deletions(-) diff --git a/compiler/main/HscTypes.hs b/compiler/main/HscTypes.hs index 99c51cd..d297a83 100644 --- a/compiler/main/HscTypes.hs +++ b/compiler/main/HscTypes.hs @@ -87,7 +87,7 @@ module HscTypes ( TypeEnv, lookupType, lookupTypeHscEnv, mkTypeEnv, emptyTypeEnv, typeEnvFromEntities, mkTypeEnvWithImplicits, extendTypeEnv, extendTypeEnvList, - extendTypeEnvWithIds, + extendTypeEnvWithIds, plusTypeEnv, lookupTypeEnv, typeEnvElts, typeEnvTyCons, typeEnvIds, typeEnvPatSyns, typeEnvDataCons, typeEnvCoAxioms, typeEnvClasses, @@ -1941,6 +1941,9 @@ extendTypeEnvWithIds :: TypeEnv -> [Id] -> TypeEnv extendTypeEnvWithIds env ids = extendNameEnvList env [(getName id, AnId id) | id <- ids] +plusTypeEnv :: TypeEnv -> TypeEnv -> TypeEnv +plusTypeEnv env1 env2 = plusNameEnv env1 env2 + -- | Find the 'TyThing' for the given 'Name' by using all the resources -- at our disposal: the compiled modules in the 'HomePackageTable' and the -- compiled modules in other packages that live in 'PackageTypeEnv'. Note diff --git a/compiler/typecheck/TcHsSyn.hs b/compiler/typecheck/TcHsSyn.hs index a50cb4d..ad75033 100644 --- a/compiler/typecheck/TcHsSyn.hs +++ b/compiler/typecheck/TcHsSyn.hs @@ -53,7 +53,9 @@ import TyCon import Coercion import ConLike import DataCon +import HscTypes import Name +import NameEnv import Var import VarSet import VarEnv @@ -256,8 +258,11 @@ setZonkType :: ZonkEnv -> UnboundTyVarZonker -> ZonkEnv setZonkType (ZonkEnv _ ty_env id_env) zonk_ty = ZonkEnv zonk_ty ty_env id_env -zonkEnvIds :: ZonkEnv -> [Id] -zonkEnvIds (ZonkEnv _ _ id_env) = varEnvElts id_env +zonkEnvIds :: ZonkEnv -> TypeEnv +zonkEnvIds (ZonkEnv _ _ id_env) = + mkNameEnv [(getName id, AnId id) | id <- nonDetEltsUFM id_env] + -- It's OK to use nonDetEltsUFM here because we forget the ordering + -- immediately by creating a TypeEnv zonkIdOcc :: ZonkEnv -> TcId -> Id -- Ids defined in this module should be in the envt; @@ -357,7 +362,7 @@ zonkTopLExpr e = zonkLExpr emptyZonkEnv e zonkTopDecls :: Bag EvBind -> LHsBinds TcId -> [LRuleDecl TcId] -> [LVectDecl TcId] -> [LTcSpecPrag] -> [LForeignDecl TcId] - -> TcM ([Id], + -> TcM (TypeEnv, Bag EvBind, LHsBinds Id, [LForeignDecl Id], diff --git a/compiler/typecheck/TcRnDriver.hs b/compiler/typecheck/TcRnDriver.hs index 48b055b..c551356 100644 --- a/compiler/typecheck/TcRnDriver.hs +++ b/compiler/typecheck/TcRnDriver.hs @@ -521,13 +521,13 @@ tcRnSrcDecls explicit_mod_hdr decls tcg_fords = fords } = tcg_env ; all_ev_binds = cur_ev_binds `unionBags` new_ev_binds } ; - ; (bind_ids, ev_binds', binds', fords', imp_specs', rules', vects') + ; (bind_env, ev_binds', binds', fords', imp_specs', rules', vects') <- {-# SCC "zonkTopDecls" #-} zonkTopDecls all_ev_binds binds rules vects imp_specs fords ; ; traceTc "Tc11" empty - ; let { final_type_env = extendTypeEnvWithIds type_env bind_ids + ; let { final_type_env = plusTypeEnv type_env bind_env ; tcg_env' = tcg_env { tcg_binds = binds', tcg_ev_binds = ev_binds', tcg_imp_specs = imp_specs', From git at git.haskell.org Tue Jul 5 16:48:20 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 5 Jul 2016 16:48:20 +0000 (UTC) Subject: [commit: ghc] master: Remove varEnvElts (1b058d4) Message-ID: <20160705164820.F1EE73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1b058d4a0f4b12bf15d186409cfff8a2b93fd3a9/ghc >--------------------------------------------------------------- commit 1b058d4a0f4b12bf15d186409cfff8a2b93fd3a9 Author: Bartosz Nitka Date: Tue Jul 5 09:50:02 2016 -0700 Remove varEnvElts varEnvElts can introduce unnecessary nondeterminism and we can finally remove it, so that no one will use it by accident. If someone wants to use varEnvElts they should either use DVarEnv or use nonDetEltsUFM and document why it doesn't introduce nondeterminism. GHC Trac: #4012 >--------------------------------------------------------------- 1b058d4a0f4b12bf15d186409cfff8a2b93fd3a9 compiler/basicTypes/VarEnv.hs | 4 +--- 1 file changed, 1 insertion(+), 3 deletions(-) diff --git a/compiler/basicTypes/VarEnv.hs b/compiler/basicTypes/VarEnv.hs index 626b5cd..92b6cc7 100644 --- a/compiler/basicTypes/VarEnv.hs +++ b/compiler/basicTypes/VarEnv.hs @@ -9,7 +9,7 @@ module VarEnv ( -- ** Manipulating these environments emptyVarEnv, unitVarEnv, mkVarEnv, mkVarEnv_Directly, - elemVarEnv, varEnvElts, + elemVarEnv, extendVarEnv, extendVarEnv_C, extendVarEnv_Acc, extendVarEnv_Directly, extendVarEnvList, plusVarEnv, plusVarEnv_C, plusVarEnv_CD, alterVarEnv, @@ -437,7 +437,6 @@ plusVarEnv_C :: (a -> a -> a) -> VarEnv a -> VarEnv a -> VarEnv a plusVarEnv_CD :: (a -> a -> a) -> VarEnv a -> a -> VarEnv a -> a -> VarEnv a mapVarEnv :: (a -> b) -> VarEnv a -> VarEnv b modifyVarEnv :: (a -> a) -> VarEnv a -> Var -> VarEnv a -varEnvElts :: VarEnv a -> [a] isEmptyVarEnv :: VarEnv a -> Bool lookupVarEnv :: VarEnv a -> Var -> Maybe a @@ -469,7 +468,6 @@ mapVarEnv = mapUFM mkVarEnv = listToUFM mkVarEnv_Directly= listToUFM_Directly emptyVarEnv = emptyUFM -varEnvElts = eltsUFM unitVarEnv = unitUFM isEmptyVarEnv = isNullUFM lookupVarEnv_Directly = lookupUFM_Directly From git at git.haskell.org Tue Jul 5 20:09:01 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 5 Jul 2016 20:09:01 +0000 (UTC) Subject: [commit: ghc] master: Fix GetTime.c on Darwin with clock_gettime (b7b130c) Message-ID: <20160705200901.E71DC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b7b130c5102948b38aaba723044288e16a80d492/ghc >--------------------------------------------------------------- commit b7b130c5102948b38aaba723044288e16a80d492 Author: Misty De Meo Date: Wed Jun 15 15:02:13 2016 -0700 Fix GetTime.c on Darwin with clock_gettime On Darwin versions with clock_gettime, #ifdefs will prevent the mach-specific time functions from being used in most places, and the mach time headers won't be included; however, this section was guarded incorrectly and would still try to use them. Fixes #12195. >--------------------------------------------------------------- b7b130c5102948b38aaba723044288e16a80d492 rts/posix/GetTime.c | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/rts/posix/GetTime.c b/rts/posix/GetTime.c index 130d3f1..4d25795 100644 --- a/rts/posix/GetTime.c +++ b/rts/posix/GetTime.c @@ -29,14 +29,14 @@ // we'll implement getProcessCPUTime() and getProcessElapsedTime() // separately, using getrusage() and gettimeofday() respectively -#ifdef darwin_HOST_OS +#if !defined(HAVE_CLOCK_GETTIME) && defined(darwin_HOST_OS) static uint64_t timer_scaling_factor_numer = 0; static uint64_t timer_scaling_factor_denom = 0; #endif void initializeTimer() { -#ifdef darwin_HOST_OS +#if !defined(HAVE_CLOCK_GETTIME) && defined(darwin_HOST_OS) mach_timebase_info_data_t info; (void) mach_timebase_info(&info); timer_scaling_factor_numer = (uint64_t)info.numer; From git at git.haskell.org Tue Jul 5 20:09:04 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 5 Jul 2016 20:09:04 +0000 (UTC) Subject: [commit: ghc] master: Adds x86_64-apple-darwin14 target. (f560a03) Message-ID: <20160705200904.8F2DD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f560a03ccdb246083fe64da3507c5be4c40960fe/ghc >--------------------------------------------------------------- commit f560a03ccdb246083fe64da3507c5be4c40960fe Author: Moritz Angermann Date: Tue Jul 5 20:32:22 2016 +0200 Adds x86_64-apple-darwin14 target. x86_64-apple-darwin14, is the target for the 64bit simulator. Ideally, we'd have (i386|armv7|arm64|x64_86)-apple-ios, yet, many #ifdefs depend on `darwin`, notably libffi. Hence, this only adds x86_64-apple-darwin14 as a target. This also updates the comment to add the `-S` flag, and dump the output to stdout; and adjusts the `datalayout` and `triple` values, as obtained through the method mentioned in the comment. Reviewers: hvr, erikd, austin, bgamari, simonmar Reviewed By: simonmar Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2378 >--------------------------------------------------------------- f560a03ccdb246083fe64da3507c5be4c40960fe aclocal.m4 | 4 ++-- compiler/llvmGen/LlvmCodeGen/Ppr.hs | 17 ++++++++++------- rts/StgCRun.c | 4 ++-- 3 files changed, 14 insertions(+), 11 deletions(-) diff --git a/aclocal.m4 b/aclocal.m4 index cbf51df..ce8944c 100644 --- a/aclocal.m4 +++ b/aclocal.m4 @@ -25,7 +25,7 @@ AC_DEFUN([GHC_SELECT_FILE_EXTENSIONS], x86_64-apple-darwin) $3='.dylib' ;; - arm-apple-darwin10|i386-apple-darwin11|aarch64-apple-darwin14) + arm-apple-darwin10|i386-apple-darwin11|aarch64-apple-darwin14|x86_64-apple-darwin14) $2='.a' $3='.dylib' ;; @@ -1936,7 +1936,7 @@ AC_DEFUN([GHC_CONVERT_VENDOR],[ # converts os from gnu to ghc naming, and assigns the result to $target_var AC_DEFUN([GHC_CONVERT_OS],[ case "$1-$2" in - darwin10-arm|darwin11-i386|darwin14-aarch64) + darwin10-arm|darwin11-i386|darwin14-aarch64|darwin14-x86_64) $3="ios" ;; *) diff --git a/compiler/llvmGen/LlvmCodeGen/Ppr.hs b/compiler/llvmGen/LlvmCodeGen/Ppr.hs index 1de630e..37d1391 100644 --- a/compiler/llvmGen/LlvmCodeGen/Ppr.hs +++ b/compiler/llvmGen/LlvmCodeGen/Ppr.hs @@ -60,14 +60,17 @@ moduleLayout = sdocWithPlatform $ \platform -> text "target datalayout = \"e-p:32:32:32-i1:8:8-i8:8:8-i16:16:16-i32:32:32-i64:64:64-f32:32:32-f64:64:64-v64:64:64-v128:64:128-a0:0:64-n32\"" $+$ text "target triple = \"arm-unknown-nto-qnx8.0.0eabi\"" Platform { platformArch = ArchARM {}, platformOS = OSiOS } -> - text "target datalayout = \"e-p:32:32:32-i1:8:8-i8:8:8-i16:16:16-i32:32:32-i64:64:64-f32:32:32-f64:64:64-v64:64:64-v128:64:128-a0:0:64-n32\"" - $+$ text "target triple = \"arm-apple-darwin10\"" - Platform { platformArch = ArchX86, platformOS = OSiOS } -> - text "target datalayout = \"e-p:32:32:32-i1:8:8-i8:8:8-i16:16:16-i32:32:32-i64:32:64-f32:32:32-f64:32:64-v64:64:64-v128:128:128-a0:0:64-f80:128:128-n8:16:32\"" - $+$ text "target triple = \"i386-apple-darwin11\"" + text "target datalayout = \"e-m:o-p:32:32-f64:32:64-v64:32:64-v128:32:128-a:0:32-n32-S32\"" + $+$ text "target triple = \"thumbv7-apple-ios7.0.0\"" Platform { platformArch = ArchARM64, platformOS = OSiOS } -> - text "target datalayout = \"e-p:64:64:64-i1:8:8-i8:8:8-i16:16:16-i32:32:32-i64:64:64-f32:32:32-f64:64:64-v64:64:64-v128:128:128-a0:0:64-n32:64-S128\"" + text "target datalayout = \"e-m:o-i64:64-i128:128-n32:64-S128\"" $+$ text "target triple = \"arm64-apple-ios7.0.0\"" + Platform { platformArch = ArchX86, platformOS = OSiOS } -> + text "target datalayout = \"e-m:o-p:32:32-f64:32:64-f80:128-n8:16:32-S128\"" + $+$ text "target triple = \"i386-apple-ios7.0.0\"" + Platform { platformArch = ArchX86_64, platformOS = OSiOS } -> + text "target datalayout = \"e-m:o-i64:64-f80:128-n8:16:32:64-S128\"" + $+$ text "target triple = \"x86_64-apple-ios7.0.0\"" Platform { platformArch = ArchARM64, platformOS = OSLinux } -> text "target datalayout = \"e-m:e-i64:64-i128:128-n32:64-S128\"" $+$ text "target triple = \"aarch64-unknown-linux-gnu\"" @@ -78,7 +81,7 @@ moduleLayout = sdocWithPlatform $ \platform -> -- If you see the above panic, GHC is missing the required target datalayout -- and triple information. You can obtain this info by compiling a simple -- 'hello world' C program with the clang C compiler eg: - -- clang hello.c -emit-llvm -o hello.ll + -- clang -S hello.c -emit-llvm -o - -- and the first two lines of hello.ll should provide the 'target datalayout' -- and 'target triple' lines required. diff --git a/rts/StgCRun.c b/rts/StgCRun.c index cf0c05c..c110f51 100644 --- a/rts/StgCRun.c +++ b/rts/StgCRun.c @@ -245,7 +245,7 @@ StgRunIsImplementedInAssembler(void) #define STG_GLOBAL ".globl " -#ifdef darwin_HOST_OS +#if defined(darwin_HOST_OS) || defined(ios_HOST_OS) #define STG_HIDDEN ".private_extern " #else #define STG_HIDDEN ".hidden " @@ -417,7 +417,7 @@ StgRun(StgFunPtr f, StgRegTable *basereg) { #define STG_GLOBAL ".globl " -#ifdef darwin_HOST_OS +#if defined(darwin_HOST_OS) #define STG_HIDDEN ".private_extern " #else #define STG_HIDDEN ".hidden " From git at git.haskell.org Wed Jul 6 09:46:25 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 6 Jul 2016 09:46:25 +0000 (UTC) Subject: [commit: ghc] master: Have addModFinalizer expose the local type environment. (567dbd9) Message-ID: <20160706094625.1E9E73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/567dbd9bcb602accf3184b83050f2982cbb7758b/ghc >--------------------------------------------------------------- commit 567dbd9bcb602accf3184b83050f2982cbb7758b Author: Facundo Domínguez Date: Wed Jul 6 06:48:27 2016 -0300 Have addModFinalizer expose the local type environment. Summary: This annotates the splice point with 'HsSpliced ref e' where 'e' is the result of the splice. 'ref' is a reference that the typechecker will fill with the local type environment. The finalizer then reads the ref and uses the local type environment, which causes 'reify' to find local variables when run in the finalizer. Test Plan: ./validate Reviewers: simonpj, simonmar, bgamari, austin, goldfire Reviewed By: goldfire Subscribers: simonmar, thomie, mboes Differential Revision: https://phabricator.haskell.org/D2286 GHC Trac Issues: #11832 >--------------------------------------------------------------- 567dbd9bcb602accf3184b83050f2982cbb7758b compiler/deSugar/DsMeta.hs | 1 + compiler/hsSyn/HsExpr.hs | 55 +++++++++ compiler/rename/RnPat.hs | 4 + compiler/rename/RnSplice.hs | 135 +++++++++++++++++++-- compiler/rename/RnTypes.hs | 1 + compiler/typecheck/TcExpr.hs | 8 ++ compiler/typecheck/TcHsType.hs | 12 ++ compiler/typecheck/TcPat.hs | 9 ++ compiler/typecheck/TcRnMonad.hs | 17 +++ compiler/typecheck/TcRnTypes.hs | 55 +++++++-- compiler/typecheck/TcSplice.hs | 100 +++++++++++---- compiler/typecheck/TcSplice.hs-boot | 3 +- iserv/src/Main.hs | 2 +- libraries/ghci/GHCi/Message.hs | 18 +-- libraries/ghci/GHCi/TH.hs | 36 +++--- .../template-haskell/Language/Haskell/TH/Syntax.hs | 4 + testsuite/tests/th/TH_reifyLocalDefs.hs | 36 ++++++ testsuite/tests/th/TH_reifyLocalDefs.stderr | 5 + testsuite/tests/th/all.T | 1 + 19 files changed, 429 insertions(+), 73 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 567dbd9bcb602accf3184b83050f2982cbb7758b From git at git.haskell.org Wed Jul 6 14:12:12 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 6 Jul 2016 14:12:12 +0000 (UTC) Subject: [commit: ghc] branch 'wip/T12370' created Message-ID: <20160706141212.371523A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/T12370 Referencing: 04ded5e3c0bcc359f4b46958b5942b8230af1b28 From git at git.haskell.org Wed Jul 6 14:12:15 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 6 Jul 2016 14:12:15 +0000 (UTC) Subject: [commit: ghc] wip/T12370: Implement LetUp rule (#12370) (04ded5e) Message-ID: <20160706141215.026423A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T12370 Link : http://ghc.haskell.org/trac/ghc/changeset/04ded5e3c0bcc359f4b46958b5942b8230af1b28/ghc >--------------------------------------------------------------- commit 04ded5e3c0bcc359f4b46958b5942b8230af1b28 Author: Joachim Breitner Date: Wed Jul 6 15:44:18 2016 +0200 Implement LetUp rule (#12370) >--------------------------------------------------------------- 04ded5e3c0bcc359f4b46958b5942b8230af1b28 compiler/stranal/DmdAnal.hs | 19 +++++++++++++++++++ 1 file changed, 19 insertions(+) diff --git a/compiler/stranal/DmdAnal.hs b/compiler/stranal/DmdAnal.hs index 53144ff..4ae46a1 100644 --- a/compiler/stranal/DmdAnal.hs +++ b/compiler/stranal/DmdAnal.hs @@ -255,6 +255,20 @@ dmdAnal' env dmd (Case scrut case_bndr ty alts) -- , text "res_ty" <+> ppr res_ty ]) $ (res_ty, Case scrut' case_bndr' ty alts') +-- The following case handle the LetUp variant of processing a let binding, and is +-- used for everything that is not a lambda. +dmdAnal' env dmd (Let (NonRec id rhs) body) + | not (isLam rhs) + , Nothing <- unpackTrivial rhs -- Lets use the existing code path for that + = (final_ty, Let (NonRec id' rhs') body') + where + (body_ty, body') = dmdAnal env dmd body + (body_ty', id_dmd) = findBndrDmd env notArgOfDfun body_ty id + id' = setIdDemandInfo id id_dmd + + (rhs_ty, rhs') = dmdAnalStar env (dmdTransformThunkDmd rhs id_dmd) rhs + final_ty = body_ty' `bothDmdType` rhs_ty + dmdAnal' env dmd (Let (NonRec id rhs) body) = (body_ty2, Let (NonRec id2 rhs') body') where @@ -587,6 +601,11 @@ unpackTrivial (Lam v e) | isTyVar v = unpackTrivial e unpackTrivial (App e a) | isTypeArg a = unpackTrivial e unpackTrivial _ = Nothing +-- isLam e /= null (fst (collectBinders e)) +isLam :: CoreExpr -> Bool +isLam (Lam _ _) = True +isLam _ = False + {- Note [Demand analysis for trivial right-hand sides] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ From git at git.haskell.org Wed Jul 6 14:17:21 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 6 Jul 2016 14:17:21 +0000 (UTC) Subject: [commit: ghc] master: Mention addModFinalizer changes in release notes. (56f47d4) Message-ID: <20160706141721.F2CC13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/56f47d4a4e418235285d8b8cfe23bde6473f17fc/ghc >--------------------------------------------------------------- commit 56f47d4a4e418235285d8b8cfe23bde6473f17fc Author: Facundo Domínguez Date: Wed Jul 6 11:18:58 2016 -0300 Mention addModFinalizer changes in release notes. >--------------------------------------------------------------- 56f47d4a4e418235285d8b8cfe23bde6473f17fc docs/users_guide/8.2.1-notes.rst | 7 +++++++ 1 file changed, 7 insertions(+) diff --git a/docs/users_guide/8.2.1-notes.rst b/docs/users_guide/8.2.1-notes.rst index 0a9963f..7b271cd 100644 --- a/docs/users_guide/8.2.1-notes.rst +++ b/docs/users_guide/8.2.1-notes.rst @@ -44,6 +44,13 @@ Template Haskell - TODO FIXME. +- ``addModFinalizer`` now exposes the local typing environment at the splice + point. This allows ``reify`` to see local and top-level definitions in the + current declaration group when used as in + + .. code-block:: none + f x = $(addModFinalizer (reify 'x >>= runIO . print) >> [| x |]) + Runtime system ~~~~~~~~~~~~~~ From git at git.haskell.org Wed Jul 6 19:36:32 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 6 Jul 2016 19:36:32 +0000 (UTC) Subject: [commit: ghc] master: Switch to LLVM version 3.8 (672314c) Message-ID: <20160706193632.4C2F43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/672314cbeb8ac386a58f17dc4650dbdf4c55d8b5/ghc >--------------------------------------------------------------- commit 672314cbeb8ac386a58f17dc4650dbdf4c55d8b5 Author: Erik de Castro Lopo Date: Thu Jul 7 05:38:14 2016 +1000 Switch to LLVM version 3.8 LLVM 3.8 was released a couple of months ago. Test Plan: Build and test on x86_64/linux (perf-llvm) and armhf/linux. Reviewers: austin, hvr, rwbarton, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2382 >--------------------------------------------------------------- 672314cbeb8ac386a58f17dc4650dbdf4c55d8b5 compiler/llvmGen/Llvm/PpLlvm.hs | 2 +- compiler/llvmGen/Llvm/Types.hs | 8 ++++++++ configure.ac | 2 +- 3 files changed, 10 insertions(+), 2 deletions(-) diff --git a/compiler/llvmGen/Llvm/PpLlvm.hs b/compiler/llvmGen/Llvm/PpLlvm.hs index 47e26ab..c9c1f95 100644 --- a/compiler/llvmGen/Llvm/PpLlvm.hs +++ b/compiler/llvmGen/Llvm/PpLlvm.hs @@ -73,7 +73,7 @@ ppLlvmGlobal (LMGlobal var@(LMGlobalVar _ _ link x a c) dat) = Nothing -> empty rhs = case dat of - Just stat -> ppr stat + Just stat -> pprSpecialStatic stat Nothing -> ppr (pLower $ getVarType var) -- Position of linkage is different for aliases. diff --git a/compiler/llvmGen/Llvm/Types.hs b/compiler/llvmGen/Llvm/Types.hs index 5c2ce5e..d2cab44 100644 --- a/compiler/llvmGen/Llvm/Types.hs +++ b/compiler/llvmGen/Llvm/Types.hs @@ -175,6 +175,14 @@ instance Outputable LlvmStatic where ppr (LMSub s1 s2) = pprStaticArith s1 s2 (sLit "sub") (sLit "fsub") "LMSub" + +pprSpecialStatic :: LlvmStatic -> SDoc +pprSpecialStatic (LMBitc v t) = + ppr (pLower t) <> text ", bitcast (" <> ppr v <> text " to " <> ppr t + <> char ')' +pprSpecialStatic stat = ppr stat + + pprStaticArith :: LlvmStatic -> LlvmStatic -> LitString -> LitString -> String -> SDoc pprStaticArith s1 s2 int_op float_op op_name = let ty1 = getStatType s1 diff --git a/configure.ac b/configure.ac index 664deb4..f4b839e 100644 --- a/configure.ac +++ b/configure.ac @@ -521,7 +521,7 @@ esac # tools we are looking for. In the past, GHC supported a number of # versions of LLVM simultaneously, but that stopped working around # 3.5/3.6 release of LLVM. -LlvmVersion=3.7 +LlvmVersion=3.8 AC_SUBST([LlvmVersion]) sUPPORTED_LLVM_VERSION=$(echo \($LlvmVersion\) | sed 's/\./,/') AC_DEFINE_UNQUOTED([sUPPORTED_LLVM_VERSION], ${sUPPORTED_LLVM_VERSION}, [The supported LLVM version number]) From git at git.haskell.org Wed Jul 6 21:23:22 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 6 Jul 2016 21:23:22 +0000 (UTC) Subject: [commit: ghc] wip/T12370: Demand analyser: Implement LetUp rule (#12370) (aa472d7) Message-ID: <20160706212322.B51AF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T12370 Link : http://ghc.haskell.org/trac/ghc/changeset/aa472d7bf13bbeb390e857c95c8b92d90d6246ae/ghc >--------------------------------------------------------------- commit aa472d7bf13bbeb390e857c95c8b92d90d6246ae Author: Joachim Breitner Date: Wed Jul 6 15:44:18 2016 +0200 Demand analyser: Implement LetUp rule (#12370) This makes the implementation match the description in the paper more closely: There, a let binding that is not a function has first its body analised, and then the binding’s RHS. This way, the demand on the bound variable by the body can be fed into the RHS, yielding more precise results. Performance measurements do unfortunately not show significant improvements or regessions. >--------------------------------------------------------------- aa472d7bf13bbeb390e857c95c8b92d90d6246ae compiler/stranal/DmdAnal.hs | 19 +++++++++++++++++++ .../tests/simplCore/should_compile/spec-inline.stderr | 2 +- 2 files changed, 20 insertions(+), 1 deletion(-) diff --git a/compiler/stranal/DmdAnal.hs b/compiler/stranal/DmdAnal.hs index 53144ff..4ae46a1 100644 --- a/compiler/stranal/DmdAnal.hs +++ b/compiler/stranal/DmdAnal.hs @@ -255,6 +255,20 @@ dmdAnal' env dmd (Case scrut case_bndr ty alts) -- , text "res_ty" <+> ppr res_ty ]) $ (res_ty, Case scrut' case_bndr' ty alts') +-- The following case handle the LetUp variant of processing a let binding, and is +-- used for everything that is not a lambda. +dmdAnal' env dmd (Let (NonRec id rhs) body) + | not (isLam rhs) + , Nothing <- unpackTrivial rhs -- Lets use the existing code path for that + = (final_ty, Let (NonRec id' rhs') body') + where + (body_ty, body') = dmdAnal env dmd body + (body_ty', id_dmd) = findBndrDmd env notArgOfDfun body_ty id + id' = setIdDemandInfo id id_dmd + + (rhs_ty, rhs') = dmdAnalStar env (dmdTransformThunkDmd rhs id_dmd) rhs + final_ty = body_ty' `bothDmdType` rhs_ty + dmdAnal' env dmd (Let (NonRec id rhs) body) = (body_ty2, Let (NonRec id2 rhs') body') where @@ -587,6 +601,11 @@ unpackTrivial (Lam v e) | isTyVar v = unpackTrivial e unpackTrivial (App e a) | isTypeArg a = unpackTrivial e unpackTrivial _ = Nothing +-- isLam e /= null (fst (collectBinders e)) +isLam :: CoreExpr -> Bool +isLam (Lam _ _) = True +isLam _ = False + {- Note [Demand analysis for trivial right-hand sides] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ diff --git a/testsuite/tests/simplCore/should_compile/spec-inline.stderr b/testsuite/tests/simplCore/should_compile/spec-inline.stderr index 64bf015..732265a 100644 --- a/testsuite/tests/simplCore/should_compile/spec-inline.stderr +++ b/testsuite/tests/simplCore/should_compile/spec-inline.stderr @@ -43,7 +43,7 @@ Rec { -- RHS size: {terms: 55, types: 9, coercions: 0} Roman.foo_$s$wgo [Occ=LoopBreaker] :: GHC.Prim.Int# -> GHC.Prim.Int# -> GHC.Prim.Int# -[GblId, Arity=2, Caf=NoCafRefs, Str=] +[GblId, Arity=2, Caf=NoCafRefs, Str=] Roman.foo_$s$wgo = \ (sc :: GHC.Prim.Int#) (sc1 :: GHC.Prim.Int#) -> let { From git at git.haskell.org Thu Jul 7 08:38:44 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 7 Jul 2016 08:38:44 +0000 (UTC) Subject: [commit: ghc] master: Show testcase where demand analysis abortion code fails (b9cea81) Message-ID: <20160707083844.E14683A301@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b9cea81ded5dc4da19fc011d96f28ade660438c2/ghc >--------------------------------------------------------------- commit b9cea81ded5dc4da19fc011d96f28ade660438c2 Author: Joachim Breitner Date: Thu Jul 7 10:41:38 2016 +0200 Show testcase where demand analysis abortion code fails By making it believe that some deeply nested value is absent when it really isn't. See #12368. >--------------------------------------------------------------- b9cea81ded5dc4da19fc011d96f28ade660438c2 testsuite/tests/stranal/should_run/T12368.hs | 27 ++++++++++++++++++++++++ testsuite/tests/stranal/should_run/T12368.stderr | 3 +++ testsuite/tests/stranal/should_run/all.T | 1 + 3 files changed, 31 insertions(+) diff --git a/testsuite/tests/stranal/should_run/T12368.hs b/testsuite/tests/stranal/should_run/T12368.hs new file mode 100644 index 0000000..e830761 --- /dev/null +++ b/testsuite/tests/stranal/should_run/T12368.hs @@ -0,0 +1,27 @@ +-- If care is not taken when aborting a fixed-point iteration, wrong absentness +-- information escapes + +-- Needs to be a product type +data Stream = S Int Stream + +bar :: Int -> Stream -> Int +bar n s = foo n s + where + foo :: Int -> Stream -> Int + foo 0 (S n s) = 0 + foo i (S n s) = n + foo (i-1) s +{-# NOINLINE bar #-} + + +baz :: Int -> Stream -> Int +baz 0 not_absent = 0 +baz 1 not_absent = baz 2 not_absent +baz x not_absent = bar 1000 arg + where + arg = S 1 $ S 1 $ S 1 $ S 1 $ S 1 $ S 1 $ S 1 $ S 1 $ S 1 $ S 1 $ not_absent + +bamf x = baz x (S x (error "This is good!")) +{-# NOINLINE bamf #-} + +main :: IO () +main = bamf 10 `seq` return () diff --git a/testsuite/tests/stranal/should_run/T12368.stderr b/testsuite/tests/stranal/should_run/T12368.stderr new file mode 100644 index 0000000..05025ac --- /dev/null +++ b/testsuite/tests/stranal/should_run/T12368.stderr @@ -0,0 +1,3 @@ +T12368: This is good! +CallStack (from HasCallStack): + error, called at T12368.hs:24:22 in main:Main diff --git a/testsuite/tests/stranal/should_run/all.T b/testsuite/tests/stranal/should_run/all.T index a4b550e..6846c82 100644 --- a/testsuite/tests/stranal/should_run/all.T +++ b/testsuite/tests/stranal/should_run/all.T @@ -12,3 +12,4 @@ test('T10148', normal, compile_and_run, ['']) test('T10218', normal, compile_and_run, ['']) test('T11076', normal, multimod_compile_and_run, ['T11076.hs', 'T11076_prim.cmm']) test('T11555a', normal, compile_and_run, ['']) +test('T12368', [ exit_code(1), expect_broken(12368) ], compile_and_run, ['']) From git at git.haskell.org Thu Jul 7 08:43:22 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 7 Jul 2016 08:43:22 +0000 (UTC) Subject: [commit: ghc] master: --without-libcharset disables the use of libcharset (979baec) Message-ID: <20160707084322.8B5823A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/979baecd394137b583d5938bd8f2738185426765/ghc >--------------------------------------------------------------- commit 979baecd394137b583d5938bd8f2738185426765 Author: Simon Marlow Date: Wed Jul 6 05:47:22 2016 -0700 --without-libcharset disables the use of libcharset >--------------------------------------------------------------- 979baecd394137b583d5938bd8f2738185426765 libraries/base/configure.ac | 16 +++++++++++++--- 1 file changed, 13 insertions(+), 3 deletions(-) diff --git a/libraries/base/configure.ac b/libraries/base/configure.ac index b8a4774..8098bc7 100644 --- a/libraries/base/configure.ac +++ b/libraries/base/configure.ac @@ -192,14 +192,24 @@ FP_SEARCH_LIBS_PROTO(iconv, [AC_MSG_ERROR([iconv is required on non-Windows platforms])]) # If possible, we use libcharset instead of nl_langinfo(CODESET) to -# determine the current locale's character encoding. -FP_SEARCH_LIBS_PROTO( +# determine the current locale's character encoding. Allow the user +# to disable this with --without-libcharset if they don't want a +# dependency on libcharset. +AC_ARG_WITH([libcharset], + [AS_HELP_STRING([--with-libcharset], + [Use libcharset [default=only if available]])], + [], + [with_libcharset=check]) + +AS_IF([test "x$with_libcharset" != xno], + FP_SEARCH_LIBS_PROTO( [locale_charset], [#include ], [const char* charset = locale_charset();], [charset], [AC_DEFINE([HAVE_LIBCHARSET], [1], [Define to 1 if you have libcharset.]) - EXTRA_LIBS="$EXTRA_LIBS $ac_lib"]) + EXTRA_LIBS="$EXTRA_LIBS $ac_lib"] + )) fi From git at git.haskell.org Thu Jul 7 09:21:36 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 7 Jul 2016 09:21:36 +0000 (UTC) Subject: [commit: ghc] branch 'wip/12368' created Message-ID: <20160707092136.71E403A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/12368 Referencing: a267da1c7fbaa4dac86a7cb5a7483fb6e2f5c446 From git at git.haskell.org Thu Jul 7 09:21:39 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 7 Jul 2016 09:21:39 +0000 (UTC) Subject: [commit: ghc] wip/12368: DmdAnal: Add a final, safe iteration (a267da1) Message-ID: <20160707092139.1D6EA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/12368 Link : http://ghc.haskell.org/trac/ghc/changeset/a267da1c7fbaa4dac86a7cb5a7483fb6e2f5c446/ghc >--------------------------------------------------------------- commit a267da1c7fbaa4dac86a7cb5a7483fb6e2f5c446 Author: Joachim Breitner Date: Thu Jul 7 11:23:48 2016 +0200 DmdAnal: Add a final, safe iteration this fixes #12368. >--------------------------------------------------------------- a267da1c7fbaa4dac86a7cb5a7483fb6e2f5c446 compiler/basicTypes/Demand.hs | 15 +++++++++++++-- compiler/stranal/DmdAnal.hs | 21 ++++++++++++--------- testsuite/tests/stranal/should_run/all.T | 2 +- 3 files changed, 26 insertions(+), 12 deletions(-) diff --git a/compiler/basicTypes/Demand.hs b/compiler/basicTypes/Demand.hs index 8dc7f3b..1849acc 100644 --- a/compiler/basicTypes/Demand.hs +++ b/compiler/basicTypes/Demand.hs @@ -35,7 +35,8 @@ module Demand ( vanillaCprProdRes, cprSumRes, appIsBottom, isBottomingSig, pprIfaceStrictSig, trimCPRInfo, returnsCPR_maybe, - StrictSig(..), mkStrictSig, mkClosedStrictSig, nopSig, botSig, cprProdSig, + StrictSig(..), mkStrictSig, mkClosedStrictSig, + nopSig, botSig, toTopSig, cprProdSig, isTopSig, hasDemandEnvSig, splitStrictSig, increaseStrictSigArity, seqDemand, seqDemandList, seqDmdType, seqStrictSig, @@ -1261,11 +1262,18 @@ emptyDmdEnv = emptyVarEnv -- nopDmdType is the demand of doing nothing -- (lazy, absent, no CPR information, no termination information). -- Note that it is ''not'' the top of the lattice (which would be "may use everything"), --- so it is (no longer) called topDmd +-- so it is (no longer) called topDmdType nopDmdType, botDmdType :: DmdType nopDmdType = DmdType emptyDmdEnv [] topRes botDmdType = DmdType emptyDmdEnv [] botRes +-- This converts a demand type to the least useful (most conservative) type +-- that mentions the same free variables. It takes the role of a top element, +-- which we do not have, since a top element would have to mention all variables +-- in the DmdEnv +toTopDmdType :: DmdType -> DmdType +toTopDmdType (DmdType env _ _) = DmdType (mapVarEnv (const topDmd) env) [] topRes + cprProdDmdType :: Arity -> DmdType cprProdDmdType arity = DmdType emptyDmdEnv [] (vanillaCprProdRes arity) @@ -1690,6 +1698,9 @@ nopSig, botSig :: StrictSig nopSig = StrictSig nopDmdType botSig = StrictSig botDmdType +toTopSig :: StrictSig -> StrictSig +toTopSig (StrictSig ty) = StrictSig (toTopDmdType ty) + cprProdSig :: Arity -> StrictSig cprProdSig arity = StrictSig (cprProdDmdType arity) diff --git a/compiler/stranal/DmdAnal.hs b/compiler/stranal/DmdAnal.hs index 53144ff..9928e17 100644 --- a/compiler/stranal/DmdAnal.hs +++ b/compiler/stranal/DmdAnal.hs @@ -475,26 +475,22 @@ dmdFix top_lvl env orig_pairs loop' n env pairs loop' n env pairs - | found_fixpoint + | found_fixpoint || n > 10 = (env', lazy_fv, pairs') -- Note: return pairs', not pairs. pairs' is the result of -- processing the RHSs with sigs (= sigs'), whereas pairs -- is the result of processing the RHSs with the *previous* -- iteration of sigs. - - | n >= 10 + | n == 10 = -- pprTrace "dmdFix loop" (ppr n <+> (vcat -- [ text "Sigs:" <+> ppr [ (id,lookupVarEnv (sigEnv env) id, -- lookupVarEnv (sigEnv env') id) -- | (id,_) <- pairs], -- text "env:" <+> ppr env, -- text "binds:" <+> pprCoreBinding (Rec pairs)])) - (env, lazy_fv, orig_pairs) -- Safe output - -- The lazy_fv part is really important! orig_pairs has no strictness - -- info, including nothing about free vars. But if we have - -- letrec f = ....y..... in ...f... - -- where 'y' is free in f, we must record that y is mentioned, - -- otherwise y will get recorded as absent altogether + loop (n+1) (addPessimisticSigs env bndrs) pairs' + -- We are not going to find a fix point any time soon. So do one final round + -- of analysis with safe assumptions about the strictness signatures | otherwise = loop (n+1) (nonVirgin env') pairs' @@ -1009,6 +1005,13 @@ addInitialSigs top_lvl env@(AE { ae_sigs = sigs, ae_virgin = virgin }) ids init_sig | virgin = \_ -> botSig | otherwise = idStrictness +addPessimisticSigs :: AnalEnv -> [Id] -> AnalEnv +addPessimisticSigs env@(AE { ae_sigs = sigs }) ids + = env { ae_sigs = extendVarEnvList sigs new_sigs } + where + new_sigs = [ (id, (toTopSig sig, top_lvl)) + | id <- ids, let Just (sig, top_lvl) = lookupSigEnv env id ] + nonVirgin :: AnalEnv -> AnalEnv nonVirgin env = env { ae_virgin = False } diff --git a/testsuite/tests/stranal/should_run/all.T b/testsuite/tests/stranal/should_run/all.T index 6846c82..5b976f1 100644 --- a/testsuite/tests/stranal/should_run/all.T +++ b/testsuite/tests/stranal/should_run/all.T @@ -12,4 +12,4 @@ test('T10148', normal, compile_and_run, ['']) test('T10218', normal, compile_and_run, ['']) test('T11076', normal, multimod_compile_and_run, ['T11076.hs', 'T11076_prim.cmm']) test('T11555a', normal, compile_and_run, ['']) -test('T12368', [ exit_code(1), expect_broken(12368) ], compile_and_run, ['']) +test('T12368', exit_code(1), compile_and_run, ['']) From git at git.haskell.org Thu Jul 7 09:28:13 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 7 Jul 2016 09:28:13 +0000 (UTC) Subject: [commit: ghc] master: Style changes for UniqFM (bedd620) Message-ID: <20160707092813.8F4EC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/bedd62037f588321312feaf16923fa04d443e3d8/ghc >--------------------------------------------------------------- commit bedd62037f588321312feaf16923fa04d443e3d8 Author: Bartosz Nitka Date: Thu Jul 7 02:31:51 2016 -0700 Style changes for UniqFM This file used the old style with type signatures separated from the code. As far as I understand the idea was to generate PostScript files from the source. I think the idea was abandoned and this more modern style is more common in the codebase. Test Plan: it still compiles Reviewers: austin, simonmar, bgamari Reviewed By: simonmar, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2383 >--------------------------------------------------------------- bedd62037f588321312feaf16923fa04d443e3d8 compiler/utils/UniqFM.hs | 293 +++++++++++++++++++++++------------------------ 1 file changed, 145 insertions(+), 148 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc bedd62037f588321312feaf16923fa04d443e3d8 From git at git.haskell.org Thu Jul 7 10:54:07 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 7 Jul 2016 10:54:07 +0000 (UTC) Subject: [commit: ghc] master: Document some codegen nondeterminism (6ed7c47) Message-ID: <20160707105407.3C8523A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6ed7c4793fe1acd491646a8312afbbda6be1fd0b/ghc >--------------------------------------------------------------- commit 6ed7c4793fe1acd491646a8312afbbda6be1fd0b Author: Bartosz Nitka Date: Thu Jul 7 03:07:20 2016 -0700 Document some codegen nondeterminism Bit-for-bit reproducible binaries are not a goal for now, so this is just marking places that could be a problem. Doing this will allow eltsUFM to be removed and will leave only nonDetEltsUFM. GHC Trac: #4012 >--------------------------------------------------------------- 6ed7c4793fe1acd491646a8312afbbda6be1fd0b compiler/cmm/CmmCommonBlockElim.hs | 3 ++- compiler/cmm/CmmLayoutStack.hs | 12 +++++++---- compiler/nativeGen/AsmCodeGen.hs | 4 +++- compiler/nativeGen/RegAlloc/Graph/Main.hs | 3 ++- compiler/nativeGen/RegAlloc/Graph/Spill.hs | 5 ++--- compiler/nativeGen/RegAlloc/Graph/SpillCost.hs | 6 ++++-- compiler/nativeGen/RegAlloc/Graph/Stats.hs | 14 +++++++------ compiler/nativeGen/RegAlloc/Graph/TrivColorable.hs | 3 ++- compiler/nativeGen/RegAlloc/Linear/Stats.hs | 3 ++- compiler/utils/GraphOps.hs | 23 +++++++++++++--------- compiler/utils/GraphPpr.hs | 5 +++-- 11 files changed, 50 insertions(+), 31 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 6ed7c4793fe1acd491646a8312afbbda6be1fd0b From git at git.haskell.org Thu Jul 7 14:46:36 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 7 Jul 2016 14:46:36 +0000 (UTC) Subject: [commit: ghc] master: Use deterministic maps for FamInstEnv (9858552) Message-ID: <20160707144636.B5F4E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9858552d607f643db0385be2133a04dd4b5ff753/ghc >--------------------------------------------------------------- commit 9858552d607f643db0385be2133a04dd4b5ff753 Author: Bartosz Nitka Date: Thu Jul 7 04:02:20 2016 -0700 Use deterministic maps for FamInstEnv We turn FamInstEnvs into lists in some places which don't directly affect the ABI. That happens in family consistency checks and when producing output for `:info`. Unfortunately that nondeterminism is nonlocal and it's hard to tell locally what it affects. Furthermore the envs should be relatively small, so it should be free to use deterministic maps here. Testing with nofib and ./validate detected no difference between UniqFM and UniqDFM. GHC Trac: #4012 >--------------------------------------------------------------- 9858552d607f643db0385be2133a04dd4b5ff753 compiler/types/FamInstEnv.hs | 20 ++++++++++---------- 1 file changed, 10 insertions(+), 10 deletions(-) diff --git a/compiler/types/FamInstEnv.hs b/compiler/types/FamInstEnv.hs index 3f07c21..c860dbc 100644 --- a/compiler/types/FamInstEnv.hs +++ b/compiler/types/FamInstEnv.hs @@ -48,7 +48,7 @@ import VarSet import VarEnv import Name import PrelNames ( eqPrimTyConKey ) -import UniqFM +import UniqDFM import Outputable import Maybes import TrieMap @@ -361,7 +361,7 @@ These two axioms for T, one with one pattern, one with two; see Note [Eta reduction for data families] -} -type FamInstEnv = UniqFM FamilyInstEnv -- Maps a family to its instances +type FamInstEnv = UniqDFM FamilyInstEnv -- Maps a family to its instances -- See Note [FamInstEnv] type FamInstEnvs = (FamInstEnv, FamInstEnv) @@ -381,16 +381,16 @@ emptyFamInstEnvs :: (FamInstEnv, FamInstEnv) emptyFamInstEnvs = (emptyFamInstEnv, emptyFamInstEnv) emptyFamInstEnv :: FamInstEnv -emptyFamInstEnv = emptyUFM +emptyFamInstEnv = emptyUDFM famInstEnvElts :: FamInstEnv -> [FamInst] -famInstEnvElts fi = [elt | FamIE elts <- eltsUFM fi, elt <- elts] +famInstEnvElts fi = [elt | FamIE elts <- eltsUDFM fi, elt <- elts] familyInstances :: (FamInstEnv, FamInstEnv) -> TyCon -> [FamInst] familyInstances (pkg_fie, home_fie) fam = get home_fie ++ get pkg_fie where - get env = case lookupUFM env fam of + get env = case lookupUDFM env fam of Just (FamIE insts) -> insts Nothing -> [] @@ -400,14 +400,14 @@ extendFamInstEnvList inst_env fis = foldl extendFamInstEnv inst_env fis extendFamInstEnv :: FamInstEnv -> FamInst -> FamInstEnv extendFamInstEnv inst_env ins_item@(FamInst {fi_fam = cls_nm}) - = addToUFM_C add inst_env cls_nm (FamIE [ins_item]) + = addToUDFM_C add inst_env cls_nm (FamIE [ins_item]) where add (FamIE items) _ = FamIE (ins_item:items) deleteFromFamInstEnv :: FamInstEnv -> FamInst -> FamInstEnv -- Used only for overriding in GHCi deleteFromFamInstEnv inst_env fam_inst@(FamInst {fi_fam = fam_nm}) - = adjustUFM adjust inst_env fam_nm + = adjustUDFM adjust inst_env fam_nm where adjust :: FamilyInstEnv -> FamilyInstEnv adjust (FamIE items) @@ -712,7 +712,7 @@ lookupFamInstEnvByTyCon :: FamInstEnvs -> TyCon -> [FamInst] lookupFamInstEnvByTyCon (pkg_ie, home_ie) fam_tc = get pkg_ie ++ get home_ie where - get ie = case lookupUFM ie fam_tc of + get ie = case lookupUDFM ie fam_tc of Nothing -> [] Just (FamIE fis) -> fis @@ -875,7 +875,7 @@ lookupFamInstEnvInjectivityConflicts injList (pkg_ie, home_ie) | otherwise = True lookup_inj_fam_conflicts ie - | isOpenFamilyTyCon fam, Just (FamIE insts) <- lookupUFM ie fam + | isOpenFamilyTyCon fam, Just (FamIE insts) <- lookupUDFM ie fam = map (coAxiomSingleBranch . fi_axiom) $ filter isInjConflict insts | otherwise = [] @@ -915,7 +915,7 @@ lookup_fam_inst_env' -- The worker, local to this module -> [FamInstMatch] lookup_fam_inst_env' match_fun ie fam match_tys | isOpenFamilyTyCon fam - , Just (FamIE insts) <- lookupUFM ie fam + , Just (FamIE insts) <- lookupUDFM ie fam = find insts -- The common case | otherwise = [] where From git at git.haskell.org Thu Jul 7 15:11:28 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 7 Jul 2016 15:11:28 +0000 (UTC) Subject: [commit: ghc] master: Correct the message displayed for syntax error (#12146) (34085b5) Message-ID: <20160707151128.548DC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/34085b501d99bd0b185a4addb0577330fa1f8356/ghc >--------------------------------------------------------------- commit 34085b501d99bd0b185a4addb0577330fa1f8356 Author: Aditya Date: Sat Jun 25 19:51:36 2016 +0530 Correct the message displayed for syntax error (#12146) >--------------------------------------------------------------- 34085b501d99bd0b185a4addb0577330fa1f8356 compiler/rename/RnSource.hs | 4 ++-- testsuite/tests/ghci/scripts/T1914.stderr | 4 ++-- testsuite/tests/ghci/scripts/T6106.stderr | 4 ++-- testsuite/tests/rename/should_fail/T4042.stderr | 4 ++-- 4 files changed, 8 insertions(+), 8 deletions(-) diff --git a/compiler/rename/RnSource.hs b/compiler/rename/RnSource.hs index 4790ada..67cf7fd 100644 --- a/compiler/rename/RnSource.hs +++ b/compiler/rename/RnSource.hs @@ -2114,8 +2114,8 @@ add gp loc (SpliceD splice@(SpliceDecl _ flag)) ds ; return (gp, Just (splice, ds)) } where - badImplicitSplice = text "Parse error: naked expression at top level" - $$ text "Perhaps you intended to use TemplateHaskell" + badImplicitSplice = text "Parse error: module header, import declaration" + $$ text "or top-level declaration expected." -- Class declarations: pull out the fixity signatures to the top add gp@(HsGroup {hs_tyclds = ts, hs_fixds = fs}) l (TyClD d) ds diff --git a/testsuite/tests/ghci/scripts/T1914.stderr b/testsuite/tests/ghci/scripts/T1914.stderr index b6357f2..6dd83fa 100644 --- a/testsuite/tests/ghci/scripts/T1914.stderr +++ b/testsuite/tests/ghci/scripts/T1914.stderr @@ -1,4 +1,4 @@ T1914A.hs:1:38: - Parse error: naked expression at top level - Perhaps you intended to use TemplateHaskell + Parse error: module header, import declaration + or top-level declaration expected. diff --git a/testsuite/tests/ghci/scripts/T6106.stderr b/testsuite/tests/ghci/scripts/T6106.stderr index ad92524..7023e2f 100644 --- a/testsuite/tests/ghci/scripts/T6106.stderr +++ b/testsuite/tests/ghci/scripts/T6106.stderr @@ -1,4 +1,4 @@ T6106.hs:1:1: - Parse error: naked expression at top level - Perhaps you intended to use TemplateHaskell + Parse error: module header, import declaration + or top-level declaration expected. diff --git a/testsuite/tests/rename/should_fail/T4042.stderr b/testsuite/tests/rename/should_fail/T4042.stderr index a00cec6..65d737b 100644 --- a/testsuite/tests/rename/should_fail/T4042.stderr +++ b/testsuite/tests/rename/should_fail/T4042.stderr @@ -1,4 +1,4 @@ T4042.hs:6:1: - Parse error: naked expression at top level - Perhaps you intended to use TemplateHaskell + Parse error: module header, import declaration + or top-level declaration expected. From git at git.haskell.org Thu Jul 7 15:12:24 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 7 Jul 2016 15:12:24 +0000 (UTC) Subject: [commit: ghc] master: Add Note [FamInstEnv determinism] (64bce8c) Message-ID: <20160707151224.456793A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/64bce8c31450d846cf1a1ca4ff31ec6c724f2e46/ghc >--------------------------------------------------------------- commit 64bce8c31450d846cf1a1ca4ff31ec6c724f2e46 Author: Bartosz Nitka Date: Thu Jul 7 08:12:05 2016 -0700 Add Note [FamInstEnv determinism] I'm just turning previous commit message into a Note GHC Trac: #4012 >--------------------------------------------------------------- 64bce8c31450d846cf1a1ca4ff31ec6c724f2e46 compiler/types/FamInstEnv.hs | 14 ++++++++++++++ 1 file changed, 14 insertions(+) diff --git a/compiler/types/FamInstEnv.hs b/compiler/types/FamInstEnv.hs index c860dbc..d2fb520 100644 --- a/compiler/types/FamInstEnv.hs +++ b/compiler/types/FamInstEnv.hs @@ -359,10 +359,23 @@ Then we get a data type for each instance, and an axiom: These two axioms for T, one with one pattern, one with two; see Note [Eta reduction for data families] + +Note [FamInstEnv determinism] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +We turn FamInstEnvs into a list in some places that don't directly affect +the ABI. That happens in family consistency checks and when producing output +for `:info`. Unfortunately that nondeterminism is nonlocal and it's hard +to tell what it affects without following a chain of functions. It's also +easy to accidentally make that nondeterminism affect the ABI. Furthermore +the envs should be relatively small, so it should be free to use deterministic +maps here. Testing with nofib and validate detected no difference between +UniqFM and UniqDFM. +See Note [Deterministic UniqFM]. -} type FamInstEnv = UniqDFM FamilyInstEnv -- Maps a family to its instances -- See Note [FamInstEnv] + -- See Note [FamInstEnv determinism] type FamInstEnvs = (FamInstEnv, FamInstEnv) -- External package inst-env, Home-package inst-env @@ -385,6 +398,7 @@ emptyFamInstEnv = emptyUDFM famInstEnvElts :: FamInstEnv -> [FamInst] famInstEnvElts fi = [elt | FamIE elts <- eltsUDFM fi, elt <- elts] + -- See Note [FamInstEnv determinism] familyInstances :: (FamInstEnv, FamInstEnv) -> TyCon -> [FamInst] familyInstances (pkg_fie, home_fie) fam From git at git.haskell.org Thu Jul 7 15:40:56 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 7 Jul 2016 15:40:56 +0000 (UTC) Subject: [commit: ghc] wip/T10613: Pretty print reasons for Many (8bc7393) Message-ID: <20160707154056.A5AF43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T10613 Link : http://ghc.haskell.org/trac/ghc/changeset/8bc7393a6b2630b76096238f1c2622697367d8a9/ghc >--------------------------------------------------------------- commit 8bc7393a6b2630b76096238f1c2622697367d8a9 Author: Joachim Breitner Date: Wed Jul 6 15:44:07 2016 +0200 Pretty print reasons for Many >--------------------------------------------------------------- 8bc7393a6b2630b76096238f1c2622697367d8a9 compiler/basicTypes/Demand.hs | 7 +++---- 1 file changed, 3 insertions(+), 4 deletions(-) diff --git a/compiler/basicTypes/Demand.hs b/compiler/basicTypes/Demand.hs index c8d42b0..03be236 100644 --- a/compiler/basicTypes/Demand.hs +++ b/compiler/basicTypes/Demand.hs @@ -377,8 +377,7 @@ data Count = One | Many ManyReasons -- Pretty-printing instance Outputable ArgUse where ppr Abs = char 'A' - ppr (Use (Many _) a) = ppr a - ppr (Use One a) = char '1' <> char '*' <> ppr a + ppr (Use c a) = ppr c <> char '*' <> ppr a instance Outputable UseDmd where ppr Used = char 'U' @@ -388,7 +387,7 @@ instance Outputable UseDmd where instance Outputable Count where ppr One = char '1' - ppr (Many _) = text "" + ppr (Many mr) = text "ω" <> parens (hcat (punctuate (char ',') (map text mr))) useBot, useTop :: ArgUse useBot = Abs @@ -761,7 +760,7 @@ oneifyDmd jd = jd isTopDmd :: Demand -> Bool -- Used to suppress pretty-printing of an uninformative demand -isTopDmd (JD {sd = Lazy, ud = Use (Many _) Used}) = True +isTopDmd (JD {sd = Lazy, ud = Use (Many _) Used}) = False -- True isTopDmd _ = False isAbsDmd :: Demand -> Bool From git at git.haskell.org Thu Jul 7 20:34:42 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 7 Jul 2016 20:34:42 +0000 (UTC) Subject: [commit: ghc] master: Utils: Fix `lengthIs` and `lengthExceeds` for negative args (6e280c2) Message-ID: <20160707203442.9ADA53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6e280c2c5b2903ae38f4da15a41ea94793907407/ghc >--------------------------------------------------------------- commit 6e280c2c5b2903ae38f4da15a41ea94793907407 Author: Ömer Sinan Ağacan Date: Thu Jul 7 20:01:47 2016 +0000 Utils: Fix `lengthIs` and `lengthExceeds` for negative args Credits goes to SPJ for finding this. >--------------------------------------------------------------- 6e280c2c5b2903ae38f4da15a41ea94793907407 compiler/utils/Util.hs | 21 +++++++++++++++------ 1 file changed, 15 insertions(+), 6 deletions(-) diff --git a/compiler/utils/Util.hs b/compiler/utils/Util.hs index ff0f45f..d20a604 100644 --- a/compiler/utils/Util.hs +++ b/compiler/utils/Util.hs @@ -443,9 +443,9 @@ atLength :: ([a] -> b) -- Called when length ls >= n, passed (drop n ls) -> [a] -> Int -> b -atLength atLenPred atEnd ls n - | n < 0 = atLenPred ls - | otherwise = go n ls +atLength atLenPred atEnd ls0 n0 + | n0 < 0 = atLenPred ls0 + | otherwise = go n0 ls0 where -- go's first arg n >= 0 go 0 ls = atLenPred ls @@ -454,15 +454,24 @@ atLength atLenPred atEnd ls n -- Some special cases of atLength: +-- | @(lengthExceeds xs n) = (length xs > n)@ lengthExceeds :: [a] -> Int -> Bool --- ^ > (lengthExceeds xs n) = (length xs > n) -lengthExceeds = atLength notNull False +lengthExceeds lst n + | n < 0 + = True + | otherwise + = atLength notNull False lst n lengthAtLeast :: [a] -> Int -> Bool lengthAtLeast = atLength (const True) False +-- | @(lengthIs xs n) = (length xs == n)@ lengthIs :: [a] -> Int -> Bool -lengthIs = atLength null False +lengthIs lst n + | n < 0 + = False + | otherwise + = atLength null False lst n listLengthCmp :: [a] -> Int -> Ordering listLengthCmp = atLength atLen atEnd From git at git.haskell.org Fri Jul 8 10:55:31 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 8 Jul 2016 10:55:31 +0000 (UTC) Subject: [commit: packages/array] master: Update a testcase before GHC change (049db4a) Message-ID: <20160708105531.658503A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/array On branch : master Link : http://git.haskell.org/packages/array.git/commitdiff/049db4ac25dd8d21b3a1bba6fe6dfab05d0e3d46 >--------------------------------------------------------------- commit 049db4ac25dd8d21b3a1bba6fe6dfab05d0e3d46 Author: Bartosz Nitka Date: Fri Jul 8 03:57:03 2016 -0700 Update a testcase before GHC change Changing InstEnv to UniqDFM changes the order some things get printed >--------------------------------------------------------------- 049db4ac25dd8d21b3a1bba6fe6dfab05d0e3d46 tests/T9220.stdout | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/tests/T9220.stdout b/tests/T9220.stdout index 71582f2..7513284 100644 --- a/tests/T9220.stdout +++ b/tests/T9220.stdout @@ -5,6 +5,10 @@ data Data.Array.Base.UArray i e {-# UNPACK #-}Int GHC.Prim.ByteArray# -- Defined in ‘Data.Array.Base’ +instance (GHC.Arr.Ix ix, Show ix, Show e, + Data.Array.Base.IArray Data.Array.Base.UArray e) => + Show (Data.Array.Base.UArray ix e) + -- Defined in ‘Data.Array.Base’ instance (GHC.Arr.Ix ix, Eq e, Data.Array.Base.IArray Data.Array.Base.UArray e) => Eq (Data.Array.Base.UArray ix e) @@ -13,10 +17,6 @@ instance (GHC.Arr.Ix ix, Ord e, Data.Array.Base.IArray Data.Array.Base.UArray e) => Ord (Data.Array.Base.UArray ix e) -- Defined in ‘Data.Array.Base’ -instance (GHC.Arr.Ix ix, Show ix, Show e, - Data.Array.Base.IArray Data.Array.Base.UArray e) => - Show (Data.Array.Base.UArray ix e) - -- Defined in ‘Data.Array.Base’ type role Data.Array.IO.Internals.IOUArray nominal nominal newtype Data.Array.IO.Internals.IOUArray i e = Data.Array.IO.Internals.IOUArray (Data.Array.Base.STUArray From git at git.haskell.org Fri Jul 8 11:04:25 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 8 Jul 2016 11:04:25 +0000 (UTC) Subject: [commit: ghc] master: Use UniqDFM for InstEnv (0481324) Message-ID: <20160708110425.278C53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/04813246f2279bbdb4dc3c268b98f097c62d098b/ghc >--------------------------------------------------------------- commit 04813246f2279bbdb4dc3c268b98f097c62d098b Author: Bartosz Nitka Date: Thu Jul 7 07:56:49 2016 -0700 Use UniqDFM for InstEnv Rationale in the comment. Also updates submodule array with test output changes. GHC Trac: #4012 >--------------------------------------------------------------- 04813246f2279bbdb4dc3c268b98f097c62d098b compiler/types/InstEnv.hs | 33 +++++++++++++++++++-------- libraries/array | 2 +- testsuite/tests/ghci/scripts/T4175.stdout | 26 ++++++++++----------- testsuite/tests/ghci/scripts/T7627.stdout | 18 +++++++-------- testsuite/tests/ghci/scripts/T8469.stdout | 6 ++--- testsuite/tests/ghci/scripts/T8535.stdout | 6 ++--- testsuite/tests/ghci/scripts/T9881.stdout | 16 ++++++------- testsuite/tests/ghci/scripts/ghci011.stdout | 32 +++++++++++++------------- testsuite/tests/ghci/scripts/ghci020.stdout | 6 ++--- testsuite/tests/ghci/should_run/T10145.stdout | 6 ++--- 10 files changed, 83 insertions(+), 68 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 04813246f2279bbdb4dc3c268b98f097c62d098b From git at git.haskell.org Fri Jul 8 13:02:14 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 8 Jul 2016 13:02:14 +0000 (UTC) Subject: [commit: ghc] master: OccName: Implement startsWithUnderscore in terms of headFS (fc53d36) Message-ID: <20160708130214.6967E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/fc53d3658ad87073fbdc080f05ad3ac01d1ec59a/ghc >--------------------------------------------------------------- commit fc53d3658ad87073fbdc080f05ad3ac01d1ec59a Author: Ben Gamari Date: Fri Jul 8 14:09:36 2016 +0200 OccName: Implement startsWithUnderscore in terms of headFS This avoids decoding the entire string just to look at the first character. Test Plan: Validate Reviewers: austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2388 >--------------------------------------------------------------- fc53d3658ad87073fbdc080f05ad3ac01d1ec59a compiler/basicTypes/OccName.hs | 4 +--- 1 file changed, 1 insertion(+), 3 deletions(-) diff --git a/compiler/basicTypes/OccName.hs b/compiler/basicTypes/OccName.hs index 6a5c489..caaf90b 100644 --- a/compiler/basicTypes/OccName.hs +++ b/compiler/basicTypes/OccName.hs @@ -521,9 +521,7 @@ parenSymOcc occ doc | isSymOcc occ = parens doc startsWithUnderscore :: OccName -> Bool -- ^ Haskell 98 encourages compilers to suppress warnings about unsed -- names in a pattern if they start with @_@: this implements that test -startsWithUnderscore occ = case occNameString occ of - ('_' : _) -> True - _other -> False +startsWithUnderscore occ = headFS (occNameFS occ) == '_' {- ************************************************************************ From git at git.haskell.org Fri Jul 8 13:02:17 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 8 Jul 2016 13:02:17 +0000 (UTC) Subject: [commit: ghc] master: GHC.Stack.CCS: Fix typo in Haddocks (b8cd94d) Message-ID: <20160708130217.2AC123A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b8cd94d631ccccf7c94dda2eceb39650faf7d568/ghc >--------------------------------------------------------------- commit b8cd94d631ccccf7c94dda2eceb39650faf7d568 Author: Ben Gamari Date: Thu Jul 7 19:42:46 2016 +0200 GHC.Stack.CCS: Fix typo in Haddocks >--------------------------------------------------------------- b8cd94d631ccccf7c94dda2eceb39650faf7d568 libraries/base/GHC/Stack/CCS.hsc | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/base/GHC/Stack/CCS.hsc b/libraries/base/GHC/Stack/CCS.hsc index bab9f75..51eb624 100644 --- a/libraries/base/GHC/Stack/CCS.hsc +++ b/libraries/base/GHC/Stack/CCS.hsc @@ -82,7 +82,7 @@ ccSrcSpan p = (# peek CostCentre, srcloc) p -- | Returns a @[String]@ representing the current call stack. This -- can be useful for debugging. -- --- The implementation uses the call-stack simulation maintined by the +-- The implementation uses the call-stack simulation maintained by the -- profiler, so it only works if the program was compiled with @-prof@ -- and contains suitable SCC annotations (e.g. by using @-fprof-auto@). -- Otherwise, the list returned is likely to be empty or From git at git.haskell.org Fri Jul 8 13:02:19 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 8 Jul 2016 13:02:19 +0000 (UTC) Subject: [commit: ghc] master: FastString: Reduce allocations of concatFS (91fd87e) Message-ID: <20160708130219.C9F6C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/91fd87e2384091f1872f91953e83b299d8e1478f/ghc >--------------------------------------------------------------- commit 91fd87e2384091f1872f91953e83b299d8e1478f Author: Ben Gamari Date: Mon Jul 4 20:33:57 2016 -0400 FastString: Reduce allocations of concatFS Instead of unpacking and then repacking we simply concatenate all of the individual ByteStrings. >--------------------------------------------------------------- 91fd87e2384091f1872f91953e83b299d8e1478f compiler/utils/FastString.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/utils/FastString.hs b/compiler/utils/FastString.hs index 237c0a2..41889cf 100644 --- a/compiler/utils/FastString.hs +++ b/compiler/utils/FastString.hs @@ -512,7 +512,7 @@ appendFS fs1 fs2 = mkFastStringByteString (fastStringToByteString fs2) concatFS :: [FastString] -> FastString -concatFS ls = mkFastString (Prelude.concat (map unpackFS ls)) -- ToDo: do better +concatFS = mkFastStringByteString . BS.concat . map fs_bs headFS :: FastString -> Char headFS (FastString _ 0 _ _) = panic "headFS: Empty FastString" From git at git.haskell.org Fri Jul 8 13:02:22 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 8 Jul 2016 13:02:22 +0000 (UTC) Subject: [commit: ghc] master: FastString: Supply mconcat implementation (c4a9dca) Message-ID: <20160708130222.75BD83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c4a9dcad885a7bbe0f60b7bef39a7d1789eae5e9/ghc >--------------------------------------------------------------- commit c4a9dcad885a7bbe0f60b7bef39a7d1789eae5e9 Author: Ben Gamari Date: Fri Jul 8 14:09:09 2016 +0200 FastString: Supply mconcat implementation Test Plan: Validate Reviewers: austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2389 >--------------------------------------------------------------- c4a9dcad885a7bbe0f60b7bef39a7d1789eae5e9 compiler/utils/FastString.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/compiler/utils/FastString.hs b/compiler/utils/FastString.hs index 490eb13..651719a 100644 --- a/compiler/utils/FastString.hs +++ b/compiler/utils/FastString.hs @@ -198,6 +198,7 @@ instance IsString FastString where instance Monoid FastString where mempty = nilFS mappend = appendFS + mconcat = concatFS instance Show FastString where show fs = show (unpackFS fs) From git at git.haskell.org Fri Jul 8 13:02:25 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 8 Jul 2016 13:02:25 +0000 (UTC) Subject: [commit: ghc] master: FastString: Add IsString instance (15751f2) Message-ID: <20160708130225.311903A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/15751f265d34d797c48270773bdd1a8e77e400bc/ghc >--------------------------------------------------------------- commit 15751f265d34d797c48270773bdd1a8e77e400bc Author: Ben Gamari Date: Tue Jul 5 06:06:29 2016 -0400 FastString: Add IsString instance >--------------------------------------------------------------- 15751f265d34d797c48270773bdd1a8e77e400bc compiler/utils/FastString.hs | 3 +++ 1 file changed, 3 insertions(+) diff --git a/compiler/utils/FastString.hs b/compiler/utils/FastString.hs index 41889cf..490eb13 100644 --- a/compiler/utils/FastString.hs +++ b/compiler/utils/FastString.hs @@ -192,6 +192,9 @@ instance Ord FastString where | otherwise = y compare a b = cmpFS a b +instance IsString FastString where + fromString = fsLit + instance Monoid FastString where mempty = nilFS mappend = appendFS From git at git.haskell.org Fri Jul 8 14:11:07 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 8 Jul 2016 14:11:07 +0000 (UTC) Subject: [commit: ghc] wip/T12357-built-in-map: TysWiredIn: Use map lookup for built-in OccNames (83e899a) Message-ID: <20160708141107.79B253A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T12357-built-in-map Link : http://ghc.haskell.org/trac/ghc/changeset/83e899a8bbd4240cfde019c8cb71e0c5efeb02f2/ghc >--------------------------------------------------------------- commit 83e899a8bbd4240cfde019c8cb71e0c5efeb02f2 Author: Ben Gamari Date: Mon Jul 4 21:09:55 2016 -0400 TysWiredIn: Use map lookup for built-in OccNames >--------------------------------------------------------------- 83e899a8bbd4240cfde019c8cb71e0c5efeb02f2 compiler/prelude/TysWiredIn.hs | 52 ++++++++++++++++++++---------------------- 1 file changed, 25 insertions(+), 27 deletions(-) diff --git a/compiler/prelude/TysWiredIn.hs b/compiler/prelude/TysWiredIn.hs index 51f5555..4c3fd38 100644 --- a/compiler/prelude/TysWiredIn.hs +++ b/compiler/prelude/TysWiredIn.hs @@ -134,6 +134,7 @@ import {-# SOURCE #-} ConLike import TyCon import Class ( Class, mkClass ) import RdrName +import UniqFM import Name import NameSet ( NameSet, mkNameSet, elemNameSet ) import BasicTypes ( Arity, Boxity(..), @@ -635,39 +636,36 @@ decl in GHC.Classes, so I think this part may not work properly. But it's unused I think. -} -isBuiltInOcc_maybe :: OccName -> Maybe Name --- Built in syntax isn't "in scope" so these OccNames --- map to wired-in Names with BuiltInSyntax -isBuiltInOcc_maybe occ - = case occNameString occ of - "[]" -> choose_ns listTyConName nilDataConName - ":" -> Just consDataConName - "[::]" -> Just parrTyConName - "()" -> tup_name Boxed 0 - "(##)" -> tup_name Unboxed 0 - '(':',':rest -> parse_tuple Boxed 2 rest - '(':'#':',':rest -> parse_tuple Unboxed 2 rest - _other -> Nothing +builtInOccNames :: UniqFM (OccName -> Name) +builtInOccNames = listToUFM $ + [ (fsLit "[]", choose_ns listTyConName nilDataConName) + , (fsLit ":" , const consDataConName) + , (fsLit "[::]", const parrTyConName) + , (fsLit "()", tup_name Boxed 0) + , (fsLit "(##)", tup_name Unboxed 0) + ] ++ + [ (fsLit $ "("++replicate n ','++")", tup_name Boxed (n+1)) | n <- [1..62] ] ++ + [ (fsLit $ "(#"++replicate n ','++"#)", tup_name Unboxed (n+1)) | n <- [1..62] ] where - ns = occNameSpace occ - - parse_tuple sort n rest - | (',' : rest2) <- rest = parse_tuple sort (n+1) rest2 - | tail_matches sort rest = tup_name sort n - | otherwise = Nothing - - tail_matches Boxed ")" = True - tail_matches Unboxed "#)" = True - tail_matches _ _ = False + choose_ns :: Name -> Name -> OccName -> Name + choose_ns tc dc occ + | isTcClsNameSpace ns = tc + | isDataConNameSpace ns = dc + | otherwise = pprPanic "tup_name" (ppr occ) + where ns = occNameSpace occ tup_name boxity arity = choose_ns (getName (tupleTyCon boxity arity)) (getName (tupleDataCon boxity arity)) - choose_ns tc dc - | isTcClsNameSpace ns = Just tc - | isDataConNameSpace ns = Just dc - | otherwise = pprPanic "tup_name" (ppr occ) + +isBuiltInOcc_maybe :: OccName -> Maybe Name +-- Built in syntax isn't "in scope" so these OccNames +-- map to wired-in Names with BuiltInSyntax +isBuiltInOcc_maybe occ + = case lookupUFM builtInOccNames occ of + Just f -> Just (f occ) + Nothing -> Nothing mkTupleOcc :: NameSpace -> Boxity -> Arity -> OccName -- No need to cache these, the caching is done in mk_tuple From git at git.haskell.org Fri Jul 8 14:11:10 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 8 Jul 2016 14:11:10 +0000 (UTC) Subject: [commit: ghc] wip/T12357-built-in-map: DsExpr: Remove unnecessary usage of concatFS (5446684) Message-ID: <20160708141110.2B5923A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T12357-built-in-map Link : http://ghc.haskell.org/trac/ghc/changeset/54466843f309aa31c41ceebb0f59410dc40e5e80/ghc >--------------------------------------------------------------- commit 54466843f309aa31c41ceebb0f59410dc40e5e80 Author: Ben Gamari Date: Fri Jul 8 16:14:29 2016 +0200 DsExpr: Remove unnecessary usage of concatFS Producing a FastString and then immediately unpacking it is rather silly >--------------------------------------------------------------- 54466843f309aa31c41ceebb0f59410dc40e5e80 compiler/deSugar/DsExpr.hs | 10 ++++------ 1 file changed, 4 insertions(+), 6 deletions(-) diff --git a/compiler/deSugar/DsExpr.hs b/compiler/deSugar/DsExpr.hs index 85177ee..b01b0e6 100644 --- a/compiler/deSugar/DsExpr.hs +++ b/compiler/deSugar/DsExpr.hs @@ -470,12 +470,10 @@ dsExpr (HsStatic _ expr@(L loc _)) = do mkStaticPtrFingerprint :: Module -> DsM Fingerprint mkStaticPtrFingerprint this_mod = do n <- mkGenPerModuleNum this_mod - return $ fingerprintString $ unpackFS $ concatFS - [ unitIdFS $ moduleUnitId this_mod - , fsLit ":" - , moduleNameFS $ moduleName this_mod - , fsLit ":" - , mkFastString $ show n + return $ fingerprintString $ intercalate ":" + [ unitIdString $ moduleUnitId this_mod + , moduleNameString $ moduleName this_mod + , show n ] mkGenPerModuleNum :: Module -> DsM Int From git at git.haskell.org Fri Jul 8 14:11:24 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 8 Jul 2016 14:11:24 +0000 (UTC) Subject: [commit: ghc] wip/T12357-built-in-map's head updated: DsExpr: Remove unnecessary usage of concatFS (5446684) Message-ID: <20160708141124.8E4EF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/T12357-built-in-map' now includes: a607011 Test Trac #10348 77e5ec8 Demonstrate that inferring Typeable for type literals works efa136f Remove derived CFunEqCans after solving givens a3f6239 GHCi: fix scoping for record selectors a6cbf41 Spelling in comments 855f56b Improved peak_megabytes_allocated 2613271 Testsuite: fix framework failure 89c7168 Fix #10534 df63736 ghc.mk: Update instances of -auto-all 1ff7f09 Lexer: Suggest adding 'let' on unexpected '=' token 0d6c97b Lexer: Suggest adding 'let' on unexpected '=' token a90712b users_guide: Various spelling fixes d46fdf2 users_guide: Various spelling fixes 681973c Encode alignment in MO_Memcpy and friends a0d158f Encode alignment in MO_Memcpy and friends c772f57 Fix #10494 0de0b14 Fix #10495. ace8d4f Fix #10493. 6644039 Test case for #10428. ff82387 Decompose wanted repr. eqs. when no matchable givens. 93f97be (mostly) Comments only f108003 Testsuite wibble around decomposing newtypes. 7eceffb Refactor handling of decomposition. 9b105c6 Reimplement Unify.typesCantMatch in terms of apartness. 298c424 Treat funTyCon like any other TyCon in can_eq_nc. a6b8b9c Fix typo in comment daf1eee Clarify some comments around injectivity. 65d4b89 Add `Monoid` instance for `IO` f063656 Fix ghc-pkg reports cache out date (#10205) 0760b84 Update foreign export docs, fixes #10467 b98ca17 Make enum01/enum02/enum03 tests clang-compatible 023a0ba Care with impossible-cons in combineIdenticalAlts 5879d5a Report arity errors correctly despite kinds f4370c6 Comments only 4a7a6c3 Rename getCtLoc, setCtLoc 02bac02 Remove some horrible munging of origins for Coercible 760b079 A bit more tracing 0899911 Comments plus tiny refactoring ee64369 Refactor filterAlts into two parts 5d98b68 Trac #4945 is working again 72b21c3 Parser: commas_tup_tail duplicate SrcSpan on "Missing" value ba7c8e5 Test Trac #10503 c45f8ce Elaborate test for Trac #10403 40698fe Spelling in comments e283cec testsuite: mark T4945 as expect_broken 440d1bc docs: Unbreak the PS/PDF builds for the User's Guide (#10509) 7d5a845 should_run/allocLimit4: disable ghci way e491803 Amend tcrun024, tcrun025 after Trac #7854 fix 7c2293a Amend tcrun037 after Trac #7854 fix 2c6a041 Fix a couple of tests for GHCi/-O* (Trac #10052) 5cc08eb Recognise 'hardhloat' as a valid vendor in a host tuple f2ffdc6 Updated output for test ghci024 85d5397 Make GHC install libraries to e.g. xhtml-3000.2.1-0ACfOp3hebWD9jGWE4v4Gh. 0cb1f5c Filter orphan rules based on imports, fixes #10294 and #10420. 29bc13a Fix all.T for T8131/T8131b. 15ef5fc Remove duplicate test. 13ba87f Build system: unset HADDOCK when haddock is not found 4854fce Change `Typeable` instance for type-lis to use the Known* classes. 38f3745 Add parsePattern parser entry point b5a2e87 Documentation: add section on .haskeline file (#2531) e60dbf3 Check KnownSymbol => Typeable deduction f70fb68 Use -package-id to specify libraries on command line. 6c5a66a Fix #10551 by using LIB_NAMES. 01f7e44 Rename $1_$2_$3_LIB_NAME to LIB_FILE. 55843f1 Further elaborate Trac #10403 test c084796 powerpc: add basic support for PLT relocations (#10402) 73a6265 Make $1 in $1_$2_$3_FOO actually be directory. 95d5031 Build system: delete unused variables in config.mk.in ece2c43 Drop prefix from package keys. aa26731 Clean outdated ext-core references in comments. 4d1316a driver: pass '-fPIC' option to all CC invocations 9a34864 Improve kind-checking for 'deriving' clauses c7b6fb5 Test Trac #10562 a2f828a Be aware of overlapping global STG registers in CmmSink (#10521) a7eee0d Comments only 3edc186 White space only 9195927 Improve pretty-printing for CoPat ff8a671 Use a Representaional coercion for data families 0b7e538 Allow recursive unwrapping of data families cc0dba1 Minor fix to free-vars in RnTypes 9014a7e Fix addDataConStrictness b69dc73 Don't float out alpha[sig] ~ Int 97e313c Add module header to test 2f16a3b Get rid of irrlevant result type signature 95fc6d5 Get rid of irrelevant impredicative polymoprhism fb7b692 Treat out-of-scope variables as holes b98ff25 Error message wibbles from out-of-scope changes 0aaea5b Tiny refactor plus comments be0ce87 Fix for crash in setnumcapabilities001 111ba4b Fix deadlock (#10545) 7c8ffd3 GHCi docs: layout rule is respected inside :{ :} cbd9278 Comments only caf9d42 Small doc fixes 0696fc6 Improve CPR behavior for strict constructors 7c07cf1 closeOverKinds *before* oclose in coverage check 614ba3c Kill off sizePred 8e34783 Make fvType ignore kinds a64a26f Better tracing and tiny refactoring ceb3c84 Improve error message for Typeable k (T k) 0e1e798 Test Trac #10524 8d221bb Test #10582 89834d6 Add -fcross-module-specialise flag 302d937 Add -fcross-module-specialise flag bb0e462 Mask to avoid uncaught ^C exceptions 9b5df2a Update performance numbers due to #10482 c6bb2fc Correct BangPat SrcSpan calculation c495c67 Build system: remove unused variable CHECK_PACKAGES 897a46c Testsuite: accept T2592.stderr (minor changes) 6b9fc65 Testsuite: put extra_run_opts last on command line daa5097 Build system: prevent "warning: overriding commands for target..." bbf6078 disable check for .init_array section on OpenBSD 9aa0e4b ghc-pkg: use read/writeUTF8File from Cabal bdd0b71 bin-package-db: copy paste writeFileAtomic from Cabal bdf7f13 Build system: rename bindist to bindist-list... d3c1dda Implement PowerPC 64-bit native code backend for Linux b5e1944 Use `+RTS -G1` for more stable residency measurements (#9675) 1d6ead7 Enable using qualified field of constructor in GHCi f856383 Fix Trac #10519 f07b7a8 Remove unnecessary OrdList from decl parser. 6400c76 users_guide: Describe order-dependence of -f and -O flags e4bf4bf Remove redundant parser entry point 8b55788 Add "since" column for LANGUAGE extensions in user guide 39d83f2 Generalize traceM, traceShowM (fixes #10023) 6b01d3c parser: Allow Lm (MODIFIER LETTER) category in identifiers 889c81c Fix some validation errors. 69beef5 Replace usages of `-w` by `-fno-warn`s b1d1c65 Support MO_{Add,Sub}IntC and MO_Add2 in the LLVM backend 124f399 Testsuite: add -ignore-dot-ghci to some tests ced27de Remove dead code / overlapping pattern (#9723) a4b0342 Lexer: remove -fno-warn-unused-do-bind aa778c8 Comments only [skip ci] c875b08 Use -fno-warn-unused-imports instead of hiding `ord` 8e12a21 Lexer.x and Parser.y: delete dead code 5d48e67 Easy way to defer type errors (implements #8353) 3fabb71 Fix typo [skip ci] (#10605) 75de613 rts: fix incorrect checking start for -x arguments (#9839) edb2c54 Remove Hugs specific test setups (omit_compiler_type) 7a3d85e Remove all *.stderr/stdout-hugs files 4681f55 Specialise: Avoid unnecessary recomputation of free variable information 2765fcf Remove warnings for -fwarn-incomplete-patterns a07898e Spelling in comments 9180df1 Fix offset calculation in __stg_gc_fun aaa0cd2 Don't eagerly blackhole single-entry thunks (#10414) d27e7fd Add more discussion of black-holing logic for #10414 d59cf4e Fix "CPP directive" in comment db530f1 Add Note [Warnings in code generated by Alex] 37de4ad Build system: don't set GhcLibWays explicitly in build.mk.sample (#10536) 62fcf05 Fix word repetitions in comments ebfc2fb Update comments around blackholes f753cf1 Allow deferred type error warnings to be suppressed 31580e2 Fix todo in compiler/nativeGen: Rename Size to Format 9a3e165 Deferred type errors now throw TypeError (#10284) 5857e0a fix EBADF unqueueing in select backend (Trac #10590) 6d69c3a Generalize `Control.Monad.forever` d03bcfa always use -fPIC on OpenBSD/AMD64 platform 00c8d4d Fix #10596 by looking up 'Int' not 'Maybe Int' in the map. 1967a52 Export more types from GHC.RTS.Flags (#9970) 8800a73 Backpack: Flesh out more Cabal details d71b65f holePackageKey and isHoleModule utility functions. 3d5f8e7 Unbreak Windows build: delete unusud throwIOIO 6f9efcb Delete duplicate "Note [Unpack equality predicates]" f3bfa3b Broaden Outputable instance for Termination 85b14a7 Comments only 4f9d600 Fix Trac #10618 (out of scope operator) b29633f Bitmap: Fix thunk explosion 889824d Document RULES and class methods c58dc1a White space only b5aabfb Infer types with flexible contexts 7dcf86f users_guide: Fix errant "a" in RULES/class methods docs a6359f2 Add testcase for #10602 6f1c076 Make mkQualPackage more robust when package key is bad. 0a3c43f Comments only 9e86bf1 Better type wildcard errors 888026d Update .mailmap [skip ci] 2d06a9f Improve error message for fundeps 9b1ebba Delete the WayPar way d69dfba Fix self-contained handling of ASCII encoding ee28a79 T1969: Update max_bytes_used a846088 T876 (32-bit): Update bytes allocated de6597e perf/compiler: Switch to -G1 and update performance metrics b935497 T9872d: Update 32-bit allocations d073c77 Do not optimise RULE lhs in substRule e922847 Add Linting for Rules 7da7b0e Make sure rule LHSs are simplified 875723b Reformat a leading # in a comment d7335f7 Test Trac #10463 02a6b29 Test Trac #10634 946c8b1 Another comment with a leading # (sigh) 2e52057 Build system: comments only [skip ci] ec197d3 Build system: add `make show!` command (#7810) f70f1b6 Build system: delete two unused files 47ebe26 Build system: delete REGULAR_INSTALL_DYNLIBS and INSTALL_DYNLIBS 392ff06 Build system: do not build stm and parallel by default 5764ade Testsuite: delete unused with_namebase 322ae32 Testsuite: delete remaining only_compiler_types(['ghc']) setups 783b79b traivs: Use the new container based travis setup 4dc3877 Testsuite: rename *.stderr-ghc to *.stderr ab5257b Testsuite: delete *.stderr-ghc-7.0 *.stdout-ghc-7.0 4ee658a0 Mark test case for #10294 expect_broken on #10301 0a40278 Flush stdout in test case for #10596 8e6a503 Mark test case for #10294 conditionally expect_broken on #10301 b1063b1 Testsuite: mark T10294 conditionally expect_broken on #10301 348f5ca Build system: delete fingerprint.py [skip ci] a592e9f Remove all references to sync-all 75fd5dc Don't get a new nursery if we exceeded large_alloc_lim 9f978b6 Fix #10642. 74a00bc initGroup: only initialize the first and last blocks of a group 504c2ae Docs: `sortOn = sortBy (comparing f)` [skip ci] 02897c5 Failing test case: idArity invariant check, #10181 e29c2ac CoreUtils: Move seq* functions to CoreSeq ae0e340 CoreUtils: Move size utilities to CoreStats fa33f45 PprCore: Add size annotations for top-level bindings 29f8225 CoreLint: Use size-annotated ppr variant 82f1c78 Fix tests ae96c75 Implement -fprint-expanded-synonyms 415351a Put Opt_Static into defaultFlags if not pc_DYNAMIC_BY_DEFAULT (#7478) 2c5c297 DeriveFoldable for data types with existential constraints (#10447) 2c9de9c Handle Char#, Addr# in TH quasiquoter (fixes #10620) a5e9da8 Fix off-by-one error in GHCi line reporting (Trac #10578) 3448f98 Reduce non-determinism in ABI hashes with RULES and instance decls bc604bd Update assert to fix retc001 and retc002 (#9243) 0d4b074 Travis: actually do debug builds ac0feec Testsuite: small test cleanups f607393 Testsuite: accept new stderr for T9497{a,b,c}-run (#10224) a0371c0 Build system: fail when encountering an unknown package tag dc6e556 Testsuite: mark T2497 expect_broken_for(#10657, ['optasm', 'optllvm']) dcaa486 Testsuite: mark T7919 expect_broken_for(#7919, ['optasm','dyn','optllvm']) 11f8612 Testsuite: mark 3 tests expect_broken_for(#10181, ['optasm', 'optllvm']) 16a8739 Testsuite: mark qq007 and qq008 expect_broken(#10181) cbb4d78 Testsuite: mark qq007 and qq008 expect_broken(#10047) 43dafc9 Testsuite: mark gadt/termination expect_broken_for(#10658, ['optasm','optllvm']) 34bb460 Testsuite: mark array001 and conc034 expect_broken_for(#10659, ['optasm',...]) 9834fea Add regression test for unused implicit parameter warning (#10632) 4c96e7c Testsuite: add ImpredicativeTypes to T7861 (#7861) 7f37274 Testsuite: add -XUndecidableInstances to T3500a 029367e Testsuite: add regression test for missing class constraint 82ffc80 LlvmCodeGen: add support for MO_U_Mul2 CallishMachOp 49373ff Support wild cards in TH splices c526e09 primops: Add haddocks to BCO primops 4cd008b Do not treat prim and javascript imports as C imports in TH and QQ 96de809 Fix primops documentation syntax d71d9a9 Testsuite: fix concprog002 (AMP) 2f18b197 Testsuite: mark concprog002 expect_broken_for(#10661, ['threaded2_hT']) d0cf8f1 Testsuite: simplify T8089 (#8089) b4ef8b8 Update submodule hpc with fix for #10529 0c6c015 Revert "Revert "Change loadSrcInterface to return a list of ModIface"" 214596d Revert "Revert "Support for multiple signature files in scope."" 9ade087 primops: Fix spelling mistake e0a3c44 Delete __GLASGOW_HASKELL__ ifdefs for stage0 < 7.8 8f48fdc Use varToCoreExpr in mkWWcpr_help 3fbf496 Comments only (superclasses and improvement) 3509191 Refactor newSCWorkFromFlavoured 7c0fff4 Improve strictness analysis for exceptions cd48797 Comments and white space only 3c44a46 Refactor self-boot info efa7b3a Add NOINLINE for hs-boot functions aa78cd6 Documents -dsuppress-unfoldings 0df2348 Comments and layout only a0e8bb7 Implement -dsuppress-unfoldings b5c1400 Comments and white space only f1d0480 Avoid out-of-scope top-level Ids 7a6ed66 Comments only 55754ea Fix test T2497 to avoid infinite loop in RULES feaa095 Do occurrence analysis on result of BuiltInRule 00f3187 Make seq-of-cast rule generate a case 35eb736 T4945 is working again f519cb5 testsuite: Show killed command line on timeout 97a50d5 configure: Bump minimum bootstrap GHC version to 7.8 dbe6dac When iconv is unavailable, use an ASCII encoding to encode ASCII 18c6ee2 Travis: use ghc-7.8.4 as stage0 to fix the build d941a89 Validate: by default do show commands a7e0326 Validate: document --quiet [skip ci] 1224bb5 Add utility function isHoleName. 50b9a7a Revert "Trac #4945 is working again" 1b76997 Testsuite: recenter haddock.base allocation numbers b949c96 Eliminate zero_static_objects_list() 0d1a8d0 Two step allocator for 64-bit systems e3df1b1 Validate: explain THREADS instead of CPUS in --help cf57f8f Travis: do pass `--quiet` to validate 0b12aca Switch from recording IsBootInterface to recording full HscSource. adea827 Add ExceptionMonad instance for IOEnv. 144096e Give more informative panic for checkFamInstConsistency. 4a9b40d Export alwaysQualifyPackages and neverQualifyPackages. 939f1b2 Some utility functions for testing IfaceType equality. dd365b1 Use lookupIfaceTop for loading IfaceDecls. 5c3fc92 Fix Trac #10670 9851275 Comments only d784bde Lexer: support consecutive references to Haddock chunks (#10398) d2b4df1 Generate .dyn_o files for .hsig files with -dynamic-too 76e2341 Accept next-docstrings on GADT constructors. e78841b Update encoding001 to test the full range of non-surrogate code points b5c9426 Parenthesise TypeOperator in import hints 1852c3d DataCon: Fix redundant import 4c8e69e rts/sm: Add missing argument names in function definitions 7ec07e4 Slight refactoring to the fix for #4012 608e76c Document type functions in the Paterson conditions e809ef5 ghci: fixity declarations for infix data constructors (#10018) 5ff4dad Add a few comments from SPJ on fixity declarations f9687ca Library names, with Cabal submodule update 45c319f Fix line number in T10018 testcase 30d8349 Comments only e161634 Comments about stricteness of catch# d53d808 Refactoring around FunDeps 6e618d7 Improve instanceCantMatch 09d0505 RetainerProfile: Add missing UNTAG_STATIC_LIST_PTR b04bed0 renamer: fix module-level deprecation message 070f76a -include-pkg-deps takes only one hyphen. 7e70c06 Use isTrue# around primitive comparisons in integer-gmp c55f61c Add missing parentheses in eqBigNatWord# 474d4cc Comment tweaks only f842ad6 Implementation of StrictData language extension 2178273 Add UInfixT to TH types (fixes #10522) 81fffc4 Remove runSTRep from PrelNames bc4b64c Do not inline or apply rules on LHS of rules 2d88a53 Improve warnings for rules that might not fire 09925c3 Revert "RetainerProfile: Add missing UNTAG_STATIC_LIST_PTR" a1e8620 Revert "Eliminate zero_static_objects_list()" e343c0a Test case for #10698 a1dd7dd Fallout from more assiduous RULE warnings f83aab9 Eliminate zero_static_objects_list() 2dbb01a Add a missing check for -fcpr-off fac11f8 Comments only 4e8d74d Deal with phantom type variables in rules 92d2567 Define DsUtils.mkCastDs and use it fa915af Spit out a little more info with -dppr-debug e4114c8 Fix an outright error in competesWith 499b926 Fix Trac #10694: CPR analysis 918dcf8 The parallel package has warnings 2e33b9c Modify spec002 to be less trivial 72d23c3 Better treatment of signatures in cls/inst 24afe6d Fix missing files 5a8a8a6 Don't allowInterrupt inside uninterruptibleMask 9f7cdfe Make configure error out on missing ghc-tarballs on Windows e7c331a Make headers C++ compatible (fixes #10700) 26315ed Fix misspelled function name in a comment 4f80ec0 Improve error message for newtypes and deriving clauses e9ad42d Typos in comments and strings d7c2b01 Fix comment that confused Haddock b5097fe Testsuite: rename rename/should_fail/T5001 to T5001b (#5001) e273c67 Testsuite: mark tests recently fixed as passing + accept new stderr 756fa0a Testsuite: skip T10489 unless compiler_debugged (#10489) 6880277 Testsuite: add arrows/should_compile/T5333 (#5333) 58b5f04 Testsuite: add typecheck/should_fail/T9260 (#9260) 58986c4 Testsuite: add typecheck/should_fail/T8034 (#8034) aee19d0 Testsuite: T10245 is passing for WAY=ghci (#10245) 36bbfbd Backpack docs on renamer and depsolver, also s/package/unit/. a442800 Build system: remove function keyword from configure.ac (#10705) a66e1ba User's guide: delete ancient "Core syntax" example 7cf87df Fix #7919 (again) 353db30 Remove checked-in PDFs. 8f81af9 Typos in comments ad089f5 Give raise# a return type of open kind (#10481) 75504f3 Typos in comments 15dd700 Replace (SourceText,FastString) with StringLiteral data type d9b618f Typo in comment 37227d3 Make BranchFlag a new kind 92f5385 Support MO_U_QuotRem2 in LLVM backend 948e03e Update parallel submodule, and re-enable warnings b38ee89 Fix incorrect stack pointer usage in StgRun() on x86_64 4d8859c Typos in comments d7ced09 Minor improvement to user guide 30b32f4 Test Trac #10134 697079f 4 reduce/reduce parser conflicts resolved d9d2102 Support wild cards in data/type family instances 7ec6ffc Typos in comments [skip ci] 64b6733 CmmParse: Don't force alignment in memcpy-ish operations 30c981e Removed deprecated syntax for GADT constuctors. f063bd5 Fix #10713. b5f1c85 Test #9233 in perf/compiler/T9233 d7b053a Pretty: reformat using style from libraries/pretty (#10735) 9d24b06 Pretty: rename variables to the ones used by libraries/pretty (#10735) 25bc406 Pretty: improve error messages (#10735) 53484d3 Pretty: remove superfluous parenthesis (#10735) 2d1eae2 Pretty: kill code that has been dead since 1997 (#10735) 6f6d082 Pretty: Args of NilAbove/TextBeside/Nest/Union are always RDocs (#10735) 926e428 Pretty: use BangPatterns instead of manual unboxing Ints (#10735) f951ffc Pretty: mimic pretty API more closely (#10735) 85179b5 Pretty: use replicate for spaces and multi_ch (#10735) dd7e188 Add framework flags when linking a dynamic library 4c55f14 users_guide: Add note about #367 to Bugs section 6029748 Drop custom mapM impl for [] ecb1752 Make -fcpr-off a dynamic flag b12dba7 Make Exception datatypes into newtypes 22bbc1c Make sure that `all`, `any`, `and`, and `or` fuse (#9848) fd6b24f Additions to users' guide and release notes 575abf4 Add Fixity info for infix types e2b5738 Allow proper errors/warnings in core2core passes 617f696 Do not complain about SPECIALISE for INLINE a426154 Warn about missed specialisations for imports 49615d9 Comments only ab98860 Minor refactor to use filterInScope 9536481 Tidy up and refactor wildcard handling 28096b2 Fix quantification for inference with sigs 75f5f23 Coments only cc07c40 Comments only 294553e T8968-1 and -3 should pass 64dba51 Test Trac #10742 eca9a1a Ensure DynFlags are consistent 97843d0 base: Add instances 600b153 llvmGen: Rework LLVM mangler aa23054 Add test for #10600 (exhaustiveness check with --make and -fno-code) bc43d23 Rejigger OSMem.my_mmap to allow building on Mac a1c934c base: Add missing Traversable instance for ZipList 6cab3af Big batch of Backpack documentation edits. 79e0a10 Test Trac #10753 a192d6b Comments only f1b4864 Sync base/changelog.md with GHC 7.10.2 release 590aa0f Make oneShot open-kinded 92f35cd cmmCreateSwitchPlan: Handle singletons up-front 2c4a7d3 Update transformers submodule to 0.4.3.0 release f04c7be Fix unused-matches warnings in CmmLex.x a40ec75 Update testsuite/.gitignore [skip ci] b4ed130 Replace HsBang type with HsSrcBang and HsImplBang 2da06d7 User manual update, as prodded by #10760. 2b4710b Add missing to User's guide to fix the build 8cce7e4 Bump template-haskell to new major version 2.11 67576dd Pretty: bugfix fillNB (#10735) bcfae08 Pretty: fix potential bad formatting of error message (#10735) 5d57087 Pretty: fix a broken invariant (#10735) 85bf76a Pretty: show rational as is (#10735) f903949 Pretty: improving the space/time performance of vcat, hsep, hcat (#10735) b0dee61 template-haskell: Add changelog entry to infix type operators 7b211b4 Upgrade GCC to 5.2.0 for Windows x86 and x86_64 e415369 Update mingw tarball location 8c5b087 SysTools: Fix whitespace in error message d2dd5af DynFlags: Prohibit hpc and byte-code interpreter ec68618 Name: Show NameSort in warning 1857191 Testsuite: mark T8089 expect_broken(#7325) on Windows 8906037 Testsuite: mark encoding005 expect_broken(#10623) on Windows ca85442 Testsuite: recenter 2 performance tests on Windows 744ff88 Testsuite: speedup running a single test e367e27 Travis: prevent 10' no output, by setting VERBOSE=2 74897de Make rts/ThreadLabels.c threadsafe for debug runtime. 22aca53 Transliterate unknown characters at output ab9403d Dump files always use UTF8 encoding #10762 b17ec56 Fix rdynamic flag and test on Windows ebca3f8 rts/Printer.c: speed up '-Da' printer for 'LIBBFD' build 18a1567 Add selectors for common fields (DataCon/PatSyn) to ConLike d97e60f Comments reformating/corrections b6be81b Build system: delete half-baked Cygwin support 98f8c9e Delete sync-all a146b28 GhcMake: Fix spelling in comment 0d0e651 Bag: Add Foldable instance 9e8562a Implement getSizeofMutableByteArrayOp primop 3452473 Delete FastBool 2f29ebb Refactor: delete most of the module FastTypes 47493e6 Build system: simplify install.mk.in a1c008b Build system: delete unused distrib/Makefile a5061a9 Check options before warning about source imports. 37a0b50 Delete ExtsCompat46 (#8330) b78494e fix 64bit two-stage allocator on Solaris/AMD64 platform (#10790) fba724c configure.ac: Allow disabling of large-address-space 1c643ba Fix algorithm.tex build and update with some new info. 0f3335f Comments and white space 816d48a Implement lookupGlobal in TcEnv, and use it 711e0bf tcRnDeclsi can use tcRnSrcDecls ac0d052 TcDeriv: Kill dead code de476e9 PrelNames: Clean up list a bit 89d25b9 BinIface: Clean up whitespace 7924469 Clean up handling of knownKeyNames a8601a8 Revert "Clean up handling of knownKeyNames" 28ad98e PrelNames: introduce dcQual in place of conName 211b349 Move newImplicitBinder to from IfaceEnv to BuildTyCl 70ea94c IfaceEnv: Clean up updNameCache a bit f6035bc MkIface: Introduce PatSynId, ReflectionId, DefMethId 7bd8f8f TysWiredIn: Shuffle code around 15c63d2 base: Remove a redundant 'return' 38c98e4 RTS: Reduce MBLOCK_SPACE_SIZE on AArch64 15cb83d Add testcase for #7411 a6826c5 Make Generic (Proxy t) instance poly-kinded (fixes #10775) 1b56c40 Respect GHC_CHARENC environment variable #10762 81ae26d Dwarf: Fix DW_AT_use_UTF8 attribute cbf58a2 Dwarf: Produce {low,high}_pc attributes for compilation units 8476ce2 Dwarf: Produce .dwarf_aranges section 0c823af Fix identifier parsing in hp2ps cd2dc9e ghc-pkg --enable-multi-instance should not complain about case sensitivity. c7f0626 integer-gmp: optimise bitBigNat c1d7b4b StgCmmHeap: Re-add check for large static allocations 60120d2 Fix 7.10 validate 12098c2 Fix typo in pattern synonym documentation. 10a0775 Anchor type family instances deterministically ad26c54 Testsuite: refactoring only 6740d70 Use IP based CallStack in error and undefined 010e187 Fix trac #10413 ff9432f Add test for updating a record with existentially quantified fields. 296bc70 Use a response file for linker command line arguments #10777 ba5554e Allow annotations though addTopDecls (#10486) c8f623e Expand declaration QQs first (#10047) 28ac9d3 Improve the error messages for class instance errors 3cc8f07 stm: Fix test case 5d7a873 Testsuite: don't warn about missing specialisations e0b3ff0 Testsuite: update expected output 3b23379 Testsuite: mark 4 tests expect_broken_for(#10712, opt_ways) 32a9ead Fix some tests that were broken by D861 c43c8e2 Testsuite: by default run all tests for a single way bd16e0b Testsuite: delete dead code 3744578 Injective type families 5dc88b7 Add test for T10836 (expected broken) 34b106f Accept underscores in the module parser. (Thanks spinda for the fix.) b639c97 Testsuite: fix tcfail220 - Maybe is wired-in now e1293bb Testsuite: only print msg when timeout kills process unexpectedly 79cdb25 Testsuite: ignore line number differences in call stacks (#10834) 85915e9 Make Data.List.foldr1 inline 19c6049 Fix T6018th test failure 64761ce Build system: implement `make install-strip` (#1851) 5c372fe ghc-pkg: don't print ignored errors when verbosity=0 c60c462 user-guide: Add missing tags around body 96b986b EventLog: Factor out ensureRoomFor*Event 062feee tracing: Kill EVENT_STARTUP 2c24fd7 Build system: put each BuildFlavour in a separate file (#10223) b40e559 Build system: simplify *-llvm BuildFlavours (#10223) 1abbacd Build system: cleanup utils/ghc-pkg/ghc.mk dc671a1 SPECIALIZE strictMinimum for Int and Integer c6b82e9 Further simplify the story around minimum/maximum 554be5e Build system: detect when user cloned from GitHub 864a9c4 Build system: remove hack for Mac OSX in configure.ac (#10476) a158607 Build system: delete the InstallExtraPackages variable 330fbbd Build system: make *-cross BuildFlavours consistent (#10223) 8be43dd Build system: cleanup BUILD_DIRS + add lots of Notes e4a73f4 Move GeneralCategory et al to GHC.Unicode 1b8eca1 Build system: check for inconsistent settings (#10157) dbb4e41 HeapStackCheck: Small refactoring 4356dac Forbid annotations when Safe Haskell safe mode is enabled. 23a301a Testsuite: comment out `setnumcapabilities001` (#10860) cdca31e Don't check in autogenerated hs files for recomp013. 3a71d78 Comments on oneShot a870738 Improve rejigConRes (again) 487c90e Add a test for Trac #10806 a7f6909 A CFunEqCan can be Derived 377395e Improve documentation for transform list-comps 50d1c72 Fix broken links in documentation 413fa95 Improve documentation of comprehensions f30a492 Testsuite cleanup 8c0eca3 Add assertions 18759cc Remove redundant language extensions 195af2d Dead code removal, export cleanup 4275028 Code movement 7ad4b3c s/StgArrWords/StgArrBytes/ 89324b8 Testsuite: normalise slashes in callstack output 37081ac Testsuite: mark enum01-enum03 expect_broken(#9399) on Windows 3ec205a CodeGen: fix typo in error message 08af42f hpc: use `takeDirectory` instead of `dropWhileEnd (/= '/')` c8d438f Testsuite: mark T6037 expect_fail on Windows (#6037) 12b0bb6 Account for stack allocation in the thread's allocation counter 14c4090 Pretty: fix unicode arrow operators. 325efac Fix `hp2ps -i-` e66daec DynFlags: remove unused sPgm_sysman (#8689) 8d89d80 Testsuite: add test for #10781 43eb1dc Show minimal complete definitions in ghci (#10847) 8ecf6d8 ApplicativeDo transformation 77662e1 Add namePackage function to template-haskell 48746ff Docs: make sure all libs are included in index.html (#10879) a8406f8 Pass TEST_HC_OPTS in bug1465 and T5792. 2d4db40 Fix #10815 by kind-checking type patterns against known kinds. 8ee2b95 Polish some error messages. b89c491 Always run explicitly requested ways (extra_ways) for fast runs. c738b12 Replace [PostTc id Type] with PostTc id [Type] e156361 Put stable pointer names in the name cache. 1637e4d Driver: --make -o without Main should be an error (#10895) 1a13551 Test #10347 d19a77a Update user guide, fixing #10772 d7f2ab0 Test #10770 79b8e89 Print associated types a bit better. 1292c17 Allow TH quoting of assoc type defaults. 27f9186 Clarify parsing infelicity. 93fafe0 Re-polish error messages around injective TFs. 6a20920 Small improvement in pretty-printing constructors. cbcad85 Fix typo in test for #10347. 2f9809e Slightly better `Coercible` errors. e27b267 Perform a validity check on assoc type defaults. 8e8b9ed Run simplifier only when the env is clean. cd2840a Refactor BranchLists. c234acb `_ <- mapM` --> `mapM_` 3f13c20 Revert "Revert "Revert "Support for multiple signature files in scope.""" 09d214d Revert "Revert "Revert "Change loadSrcInterface to return a list of ModIface""" 06d46b1 Unify hsig and hs-boot; add preliminary "hs-boot" merging. d516d2e Fix build failure, I think. 07f6418 Remove graphFromVerticesAndAdjacency 5a8b055 TcDeriv: Use a NameEnv instead of association list 83e23c1 Remove (now bogus) assert. 0b852fc base: use Show for ErrorCall in uncaughtExceptionHandler d4d34a7 Make derived names deterministic 089b72f DeriveLift extension (#1830) 4cdab73 HscMain: Place CPP macro invocation on one line 79f5732 testsuite: attempt fixing fallout from 089b72f52 c6bdf4f Remove references to () from types of mkWeak# and friends 65bf7ba DsBinds: Avoid using String when desugaring CallStack construction 939a7d6 Annotate CmmBranch with an optional likely target cf90a1e Add constant-folding rule for Data.Bits.bit 73921df Update Cabal to recognize DeriveLift 453cdbf base: export allocation counter/limit API from System.Mem 5c11523 reify associated types when reifying typeclasses 39a262e Revert "reify associated types when reifying typeclasses" 2440e3c Fix a bug with mallocForeignPtr and finalizers (#10904) b08a533d Fix DeriveGeneric for types with same OccName (#10487) 4f9ee91 Testsuite: update expected output for T8832 on 32-bit systems (#8832) 5883b56 Testsuite: properly fix T8832.stdout-ws-32 (#8832) 1395185 Testsuite: add test for #10767 fb40926 Weak: Don't require wrapping/unwrapping of finalizers a98815a Dwarf: Rename binding to avoid shadowing ppr a0b1f41 Dwarf: Ensure block length is encoded correctly f7fd864 Skip a possible BOM in utf8 encoding 3fbf8f4 Debug: Remove extraneous LANGUAGE CPP 988b2ba rts: Clean up whitespace in Trace.h b4d43b4 reify associated types when reifying typeclasses(#10891) 78053f4 Allow enumDeltaIntegerFB to be inlined 2eddcd9 Lexer: delete dead code for binary character literals 23baa65 .gitignore update for some test files. e3ab25a Typos in comments 03b3804 Add Data.Semigroup and Data.List.NonEmpty (re #10365) f2a174a Update nofib submodule a52db23 Update nofib submodule again eb975d2 Fix treatment of -0.0 57e3742 Document peculiarities of `traceM`. b29f20e nativeGen PPC: fix > 16 bit offsets in stack handling bd41eb2 LLVM: Implement atomic operations in terms of LLVM primitives 9539408 LLVM: Factor out accumulation of LLVM statements and variables 7442434 Move CallStack back to base e3d2bab Fix signature of atomic builtins 9ed700b Don't use old linkable for hs-boot files. 4fd6207 Move user's guide to ReStructuredText 93e21b9 docs: Fix ghc_config.py.in b6f76b9 Prevent GHC from silently dying when preprocessor is not found c4d7df0 Fix broken validation Build 6564 and accepting a few other test results a3c78ab Build system: add mk/validate.mk.sample a96f1ac Testsuite: update expected output for T8602 6cde981 Make GHC generics capable of handling unboxed types 0eb8fcd Enable `Enumeration is empty` warnings for `Integer` 2f74be9 Fill in associated type defaults with DeriveAnyClass d2fb532 testsuite: Bump up haddock.base expected allocations 620fc6f Make Windows linker more robust to unknown sections aecf4a5 Build system: don't create mk/are-validating.mk c0bdfee Testsuite: only add -fno-warn-missed-specialisations for ghc>=7.11 7fcfee1 A few typos in comments 5ca1d31 Testsuite: make driver python 2.6 compatible again 427f8a1 Deduplicate one-shot/make compile paths. 8c1866a Comments only 0e169a8 Fix kind-var abstraction in SimplUtils.abstractFloats ca816c6 Remove dead code: ruleLhsOrphNames 7da3d30 Comments only 3833e71 Comments about TcLevel assignment 59883ae Documentation for FrontendResult 36811bf AsmCodeGen: Ensure LLVM .line directives are sorted ea4df12 Ensure shiftL/shiftR arguments aren't negative 7b443bb Improve error messages for ambiguous type variables 69a6e42 Allow non-operator infix pattern synonyms e2b579e Parser: revert some error messages to what they were before 7.10 f64f7c3 Tests for #10945 and #10946 931d0a7 Move orphan instance/rule warnings to typechecker/desugarer. e99e6db Extra files to ignore from the new Restructured documentation. 0ead0ca Disable man building for most quick build styles. c7ab799 Ignore __pycache__. e5baf62 Simplify type of ms_srcimps and ms_textual_imps. 5dc3db7 Switch to LLVM version 3.7 80602af Revert "Switch to LLVM version 3.7" e331392 Fix error msg: ghci can't be used with -prof or -static (#10936) 5d84110 Add short library names support to Windows linker 182c44d Keep `shift{L,R}` on `Integer` from segfaulting 840df33 Rename SpecInfo to RuleInfo (upon SPJ's advice). fa5eabe sphinx: Don't share doctrees between targets 614ce4b Testsuite: T3333 still fails on non-linux statically linked ghci (#3333) bbad4f6 Delete ShPackageKey for now. f002340 compiler/nativeGen/PPC/Ppr.hs: Whitespace 4bd58c1 PPC: Fix right shift by 32 bits #10870 e737a51 base: MRP-refactoring of AMP instances 6b7bad9 Test Trac #10931 f8fbf38 Reinstate monomorphism-restriction warnings dcc3428 Don't inline/apply other rules when simplifying a rule RHS. 330ba6a testsuite: attempt fixing T10935 output 94ef79a Slightly wibble TcSimplify documentation d2f9972 Make dataToQa aware of Data instances which use functions to implement toConstr 1818b48 Fix incorrect import warnings when methods with identical names are imported e5bfd70 docs: overhaul Derive{Functor,Foldable,Traversable} notes dec5cd4 base: Add forkOSWithUnmask e8c8173 Allow arr ∧ (first ∨ (***)) as minimal definition of Arrow instance 29310b6 Switch to LLVM version 3.7 7756161 travis: use LLVM 3.7 933adc0 Fix GHCi on Arm (#10375). 729bf08 User should use -package-id flag if value in question is IPID. 5b0191f Update Cabal to HEAD, IPID renamed to Component ID. b92a51f Rename package key to unit ID, and installed package ID to component ID. 6338a1c Rename PACKAGE_KEY and LIB_NAME in build system. 20e30d5 Minor stylistic update. 04e8366 ELF/x86_64: map object file sections separately into the low 2GB 78c9dea Fix windows build after D975 4d6844a rts/Linker.c : Fix armhf build (#10977) 808bbdf Remove dead function patSynTyDetails b1884b0 Implement DuplicateRecordFields 75492e7 Add typed holes support in Template Haskell. 6a8ca65 Allow left ∨ (+++) as minimal definition of ArrowChoice instance e7c076d base: changelog entries for Arrow/ArrowChoice 324e0ac base: MINIMAL pragmas for Arrow/ArrowChoice 3340fe0 Build system: fix `make -j1` (#10973) 603a369 Silence the linker on Windows so tests pass fff0254 Move Control.Monad.IO.Class to base from transformers a6a3dab Libdw: Add libdw-based stack unwinding 40cbf9a Signals: Print backtrace on SIGUSR2 e8ed213 Make Monad/Applicative instances MRP-friendly 6638bfd CmmParse: Clarify description of calling convention d990b5f Signals: Always install SIGUSR2 handler 75c7cda ghc-pkg: Express return-method in terms of pure c6781a5 template-haskell: MRP-refactor Applicative/Monad instances 1e34f62 MRP-refactor `GHCi` Applicative/Monad instance d6d421c template-haskell: set explicit return=pure 40235c3 fix RTS linker compilation failure on Solaris 7bbb61b Driver: `ghci -e` should behave like `ghc -e` (#9360) 2b25a58 base: Have the argument of mask restore the state. 96dc041 Systools.hs: Improve detection of GCC and Clang ae4acbd Testsuite Windows: don't use forward slashes in topdir path 1750ebc Reject top-level typed TH splices. Fixes #10945 bb7e93c Extended default rules now specialize Foldable, Traversable to [] (#10971) 68a084f Testsuite: add test for #10997 2bc6efc Fix caching of pagesize 7855afb Fix breakage in the GHCi debugger e3e5a96 Remove old trace statement d77c404 Stop the pipeline when it doesn't need to be run. c633f71 Add another test for #10549 1e8d1f1 Suggest enabling PatternSynonyms (#10943) 9ec5996 rts/Schedule.c: remove unused variable 0499aa7 Add missing stderr file 9cb192c Make stronglyConnCompFromEdgedVertices deterministic 0ae6a43 Suggest chmod 755 instead of 644 fa7d582 Quote GHC path in configure so we can deal with multiple spaces. 8f5ad1a Quote GHC_PKG in Makefile. fdb08e2 Add testcase for #10426 0afba67 arclint: ReST doesn't need ArcanistMergeConflictLinter fd63ea5 base: Note platform dependence of registerFd 7dae074 Verify minimum required version of sphinx-build 67284a0 gitignore: Ignore sphinx doctrees directories 2866dfb Fix broken .arclint 4e40340 Support more sphinx-build versions in configure script ec14392 typo in comments: s/selectg/select/ 798d2e2 configure.ac: Fix autotool warnings 7aea0cf use Proxy instead of undefined -- we already dropped support for 7.6 ca12c24 Update example GHCi startup abc214b rts/Linker.c: Split RTS symbols out into separate file 3ed4b80 rts/Linker.c: Convert #if/#else to if/else 898f34c rts/RtsSymbols.c: Fix Windows build 43751b2 Provide a utility to check API Annotations c2fab84 Add testcase for #10370 86e5eb9 Remove redundant typedef 0b79aa1 base: Add Haddocks to GHC.RTS.Flags 73c273a Fix a typo in the User's Guide ReST intro 23e344b Remove cygwin32_HOST_OS #ifdefs 499ce29 Add flag to reverse errors in GHC/GHCi a9c93bd Implement MIN_VERSION and VERSION macros natively in GHC. c10c01c Build system: comments only [skip ci] f86fb5e Add regression tests for #10045, #10999 6831815 Comments only 0ce858e Zonk properly when checkig pattern synonyms adc3d17 manpage: Mark as orphan document d1d8704 Use correct documentation flag for freverse-errors 158d2a9 Make it possible to have different UniqSupply strategies 079dd12 Fix "Use correct documentation flag for freverse-errors" dc13467 DynFlags: Fix more merge errors ffcdd84 Sort field labels before fingerprint hashing 166c597 DynFlags: Yet one more fix 31704ad Make worker-wrapper optional 9efa56d Fix the DYNAMIC_GHC_PROGRAMS=NO build on Mac/Windows 19354fb Make T10970a non-dependent on GCC version. 7c2ab6f Testsuite: accept output for T10999 (#10999) d1ab6fc PrelNames: Fix duplicate unique 9fc2d77 Build system: don't add ALL_HC_OPTS when linking 04b0a73 Pattern synonyms: swap provided/required de27bed Update haskeline/terminfo submodules c1e1584 Update `deepseq` submodule 776d55c rts/Linker.c: Drop support for legacy OS X dyn loading ce2416b Fix rts/T9579 tests on OS X 08f5c4e Backpack documentation updates for component IDs [no-ci] 032be43 Testsuite: report and error out on unfound tests a051788 Revert "Build system: don't add ALL_HC_OPTS when linking" 2a74a64 Record pattern synonyms fa58731 Revert "Build system: don't create mk/are-validating.mk" e31113f Move mkDefaultMethodIds, mkRecSelBinds from TcTyClsDecls to TcTyDecls d25fa86 TcTyDecls: Remove redundant import of Applicative 40e6214 DynFlags: Add (another) missing hunk from D1360 bef2f03 Generate Typeable info at definition sites bbaf76f Revert "Generate Typeable info at definition sites" e272ab9 x86 codegen: don't generate location comments 8ddf417 Linker: Fix type in m32_free_internal 9b3a058 Swap prov/req in variable naming in Parser.y 9376249 Fix unused-import stuff in a better way 3e94842 Record usage information using GlobalRdrElt da58d15 Kill redundant import 268aa9a integerConstantFolding: when(compiler_debugged(), expect_broken(#11006)) 0a16374 Disambiguate record selectors by type signature 1f1c7c6 Build system: rename runghc.hs to Main.hs b05ab1a Build system: cleanup a few .cabal files 314395e Build system: cabalise deriveConstants + genprimopcode 2624298 Fix segfault due to reading non-existent memory 42e8528 CmmParse: Expose popcnt operations 3e2c227 Linker: Clean up USE_MMAP usage 1c80db5 Insert an empty line between two STG definitions in dump output. 56f9ef4 Unify: Add Outputable instance for UnifyResultM aa289d2 Move win32 tarball download logic to script f78b477 driver: use PROGBITS type for .debug-ghc-link-info section 59e728b Testsuite: suggest quoting $(TEST_HC) 91c6b1f Generate Typeable info at definition sites 39b71e8 Reimplement shadowing on a per database basis. f5974c8 rts: Make MBLOCK_SPACE_SIZE dynamic fce758c Add failing test for #11039 a5cb27f Make type-class dictionary let binds deterministic e03e22c testsuite: performGC requires SMP support for 'qg' option d9d201c testsuite: 'threaded2' tests require '-N' RTS option support e0071c3 unreg: handle CmmStack in C codegen (unbreaks '-g') 8995865 Update primitive/vector submodules 62f0fbc Update parallel submodule 8160f42 Add subWordC# on x86ish 7a48e6c Make ghc-cabal's `System.Directory` import more robust 6bef55c Fix documentation build on windows e2a78ee Signals: Ensure libdw session is freed 8f02baa Remove Data.List.NonEmpty.{words,unwords,lines,unlines} bc7cc25 disable large address space on OpenBSD da1a8da llvmGen: Fix build with Clang 8fd5cff llvmGen: Really fix build with Clang 3021cc0 Add rts/Linker support for more than 64k sections 31bcf9b Apply WERROR only to stage2 HC options c3b0215 Provide a utility to check API Annotations docs 4ad2a8f rts/posix: Reduce heap allocation amount on mmap failure c8e866a Enforce linkage with pthread library on OpenBSD 184dfce Linker: More uint64_t to uintptr_t fixes 9f0ecb4 ghc-prim: Fix hs_ctz64 for powerpc 62e1b35 Update array/stm/hpc/haddock submodules d2a7fb9 Update directory submodule 12abc77 Update filepath submodule de8443c Update process submodule 3238ef7 Update unix submodule 32f92a3 Update hoopl submodule f8ba4b5 Bump `base` version to 4.9.0.0 (closes #11026) 4b8b934 ghc-prim: add API delta as changelog (re #11043) 84bf1eb Bump ghc-prim version to 0.5.0.0 (closes #11043) f16827f ApiAnnotations: BooleanFormula is not properly Located 5a48180 keepCAFsForGHCi was broken 677d768 DynFlags: -freverse-errors should be defFlag 3431ad6 Update Cabal submodule 6fb0ba6 Dwarf: Preserve stack pointer register 76611d7 Dwarf.Types: Fix comment style 159a1a2 cmm: Expose machine's stack and return address register d9f8862 StgStartup: Setup unwinding for stg_stop_thread bb446b2 Libdw: Remove special treatment for stg_stop_thread b8df858 Dwarf.Constants: Introduce Haddock sections 52c6e3d Libdw: Fix symbol naming e9bfb3f Minor simplification in unariser pass: 65f3c4c Change sphinx for documentation building on windows to the python3 version f46f32b EventLog: Loop fwrite if necessary during flush 9fe5497 rts: Produce stack trace on fatal error 1e2259b Update process submodule to process-1.4 release c00c5e5 get rid of Elf32/Elf64_Section as this is a non-portable Linux-ism. 130ca3e Update filepath submodule for proper version 5065cf4 base: Update `@since 4.8.2` annotations (re #11026) 0bc8c6a base: GHC.RTS.Flags symbols really were introduced in 4.8.2 83fd2ba base: Add changelog entry for 4.8.2.0 8c80dcc base: Add new Control.Monad.Fail module (re #10751) b62605e Add `MonadPlus IO` and `Alternative IO` instances 334fe45 rts/Hash: Constify HashTable* in lookupHashTable 987d542 Build system: renable -Wall on validate (base) 0e21678 Cabal-level sanity check to enforce Cabal flag-invariant 22fcf9c Tweak settings for LLVM tests e547954 Use full name of LLVM program in error message 10647d4 Linker: #ifdef cleanup a58eeb7 Call Arity: In "e x", the result of "x" is not shared ce1f160 Make GHCi & TH work when the compiler is built with -prof 6e6438e Allow the GHCi Linker to resolve related dependencies when loading DLLs be88585 fix #10734 by adding braces to pretty-printing of let inside do 2208011 Remove PatSynBuilderId d9c1450 Build system: use stage0 to build dll-split 8262c95 Parser: allow empty multi-line deprecation warnings bd69f6f minor: use unless instead of (when . not) 932d503 Replace freeVarsOf scrut with scrut_fvs to avoid repetition 80d7ce8 Add pprSTrace for debugging with call stacks 0e40c01 Quote file paths in linker scripts 2b7d9c2 Add OpenBSD specific RTS symbols f405632 Fix sporadic failing ghci/Linker/Dyn tests 3cfe60a Abstract TFs can have injectivity information 96621b1 Associate pattern synonyms with types in module exports 5eb56ed Fix link in documentation fbc2537 OPTIONS_GHC compiler flags may contain spaces (#4931) ea8c116 Remove unused field in ConDecl f0f9365 Remove fun_infix from Funbind, as it is now in Match 109d7ce Systools: read ELF section without calling readelf fa61edd Improve documentation of Data.List.lines: 0f49508 Put kind variables before type variables when specializing badf5d5 Detect invalid foreign imports in bytecode compiler fb0d512 nativeGen.PPC: Fix shift arith. right > 31 bits afbd30b mkGadtDecl no longer in P monad 63cad5d Rename bundled pattern synonym tests to reflect new terminology a038b72 Remove redundant test. 9bea234 fix RTS Linker on platforms without SHN_XINDEX support 4a32bf9 Implement function-sections for Haskell code, #8405 e090f1b Change demand information for foreign calls 8755719 rules/haddock: Set __HADDOCK_VERSION__ 351de16 New magic function for applying realWorld# ac2e1e5 T10678: Fix bytes allocated statistic 5d6133b Ignore comments in getOptions 2290c8b APIAnnotations:add Locations in hsSyn for layout e66f79d Give helpful advice when a fully qualified name is not in scope b8d263d Turn ImportedModsVal into a data type 5a86292 Remove imv_empty from ImportedModsVal 8868ff3 Update note for Parent to explain PatternSynonym. 8988be8 Make 'error' include the CCS call stack when profiled 3353f62 Rip out __HADDOCK__ references 5488422 Fix bootstrapping with GHC 7.10.1 46a03fb Implement the Strict language extension fe95463 ApiAnnotations: Add SourceText for unicode tokens ee91482 ApiAnnotations : ITopenExpQuote needs SourceText 83b214d RtsFlags: Clean up stale CPP b8a849b users-guide: Limit column width 69822f0 RtsFlags: Refactor some of the deeper switches 7485d0c ghc.mk: Make install_docs rule sh-compatible 82cf672 haddock.mk: Use \{1,\} instead of \+ 3773e91 Use TcM instead of it's expanded form, in TcSplice 741cf18 Weaken monadic list operations to Applicative e2d9821 Data.List.isSubsequenceOf documentation clarification 2d1a563 Implement support for user-defined type errors. 3d88e89 s/FrontendMerge/FrontendInterface/g 9193629 Move usage calculation to desugaring, simplifying ModGuts. ac1a379 Revert "Unify hsig and hs-boot; add preliminary "hs-boot" merging." df8169c Bump process submodule 4e74ef9 T9181: Fix testsuite output 615ba5f Remove orphan Functor instance of Data.Graph.SCC 7c9cbfd template-haskell: drop `TemplateHaskell` requirement b3d6c0f Update Cabal submodule for new known extension 8ad9e74 Make `timer_create(CLOCK_REALTIME)` autoconf test more reliable acce37f Fix archive loading on Windows by the runtime loader 7b962ba Implement OverloadedLabels 233d131 MonadFail proposal, phase 1 98a4fa5 DynFlags: Don't list TemplateHaskell as supported if it's not 11e336e More import related hints f405e1e Disable failed specialisation warnings by default & update documentation. f9e17fd Add -fwarn-missing-monadfail-instance to mkUserGuidePart 6b3d5b5 rts: Kill PAPI support c945c90 base: Documentation for TypeError 112ce87 docs: Ignore Sphinx doctrees produced by manpage build 3ee0c14 Improve MonadFail errors by mentioning the pattern 2f7e895 users-guide: Give links more contrast a0f977e relnotes: Update base version 8eefdf0 users-guide: Use tango pygments style 02eb44d users-guide: Fix typo in conf.py 2d0e1db Comments only 8e8d26a Comments on TcRnTypes.canDischarge 07eb258 Refactor HsExpr.RecordCon, RecordUpd c61759d Fix inconsistent pretty-printing of type families cc79dd1 users-guide: Move

outside of tag 971f2c9 Correct > to > in user's guide a41830f Mention "-XMonadFailDesugaring" in the docs a586622 Release Notes: Mention out-of-scope error message improvements 2442038 Fix interaction of DuplicateRecordFields and GHC.Generics 3e2a4ee Fix broken build-system when libffi uses install-sh 65d7ff0 Make `derivedConstants` more crosscompile-friendly 7dfde0e derivedConstants: Add support for AIX c5d8162 Make GHC aware of OSAIX and AixLD 75036aa Set AIX specific CFLAGS flags fce0465 Unbreak Text.Read.Lex.lex on Unicode symbols d732ce0 Bump process submodule b72ca3e Pattern Synonym Documentation a689c8e ghci: don't let ctags/etags overwrite source files 1994304 user's guide: Fix some accidental triple-` quote 998c371 users-guide: Fix version number 7e6dcf4 base: Delete errant GHC/Stack.hsc f40fe62 Follow-up fixup to c5d8162d230c373 7f77e4e Fix Windows builds after D1242 d585073 RtsFlags: Fix const warning 192dd06 Suppress conflicting types for builtins warnings 6664ab8 Add DVarSet - a deterministic set of Vars 2325bd4 Create a deterministic version of tyVarsOfType b98ff3c Function definition in GHCi a703fbc Remove accidentally added T10359 blob 4976ab2 Follow-up fix to 3e2a4eefbed7002437c3f (re #11109) 638fde5 Add comment to Parser.y re extra API Annotation 64737f2 New expected test output for 32 bit platforms 3df9563 ApiAnnotations: Make all RdrName occurences Located 6393dd8 Make abstractVars deterministic in SetLevel 02c689c build.mk.sample: Document meaning of WERROR 5d6cfbc Rip out Papi configure check 7c9a04d Add a note explaining why every RdrName is Located dbad0d5 Libdw: Fix build on 32-bit platforms 70ee638 Libdw: Fix initial register collection on i386 36b2139 rts: Expose more libdw symbols a3a8ce6 rts: Add simple resource pool 6fbf22d rts: Add LibdwPool, a pool for libdw sessions bb249aa base: Add Haskell interface to ExecutionStack 7aaeaf8 Support multiple debug output levels 40be909 Dwarf: Ensure tick parentage is preserved 9471562 Output source notes in extended DWARF DIEs 5955510 Improve constraint-used-as-type error msg 70efb62 Add tests/monadfail/Makefile e587217 Add the rest of the notes for Located RdrName 1c45f41 rts: Always export Libdw* symbols 12dbc89 Add `PrelNames.thenAName` for `Applicative(*>)` f09f247 Implement new `-fwarn-noncanonical-monad-instances` c05fddd Rearrange error msgs and add section markers (Trac #11014). 6d14793 Add -Wcompat warning flag group e506f02 Rewrite checkUniques and incorporate into validate 8c5fe53 DynFlags: Update comments to reflect new users guide 8dc6da8 Comments only 5e04c38 Simplify the MonadFail code 76f3142 DynFlags: Drop stale comment 9032d05 update link to MonadFail proposal 924f851 Refactor default methods (Trac #11105) e9a4c09 Comments only e913676 Add a simplifier trace for eta-expansion 9aa9458 Note STM's vulnerability to non-allocating loops c7a058f User's Guide: Add links to MFP wiki page 5699ac9 User documentation for DuplicateRecordFields d2a2d5e Note #11108 in the bugs section of users guide c4308b4 rts/Pool: Add poolTryTake 1712a9e LibdwPool: Use poolTryTake ba14f04 Libdw: Handle failure to grab session for location lookup d25f853 Update transformers submodule 49aae12 Check arity on default decl for assoc types 583867b Update haskeline & terminfo submodules 85fcd03 Implement new -XTemplateHaskellQuotes pragma 72e3620 ghci: Add support for prompt functions 55c737f ghc-pkg: print version when verbose 399a5b4 Remove deprecated quasiquoter syntax. 71c0cc1 GHCi should not defer typed holes 54a9456 Update containers submodule 616aceb Update deepseq submodule 5897213 Remove redundant `#if`s f101a82 ghci: Refactor handling of :show bcd55a9 Some improvements on CoreToDos passed to plugins 290def7 Implement warnings for Semigroups as parent of Monoid afb7213 MkId: Typos in comments 14d0f7f Build system: Add stage specific SRC_HC_(WARNING_)OPTS 6dce643 Fix grammar and typo in TcTyDecls 36c1247 Remove duplicated line 44c3e37 Fix warning about unused pattern variable b432e2f Make the determinism tests more robust 1e041b7 Refactor treatment of wildcards 218fdf9 Make the order of fixities in the iface file deterministic 741f837 Implement more deterministic operations and document them 52b02e6 Comments only (isIrrefutablePat) b564731 Comments (TcSMonad) d00cdf2 Revert "ghci: Add support for prompt functions" 1caff20 StgSyn: Remove unused SRT constructor c75948b Move Stg-specific code from DynFlags to SimplStg d4d54b4 Remove *.xml from gitignore a12e47b Avoid panic due to partial ieName 8cba907 Create empty dump files when there was nothing to dump 0d1a2d2 ErrUtils: Spruce up Haddocks e7929ba Update bytestring submodule d25f3c0 users_guide/glasgow_exts.rst: fix link markup 8a50610 Major Overhaul of Pattern Match Checking (Fixes #595) 43a31fe testsuite: haddock.compiler: Bump expected allocations a034031 extending_ghc.rst: fix broken link (Trac #10950) c5597bb Revert "Create empty dump files when there was nothing to dump" 7b29b0b Fix haddock syntax 0dd61fe Kill redundant patterns 934b3a0 Update test output 40fc353 Bump hoopl submodule ae4398d Improve performance for PM check on literals (Fixes #11160 and #11161) 99d01e1 Remove unused import in deSugar/TmOracle.hs 7af29da Use Autoconf's AC_USE_SYSTEM_EXTENSIONS cd9f3bf RTS: Rename InCall.stat struct field to .rstat 6ef351d On AIX we need -D_BSD defined in d40f5b7 PmExpr: Fix CPP unacceptable too clang's CPP 36a208f Use builtin ISO 8859-1 decoder in mkTextEncoding befc4e4 Check: More Clang/CPP wibbles e9220da Bump allocations for T783 dc33e4c T5642 is broken 96e67c0 T5642: Skip it entirely 5b2b7e3 Make callToPats deterministic in SpecConstr 1c9fd3f Case-of-empty-alts is trivial (Trac #11155) 28035c0 Add derived constraints for wildcard signatures 1cb3c8c Wibbles only 822141b Make -dppr-debug show contents of (TypeError ...) 1160dc5 Fix egregious error in eta-reduction of data families 31b482b Minor refactoring of user type errors 67565a7 Tidy user type errors in checkValidType 43a5970 Comments only 16aae60 T5642: Fix skip usage caa6851 testsuite: Rename pmcheck/T7669 to pmcheck/T7669a d4bf863 Update peak_megabytes_allocated for T9675 020375d Add linter to check for binaries accidentally added to repository 901cab1 lint: Add linter to catch uses of ASSERT macro that Clang dislikes c865c42 StgCmmMonad: Implement Outputable instance for Sequel for debugging e2c518e libdw: enable support only on i386 and amd64 81cf200 pmcheck: Comments about term equality representation 406444b pmcheck: Comments about undecidability of literal equality 8f28797 Fix broken linters when using python3 c714f8f Use git.h.o copy of arcanist-external-json-linter a14296c Temporarily disable external-json linters 51d08d8 Enable non-canonical Monad instance warnings for stage1/2 314bc99 ghc.mk: cleanup: use tab consistently d6512c7 ghc.mk: don't run mkUserGuidePart more than once 13ab2c6 ghc.mk: fix docs re-rebuilding 5f1e42f Allow to compile OSMem.c when MEM_NORESERVE is not available df67940 Make ghc.mk compatible with pedantic /bin/sh impls 986ceb1 Implement new `-fwarn-noncanonical-monoid-instances` 8b42214 Tweak use of AC_USE_SYSTEM_EXTENSIONS be92c28 Update hoopl submodule f5127c8 linters/check-cpp: Don't produce debug log 3ea4fb7 Documentation: escape characters in template-haskell Haddocks 42a5469 Ignore generated linter.log 3d55e41 ghc-pkg: Restore old behavior in colored version; fixes 6119 8cef8af Re-export data family when exporting a data instance without an export list 91e985c Minor stylistic fixes in glasgow_exts.rst 2110037 Add isImport, isDecl, and isStmt functions to GHC API d4bcd05 rts: Remove space before argument list in ASSERTs 700c42b Use TypeLits in the meta-data encoding of GHC.Generics 51a5e68 Refactor ConDecl 1bd40c8 Move checking for missing signatures to RnNames.reportUnusedNames 151c4b0 ghc-pkg: don't sort packages unnecessarily 04e1c27 rts: One more Clang-unfriendly CPP usage 0933331 Re-use `transformers`'s `MaybeT` rather than our own b292720 Remove redundant CPP conditionals 834f9a4 Get rid of tcView altogether 2f6e87a Introduce HasGhciState class and refactor use-sites 9f4ca5a Associate ErrorCall pattern with ErrorCall type fd3b845 Make HasDynFlags more transformers friendly 7a40a6c Update libffi-tarballs submodule to libffi 3.1 (re #10238) bb753c5 Rename s/7.12.1/8.0.1/ two minor occurences 2cfa5db Fix double MaybeT instance 2106d86 Fix typo sneaked in with fd3b845c01aa26b6e5 69c3964 docs/glasgow_exts: Use warning admonition e792711 users_guide: Show sub-sub-sections in ToC aa6ae8a Comments only 6c794c3 Comments about polymorphic recursion d7729c7 An assortment of typos 7997d6c Refactor GHCi Command type; allow "hidden" commands 31bddc4 Add missing whitespace in toArgs' error msg af77089 Fix DeriveAnyClass (Trac #9968) e9ea020 Comments only 8317893 Improve documentation for DeriveAnyClass 688069c More typos in comments/docs 602889a Test Trac #11192 f4f00c0 Test Trac #11187 41ef8f7 Make sure PatSyns only get added once to tcg_patsyns f7c17c8 T7478: Don't expect broken on Darwin 5447c20 Mark retc001 as broken on Darwin 262954c T4801: Update expected allocations on Darwin c205aeb Removed colon append operation (fixes #10785) b138248 Improved data family export documentation ceaf0f4 testsuite: Only run recomp015 on ELF-based platforms 6e56ac5 Fix infix record field fixity (#11167 and #11173). 6746549 Add kind equalities to GHC. 5183109 Revert README.md changes from 6746549772c5 a6e0394 haddock: Fix submodule commit to point to ghc-head b5d5d83 Revert .gitmodules changes from 6746549772c5 a459451 rm rae.txt 68f198f Test case for #7961. 779dfea Test #9017 in polykinds/T9017 a3c2a26 Frontend plugins. 1883afb Implement -fwarn-missing-pat-syn-sigs 3ec8288 Rework the Implicit CallStack solver to handle local lets. 4935b48 Make -XStrict imply -XStrictData 3640ae9 Dwarf: Use .short instead of .hword on Darwin aaed24a Build system: fix 'make install-strip' in bindist 9934819 Refactor type families in Template Haskell 59cc6ed Fix release notes markup 669c5ed Remove redundant imports f48015b configure: add support for 'sh4' (Trac #11209) 0bf0cf9 Update Cabal submodule fcc6b1d Use idiomatic way to tell Autoconf the c compiler baed2f5 Don't pass CC= explicitly to `./configure` scripts 65920c9 Some more typos in comments 04ab55d Use Cxt for deriving clauses in TH (#10819) 023f11f Suggest import Data.Kinds when * is out of scope 419b6c0 Make binds in do-blocks strict when -XStrict (#11193) 59d3948 Add testcase for #11216 402bbe6 Add IsString Outputable.SDoc instance 05fe546 Test #9632 in dependent/should_compile/T9632 ddde542 DynFlags Remove -fwarn-context-quantification flag 9017f16 Mention "handle is semi-closed" in error messages 05a5ebe Fix runghc when $1_$2_SHELL_WRAPPER = NO 6d9c18c DynFlags: remove Opt_Static 33742db DynFlags: delete function that doesn't do anything f4dd486 Document -XOverloadedLabels 8e6f9bf TysWiredIn: Fix a comment - Note [TYPE] is in TysPrim 4c9d1ea Update expected test output for 32 bit platforms f4d90f9 Reset process submodule to v1.4.1.0 release tag d1ca5d2 Fix formatting complaint from Sphinx 98cdaee Improve documentation for -XStrict b8ca645 Comments on equality types and classes 6eabb6d Allow recursive (undecidable) superclasses 947e44f Comment layout only e2c9173 Narrow scope of special-case for unqualified printing of names in core libraries 758e6b3 base: NonEmpty: Fix documentation example a701694 Add testcase for #11224 28638df primops: Mark actions evaluated by `catch*` as lazy c1e2553 Expose enabled language extensions to TH 50c795c Update pretty submodule to v1.1.3.2 release 3a48e6e Update binary submodule to binary-0.8 snapshot 2206fa8 Add `-W(no-)xxx` aliases for `-f(no-)warn-xxx` flags 437ebdd Start using `-W` instead of `-f(no-)warn` in some places d36e9e1 GHC.Stack: Fix Haddock markup 4c7da9c Update haddock submodule ab79ed7 Improve detection of `fdatasync(2)` (re #11137) 11b9ada Synchronize Haddock submodule with master branch efaa51d Look through type synonyms in GADT kind signatures 046b47a Note [The equality types story] in TysPrim b35cc1f Update Cabal submodule to latest snapshot 1687f99 Update transformers submodule to latest v0.5.0.0 6c9258d Add test for #10897 7221ad7 GHC doesn't have a way to ask for user-package-db, so Cabal reimplemented it. 4905b83 Remote GHCi, -fexternal-interpreter a6d664c accept output dd3837a Fix tests when run in parallel acd447e Bump haddock expected performance numbers b20a65d testsuite: Add missing LiteralsTest2.hs 786d528 TcTypeable: Don't use bogus fingerprints when suppress-uniques is enabled 62e60bb Fix haddock hyperlinker 27f47cd Fix libffi dependency, and remove redundant LibFFI.hsc 0cc4aad Build system: Cabalize genapply 86ad116 Add Shake configuration to configure.ac 109d847 Build system: Make cGhcRtsWithLibdw flag a proper Bool e58a936 rules/haddock: Add EXTRA_HADDOCK_OPTS flag 4f870f8 Conditionally show plural "s" in warnings cab1316 Fix #11232. 4b161c9 Reify DuplicateRecordFields by label, rather than by selector d3dac4e Add -fprint-typechecker-elaboration flag (fixes #10662) 575f0ad users_guide: Remove extraneous vertical whitespace e7f22bf Improve pretty-printing in pprIfaceIdBndr e32c2e1 Remove unused T10524.stderr 89d70f9 Update Cabal submodule aee58e1 T9961 allocations crept further upwards e2e24f2 Disable recomp015 on ARM ece8aff Remove warning-suppression flags for Cabal a2f04a2 Testsuite: #10712 is fixed 9d9c534 Lexer: update outdated comments [skip ci] 1b6323b IO Handles: update comments [skip ci] ae86eb9 Fix tcTyClTyVars to handle SigTvs 1722fa1 Fix #11230. c1bd3d4 Build system: also put scripts in libexecdir/bin 272e1cc Testsuite: allow spaces in TEST_HC passed in by the user 116ba5e Build system: allow bindist without docs f1fa383 Suppress warnings when compiling primitive and random bc436f9 Testsuite: mark frontend01 conditionally expect_broken on #10301 e0e03d5 Move Data.Functor.(Classes,Compose,Product,Sum) into base c5c72aa Update containers submodule to v0.5.7.0 release 3dd06d5 Random typo fixes 06cb695 ghci: fix UNREG build (missing fromJust import) 98ccb72 Testsuite: widen lazy-bs-alloc 3->5% 8d45ccd Testsuite Windows: fix sigof01m, sigof012m and sigof02dm dc8b647 Testsuite Windows: fix ghcpkg03 and ghcpkg05 34393d9 Documentation for -fexternal-interpreter 77b7f24 Use `-Wno-tabs` more targetted ba80fc6 Fix PowerPC build 55e9ab8 Update directory submodule to v1.2.5.0 release 83e4140 Comments only ed3bfca Update Win32 submodule to fix 77b7f24543f fallout 8946ee6 GHCi.Run: Remove redundant language pragma 53a567c configure.ac: Rename shake/ to build/ f857d27 configure.ac: Rename build/ to shake-build/ 9d921d6 Test Trac #11248, #11249 ff752a1 tcCheckSatisfiability: less aggressive superclass expansion 987426c SrcLoc: Eliminate constructors of RealSrcSpan d6b91ea Add test for T11122 4198b81 ghc.cabal: Backpack directory no longer exists 0e9a331 LLVM backend: Show expected LLVM version in warnings/errors e02a4c2 Fix build for AArch64/Arm64 9356393 Update terminfo submodule to v0.4.0.2 release 97281b4 Update terminfo submodule to v0.7.2.2 release ccc5a1a Build system: fix 'make sdist' d1416c3 Update .mailmap [skip ci] 5431273 Bump hsc2hs submodule b2670fc fix typo 2cc5b60 Documentation, tests for hsc2hs's new #alignment macro b028384 Add -Nmax RTS feature (#10728) 59de6e8 Add sparc64 a known architecture (Ticket #11211) 7b8a822 Make ghc-boot Hackage-ready 64b6a76 Fix typo in 7b8a8222e8f0 d8c8902 First pass at cleaning up ghci.cabal 34eaf2b Fix two occurences of `x86_HOST_ARCH` bcc213d Update time submodule to v1.6 release dd56eb1 Merge new commands from ghci-ng (re #10874) 59cc32c Update containers submodule to v0.5.7.1 release tag 3b66960 Remove unused/redundant fields from ghc-cabal. f7bd37e aclocal.m4: Fix llc/opt detection code 1a86413 Update binary submodule to final 0.8.0.0 release 8d95412 Disallow empty where bindings in pattern synonym declarations. 44640af Allow as-patterns in pattern synonym declarations. 29ca4a1 DynFlags: call defaultWays when creating defaultFlags 62155a6 TcTyClsDecls: use zipWith3M_ instead of generating triplets 850710a TcTyClsDecls: Add a type annotation d8ed20c Add Location to RdrName in FieldOcc b225b23 Modify IsString String instance (fixes #10814) eb7796f Warn about unused type variables in type families edcf17b Move Const to own module in Data.Functor.Const and enable PolyKinds 6457903 Implement phase 1 of expanded Floating 9f23dd9 testsuite: Add ClassOperator testcase 25db56c Minor clean-up to ghc-bin.cabal.in e29ee49 Fix AnnDotDot in module export 99b956e Fix-up GHC 7.12 artifacts ee6fba8 Encode strictness in GHC generics metadata c8c44fd Maintain cost-centre stacks in the interpreter 4bb9f88 TcTyClsDecls: Remove invalid comments about list monads fd1b5ae testsuite/ClassOperator: This actually should_fail a61e717 testsuite: Add testcase for #8316 eeecb86 Add proper GADTs support to Template Haskell 55250a6 Rename GHCi's UI modules into GHCi.UI(.*) ff3f918 Fix #11256 by not immediately erroring if we can't find a module. 2dff6c1 Added missing instances for Identity and Const (#11210) 1fcdcae testsuite/ClassOperator: Mark as compile_fail instead of should_fail fb3302c base: Add sections to changelog 083b700 users_guide: Synchronize relnotes with base changelog c12fc2e Update hoopl submodule to final 3.10.2.1 release aa7fb9a Fix GHCi segfault in Windows 32bit ff92395 Make HsAppsType contents Located 44de66b Update Cabal submodule to latest snapshot ea3f733 Comments only, about coercion holes b407bd7 Retain AnnTilde in splitTildeApps f975b0b Rework Template Haskell's handling of strictness 6eabd93 Update stm submodule to v2.4.4.1 release 29928f2 Fix grouping for pattern synonyms f40e122 Fix typechecking for pattern synonym signatures 51d8330 Remove duplicate T11224 test definition 7966eea Localize API Annotation in LInjectivtyAnn 01b0461 Remove another duplicate test 575a98e Refactor named wildcards (again) 721d56d APIAnnotations:AnnComma in wrong place in qcnames1 d3ce417 Tweak comments around UnivCos. 21b25df CoercionN is not in scope in TyCoRep 998739d Refactor package flags into several distinct types. 1faf1fc Implement -hide-all-plugin-packages and -plugin-package(-id), fixing #11244 3e99980 Update filepath submodule to latest snapshot 5f08681 - fix tests on OpenBSD which requires _DYNAMIC symbol 48e0634 Revert "Allow as-patterns in pattern synonym declarations." b55ad1b Wibble to error message in Trac #10426 1963250 Comments and white space c069be8 Add a pattern-syn form of PromotionErr 99eb002 Comments only 6eb9dc9 Tidy up and comment wildcards in family instances ed213ea Test Trac #11274 7ed0da6 Modify Nmax to maxN Trac #10728 dab8e34 Delete incorrect *-ws-32 expected test output 84f6739 - fix gc_thread related compilation failure on Solaris/i386 platform f13de71 Fix super-class cycle check b37f216 Comments only 7824870 Fix ASSERT in buildPatSyn, and T10897 test 380b25e Allow CallStacks to be frozen cb989e2 API Annotaions:add name in PatBind Match d1e9f82 Update tests for Trac #11039 f141f41 Test #10432 7cddcde Docs: -interactive-print should reside in registered package 3221599 Make testsuite work again with Py3 353e97a config.mk.in: Disable stripping by default on ARM 3017cbc ghc-cabal: Bring back TRANSITIVE_DEP_NAMES 6ec236b Improve SimplUtils.interestingArg d990354 Improve the runRW magic in CorePrep fcc7498 Improve tracing a bit in CoreSubst 1af0d36 Refactoring only e338376 Fix normalisation of TyCon representations 48db13d Don't drop last char of file if -osuf contains dot 2db18b8 Visible type application 2032635 Testsuite: fix qq005 and qq006 (#11279) bc8cac1 Testsuite: mark T7681 expect_broken (#11287) 5e4e9e0 Fix #11255. bd7ab66 Test #11254 in typecheck/should_compile/T11254 1411eaf Note [TyBinder] in TyCoRep 52da6bd Have mkCastTy look more closely for reflexivity. da69358 Fix #11287. b218241 Test #10589 in typecheck/should_compile/T10589 05e3541 Test #10619 in typecheck/should_fail/T10619 0fda908 Bump Haddock submodule again 8bf2d8f Linker: Fix cut-and-paste error in debug output 422107e T10518: Ensure literal has 64-bit type e39d10f testsuite/T8274: Remove 32-bit test output fb5d26d testsuite/codegen: Add missing dummy Makefiles 0b0652f testsuite/T9430: Fix word-size dependence b62215d Linker: Reenable Thumb support e8672e5 libraries/ghci: Implement mkJumpToAddr for ppc64 909bbdb Linker(ELF): Fix addProddableBlocks usage da5e693 testsuite/joao-circular: Clean up test results a3b34b6 Clean up a botched merge. d1ebbb0 testsuite/CmmSwitchTest: Mark as broken on 32-bit platforms 11778f7 Add testcase for getSizeofMutableByteArray# 07b3be7 integer-gmp: Fix #11296 bec5350 Adding flags: -ffull-guard-reasoning and too-many-guards c8d0af3 RTS: Detect powerpc64le as ELF 64-bit system 1b00016 The -package flag should select match from right-most package db. 0054bcd rts/Linker(ARM): Ensure all code sections are flushed from cache 01299ca Synchronise ghci-package version with ghc-package 4a10ecb Patch-level increment integer-gmp to 1.0.0.1 e01aa22 Patch-level increment integer-simple version 0.1.1.1 c7830bd Update hpc submodule to 0.6.0.3 version 3aa4a45 Update filepath submodule to v1.4.1.0 rls tag 295085c Update time submodule to latest snapshot bab5109 Make git-committer inferred version-date TZ-invariant 7fef7fe drop obsolete/redundant OPTIONS pragma [skip ci] af92ef3 ghc/Main: Update list of --print modes 4f69203 Fix panic when using pattern synonyms with DisambiguateRecordFields 5bb7fec Export some useful GHC API functions. 8e735fd Fix GEq1 when optimizations are enabled 2e49c8c users_guide: Move 7.12.1-notes to 8.0.1-notes 9cb79c5 Update a few references to GHC 7.12 b093e63 Modify getFullArgs to include program name df6cb57 Accept submodule libraries/primitive commit 1af89788d fcc7649 Introduce negative patterns for literals (addresses #11303) a1e01b6 testlib: Make TyCon normalization Python 2.6-compatible adcbc98 Add regression test for #11303 e4cc19d Update Cabal submodule to latest snapshot c6cab9d Remove `cabal07`-test broken by e4cc19de4bdbcc 34af60c testsuite: normalise away `ld`-warning on AIX c06b46d Fix #11305. 8fcf1e7 Make iserv-bin compatible with GHC version bump to 8.0 07779c2 T11303: Set maximum heap size 630303a users_guide/ghci: Fix heading 3bbc01a Testsuite: mark T7653 with high_memory_usage b0fa286 Fix some typos e9ab6d5 rts/PrimOps.cmm: fix UNREG profiled build d3a79bc rts/Linker.c: mark ia64 as 64-bit ELF, drop unused branches 0380a95 glasgow_exts.rst: fix code block 947c8a5 Bump GHC HEAD's Version from 7.11 to 8.1 bb7f2e3 Address #11245: Ensure the non-matched list is always non-empty 25e4556 Various API Annotations fixes 75851bf fix ghci build on ArchUnknown targets 0579fe9 Improve exprIsBottom 5ba3caa Comments only 70eefbc Test Trac #11245 351dea4 Drop redundant `-D__GLASGOW_HASKELL__=...` flag eae40e1 Use 0/1 instead of YES/NO as `__GLASGOW_HASKELL_TH__` macro value 0d20737 Drop redundant/explicit `=1` in `-DFOO=1` flags 2f923ce Drop pre-AMP compatibility CPP conditionals 3c8cb7f Remove some redundant definitions/constraints 12ee511 Remove ghc-7.8 `-package-name`-compat handling 37945c1 Simplify -fcmm-sink handling for Parser.hs 6a010b9 Update haskeline submodule to latest snapshot 8afeaad travis: use GHC 7.10.3 dafeb51 Canonicalise `MonadPlus` instances b469b30 Minor fix of MonadFail instance for `ReadPrec` ab0d733 Update Cabal submodule, Fixes #11326 f3cc345 Add strictness for runRW# 0b8dc7d API Annotations: AnnTilde missing 78daabc mk/config.mk.in: drop unused CONF_CC_OPTS for ia64 f5ad1f0 AnnDotDot missing for Pattern Synonym export 256c2cf Test Trac #11336 0490fed Linker: ARM: Ensure that cache flush covers all symbol extras d159a51 Linker: ARM: Refactor relocation handling 48e0f9c Linker: Make debugging output a bit more readable 07d127a Linker: Use contiguous mmapping on ARM d935d20 Omit TEST=T10697_decided_3 WAY=ghci 1dbc8d9 Add test for #10379 04f3524 Linker: ARM: Don't change to BLX if jump needed veneer c7d84d2 Update .mailmap [skip ci] 7e599f5 Linker: Move helpers to #ifdef da0f043 Rewrite Haddocks for GHC.Base.const 5c10f5c users_guide: Add ghci-cmd directive 4c56ad3 Build system: delete ghc-pwd 0acdcf2 Avoid generating guards for CoPats if possible (Addresses #11276) 1a8b752 Add (failing) test case for #11347 1f526d2 Release notes: Mention remote GHCi cdeefa4 ghc.mk: Add reference to Trac #5987 77494fa Remove -Wtoo-many-guards from default flags (fixes #11316) e32a6e1 Add Cabal synopses and descriptions bbee3e1 StgCmmForeign: Push local register creation into code generation bd702f4 StgCmmForeign: Break up long line aa699b9 Extend ghc environment file features 4dc4b84 relnotes: Note dropped support for Windows XP and earlier 852b603 Restore old GHC generics behavior vis-à-vis Fixity cac0795 Change Template Haskell representation of GADTs. 89ba83d Bump Cabal and Haddock to fix #11308 7861a22 Add a note describing the protocol for adding a language extension f01eb54 Fall back on ghc-stage2 when using Windows' GHCi driver 568736d users guide: Add documentation for custom compile-time errors 5040686 users guide: Add links to release notes 47367e0 Rewrite announce file 0a04837 users guide: Tweak wording of RTS -Nmax description 0839a66 Remove unused export 3f98045 Tiny refactor 97c49e9 Spelling in a comment 290a553 Tidy up tidySkolemInfo 4dda4ed Comment wibble 29b4632 Inline solveTopConstraints dc97096 Refactor simpl_top 02c1c57 Use an Implication in 'deriving' error a5cea73 Turn AThing into ATcTyCon, in TcTyThing 9915b65 Make demand analysis understand catch 1ee9229 Test Trac #10625 c78fedd Typos in docs and comments 6be09e8 Enable stack traces with ghci -fexternal-interpreter -prof 09425cb Support for qRecover in TH with -fexternal-interpreter 6f2e722 User's Guide: injective type families section 0163427 Fix Template Haskell's handling of infix GADT constructors 1abb700 Improve GHC.Event.IntTable performance c33e7c2 Fix +RTS -h when compiling without -prof 10769a1 Rename the test-way prof_h to normal_h 47ccf4d Add a pointer to the relevant paper for InScopeSet 2bd05b8 Docs for stack traces in GHCi f7b45c3 Build system: fix `pwd` issues on Windows 1cdf12c Fix test for T9367 (Windows) a6c3289 users_guide: Use semantic directive/role for command line options 86d0657 users-guide: A few fixes 8f60fd4 docs: Fix DeriveAnyClass reference in release notes and ANNOUNCE 67b5cec user-guide: More semantic markup 0dc2308 user-guide/safe_haskell: Fix typos a84c21e Reject import declaration with semicolon in GHCi 831102f Parser: delete rule numbers + validate shift/reduce conlicts 4405f9d Add failing testcase for #10603 5cb236d fix -ddump-splices to parenthesize ((\x -> x) a) correctly fbd6de2 Add InjectiveTypeFamilies language extension 4c9620f TrieMap: Minor documentation fix b1c063b ghc.mk: Use Windows_Target instead of Windows_Host 8e0c658 Linker: Define ELF_64BIT for aarch64_HOST_ARCH 00c8076 fix typo causing compilation failure on SPARC (ArchSparc -> ArchSPARC) 6cb860a Add -prof stack trace to assert 3e796e1 A little closer to supporting breakpoints with -fexternal-interpreter 88d6d5a Use implicit CallStacks for ASSERT when available d44bc5c TemplateHaskell: revive isStrict, notStrict and unpacked ac3cf68 Add missing type representations e782e88 Add test for Data.Typeable.typeOf c3f9246 Print a message when loading a .ghci file. 6ea24af Handle over-applied custom type errors too. c313327 Minor improvement in CoreDump outputs: c73333a Minor code refactoring 61011b4 users-guide: Wibbles 91dcc65 GHC.Generics: Fix documentation f0c4e46 Add tests for #11391 b0641ad INSTALL.md: Mention -j and other wibbles 78a4c72 Rename InjectiveTypeFamilies to TypeFamilyDependencies 4dbc31b users-guide: Update language extension implications b355b8f users-guide: Add since annotations for language extensions 83c13c2 user-guide: Use ghc-flag for dump formatting flags fd686c4 API Annotations: use AnnValue for (~) db371c1 T11300: Fix test on windows 49e414a Remove lookup of sections by name instead use the index numbers as offsets 91f1c60 Fix #11015 with a nice note. 8959b03 ANNOUNCE: Mention powerpc code generator b90cac6 user-guide: Note Cabal version limitation faf3f96 users-guide: Fix cabal version number c6a3e22 Link command line libs to temp so e7eec3a Use XZ compression by default 7cf16aa Don't output manpage in same directory as source 756b228 Refactor lookupFixityRn-related code following D1744 67fc3f3 configure.ac: Export MAKECMD to build system 443bf04 Allow pattern synonyms which have several clauses. 165ae44 Expand type/kind synonyms in TyVars before deriving-related typechecking e6ca930 Fix #11355. d4af57f Test #11252 in ghci/scripts/T11252 d459f55 Fix #10872. 6c07f14 Fix #11311 3a7f204 Clarify topological sorting of spec vars in manual 39ea4b4 Fix #11254. bafbde7 Constrained types have kind * in validity check. 072191f Fix #11404 33950aa Tiny refactoring in TcUnify 80b4c71 Fix typo in error message (#11409) 3c6635e Fix #11405. 148a50b Fix some typos 3a1babd Work SourceText in for all integer literals 9308c73 Fix a number of subtle solver bugs 3b6a490 Add missing T11408.hs ae1c48c rts/posix: Fail with HEAPOVERFLOW when out of memory during mmap d1ce1aa users-guide: Clean manpage build artifacts and fix usage of clean-target b3eb8fa Complete operators properly 65b810b Show TYPE 'Lifted/TYPE 'Unlifted as */# in Show TypeRep instance f3a867e Add testcase for #11414 2fd407c validate: Use gz compression during bindist check a7b751d un-wire-in error, undefined, CallStack, and IP 5a62b6a Simplify API to tcMatchTys f02200f Layout only cb24e68 Fix typecheck of default associated type decls b7e5c30 White space only 6e0c0fd Improve debug printing/warnings ec8a188 Refactoring on IdInfo and system derived names 8e6a68d Add Trac #11427 to Note [Recursive superclasses] e2c7b7e Implement scoped type variables in pattern synonyms 8e50301 Test Trac #11379 5412899 Typo in comment 817dd92 Fixes to "make clean" for the iserv dir b8abd85 Replace calls to `ptext . sLit` with `text` 240ddd7 Switch from -this-package-key to -this-unit-id. cbc03f1 ghci: Kill global macros list d2ea7f9 Hide derived OccNames from user 38666bd user-guide: Delete errant fragment aff51af users-guide: Begin documenting --frontend 80265c4 Typos in comments 9d33adb Check InScopeSet in substTy and provide substTyUnchecked 713aa90 Re-export ghc-boot:GHC.Serialized as Serialized 952eda2 Fix IfaceType generation for TyCons without TyVars 975bdac T11266: Improve the test by adding more of the other problematic modules 514bac2 Fix combineIdenticalAlts 0373a84 Oops. Add missing close-comment 5cce095 Use (&&) instead of `if` in Ix derivation 84b0ebe Rework derivation of type representations for wired-in things 225afc4 Add test T9407 (Windows) 6ddc991 Update submodule stm + random 48d4bc5 substTy to substTyUnchecked to fix Travis build 1ce1371 MkId: Update OpenKind reference 2e65aae Add comments about tyCoVarsOfType e604e91 Comments only c572430 Re-add missing kind generalisation 6f95e23 Comments only b3ee37c Improve pretty-printing of UnivCo 07afe44 Remove the check_lifted check in TcValidity b2e6350 Strip casts in checkValidInstHead 395ec41 Allow implicit parameters in constraint synonyms ede055e TyCoRep: Restore compatibility with 7.10.1 f23b578 user-guide:: Improve -D description 928484d user-guide: Refer to MIN_VERSION_GLASGOW_HASKELL from intro 3883f99 rel-notes: Note the return of -Wmonomorphism-restriction 7cb893f Update and improve documentation in Data.Foldable 96303db Add a missing .gitignore entry in annotations tests 2ffc260 Add -ignore-dot-ghci to tests that use --interactive 4c4a0a5 Fix docstring GHC.IO.Handle.FD.openFileBLocking 4c11db6 sphinx-build: fix python stack overflow (Trac #10950) b617e9f Improve comments in CmmSwitch 85e147e Always run test T9407 36b174d Add expected stderr for #11466 test case adb721b Make a constraint synonym for repeated BinaryStringRep and use it. 835a2a2 Default non-canonical CallStack constraints 2df4221 Add tests for #11465 and the kind invariant 9048c3d Don't print "Loaded GHCi configuration" message in ghc -e (#11478) 65881c0 Mark some ghci tests as req_interp 6e5f828 Fix a formatting error in the user's guide 4d51bfc Do not count void arguments when considering a function for loopification. b01288d rts: Disable tick timer unless really needed 4e04043 Add test for Trac #11056 f42db15 Remove unused IND_PERM 06c2547 Small doc fix 7cd37c5 Give a more verbose error message when desugaring a HsTypeOut 8e9a870 Remove -Wredundant-superclasses from standard warnings 1be8491 mkUserGuidePart: Better flag cross-referencing 6f96109 user-guide: Reformat warning lists b5e52bf user-guide: Fix typos ec87788 Don't add ticks around type applications (#11329) 923d215 user-guide: Document -L RTS flag 89bdac7 Add test for #11473 8b5ea7c User's guide: fix singular/plural typo in flagnames 98d6a29 Docs: delete section on Hierarchical Modules edc68b2 Remove `replaceDynFlags` from `ContainsDynFlags` 2c6fe5b Add -fwarn-redundant-constrains to test for #9708 fd6dd41 Implement `-Wnoncanonical-monadfail-instances` warning ff21795 Special-case implicit params in superclass expansion 746764c Refactor validity checking for type/data instances 42c6263 Avoid recursive use of immSuperClasses f7e0e5f Improve tracing in checkValidInstance 3c060f3 Fix exprIsHNF (Trac #11248) 5c82333 Show error message for unknown symbol on Elf_Rel platforms edb30fd Comments only: more alternate names for ARM registers [skip ci] bc1e085 HscTypes: Fix typo in comment 132c208 Rename -Wmissing-monadfail-instance to plural-form 6e2658f Better document behavior of -Wmissed-specialisations 128b678 user-guide: Note order-dependence of flags f0f63b3 Implement -Wunrecognised-warning-flag 9fe7d20 Ensure that we don't produce code for pre-ARMv7 without barriers 632f020 Less verbose output for the in-scope set cf788a5 White space only 47b3f58 Add "ticks-exhausted" comment 1c6d70c Kill off zipTopTCvSubst in favour of zipOpenTCvSubst 016a0bd Fix two cloning-related bugs 34c9a4e Missed plural renaming in user's guide 5f5dc86 Minor users-guide markup fixup [skip ci] 9b71695 Update transformers submodule to 0.5.1.0 release f1885df Update process submodule to 1.4.2.0 release 3798b2a Fix three broken tests involving exceptions 01809bc Pass InScopeSet to substTy in lintTyApp e24a9b5 Nicer error on +RTS -hc without -rtsopts or -prof 6d2bdfd Fix segmentation fault when .prof file not writeable 6817703 Split off -Wunused-type-variables from -Wunused-matches 144ddb4 Construct in_scope set in mkTopTCvSubst eeb67c9 Testsuite: fixup req_profiling tests (#11496) e2bdf03 Build profiling libraries on `validate --slow` (#11496) 44a5d51 Enable RemoteGHCi on Windows 45fd83b Fix a typo in the note name in comments 448ea97 Typos in comments 1f6d142 ghci: fix trac issue #11481 1c6130d rts/Timer: Actually fix #9105 0dc7b36 Restore original alignment for info tables 0d92d9c Use stage1 build variables when building the RTS d50609e Test for undef bugs in the LLVM backend when validating 45c6fbc Document -fllvm-fill-undef-with-garbage 4faa1a6 s/unLifted/unlifted for consistency 2899aa5 Fix some substitution InScopeSets 00cbbab Refactor the typechecker to use ExpTypes. 5dcae88 Rename "open" subst functions 85daac5 Fix cost-centre-stack bug when creating new PAP (#5654) a496f82 Remote GHCi: create cost centre stacks in batches 71b1183 Update profiling test output 0d5ddad fix validate breakage 63700a1 Use the in_scope set in lint_app 1b72534 Fixup test for #10728 61e4d6b Mark dynamic-paper as expect_fail_for optasm and optllvm (#11330) d3b7db0 Fix the Windows build 0dd663b Add closing parenthesis in comment for eqString (#11507) bc83c73 Add release note about flexible RebindableSyntax bb956eb Add asserts to other substitution functions 6c7760b Define CTYPE for more Posix types 2fbf370 Update unix submodule to latest snapshot b61f5f7 Put docs in /usr/share/doc/ghc- 4d0e4fe Add type signatures. 90f688e Code formatting cleanup. 6544f8d Properly track live registers when saving the CCCS. 669cbef Fix Trac issue #11487. 34519f0 When encountering a duplicate symbol, show source of the first symbol f8e2b7e Minor doc fixes to GHC.Generics a883c1b Missing @since annotations in GHC.Generics e5a0a89 Suppress substitution assertions to fix tests 0d60165 Simplify ghc-boot database representation with new type class. 94048f9 Hide the CallStack implicit parameter 86897e1 Implement basic uniform warning set tower ba88aab Fix LOOKS_LIKE_PTR for 64-bit platforms 2ad46a8 Add some Outputable instances 02e3ce0 Typo in docs 7329310 Fix runtime linker error message when old symbol had no owner dd0b7c7 Avoid mangled/derived names in GHCi autocomplete (fixes #11328) ddd38e7 Update unix submodule to latest snapshot af8fdb9 TyCoRep: Implement some helpers for dropping/checking Levity arguments 2fb6a8c Remote GHCi: Optimize the serialization/deserialization of byte code 7cb1fae Remote GHCi: batch the creation of strings c996db5 Remote GHCi: parallelise BCO serialization 01c587c Fix Windows build after D1874 07ed241 Use a correct substitution in tcCheckPatSynDecl a7ad0b9 Make TypeError a newtype, add changelog entry db97ed9 Add (failing) test for #11247 871c96f TcMType: Add some elementary notes 92c46a4 Update cabal_macros_boot.h 483858e Update binary submodule to 0.8.2.0 release db121b2 Allow all RTS options to iserv 28f951e Overhaul the Overhauled Pattern Match Checker bbc0ec5 Fix a few loose ends from D1795 4f9967a Remove unused LiveVars and SRT fields of StgCase and StgLetNoEscape 91a56e9 Use default xz compression level 70980b1 GHCi: Fix Windows build (again) 8aa9f35 Fix @since annotations for renamed pretty{CallStack,SrcLoc} 38af3d1 Add a derived `Show SrcLoc` instance b49d509 Add test for #11516 5d73fb6 Revert "Remove unused LiveVars and SRT fields of StgCase and StgLetNoEscape" f1f5837 unlit: mark local functions as 'static' 72545c7 hp2ps: mark local functions as 'static' f3923d5 testsuite: ignore *.prof.normalised files 1060301 mkDocs: Update for xz c96acf3 mkDocs: Fix fallout from c5f4f95c64006a9f 66fa0ed validate: enable -DDEBUG in stage 1 by default 7362809 rts: drop unused calcLiveBlocks, calcLiveWords 9e43c7f rts: mark scavenge_mutable_list as static 4f283a6 rts: mark 'copied' as static 256c1b3 rts: drop unused getThreadCPUTime 3dbd836 rts: mark 'wakeBlockingQueue' as static 8abc7e7 rts: drop unused mut_user_time_during_heap_census 39cba20 rts: mark 'removeFromRunQueue' as static 7a48865 rts: mark 'setProgName' as static a49c9d4 rts: drop unused 'traverseAllRetainerSet' c358567 rts: mark 'blockedThrowTo' as static e1ca583 rts: mark 'ccs_mutex' and 'prof_arena' as static 0e51109 rts: drop unused 'traceEventThreadRunnable' 0a2bd9c rts: mark 'shutdownCapability' as static c0a0ee3 Fix haddocks for TypeError b3e9452 Bump haddock submodule 8263d09 Remove unused export from TcUnify 2cf3cac Allow foralls in instance decls 20f90ea Fix SimpleFail12 error output e2b66a0 user-guide: Add cross-reference for -XUnicodeSyntax 4e65301 Add Edward Kmett's example as a test case 6036cb6 Comments only, on the invariants of GlobalRdrEnv a96c4e7 Add comments to TcCoercibleFail ee11a84 White space and comments only 8871737 Document and improve superclass expansion e72665b Comment out some traceFlat calls 7212968 Improve tracing in TcInteract d6b68be Improve error messages for recursive superclasses f79b9ec Use runTcSDeriveds for simplifyDefault 6252b70 A small, local refactoring of TcSimplify.usefulToFloat 43e02d1 Fix a nasty superclass expansion bug 5a58634 release notes: Note new two-step allocator 96d4514 Some tiding up in TcGenDeriv fac0efc Define mkTvSubst, and use it c9ac9de Test Trac #11552 489a9a3 Define tyConRolesRepresentational and use it 023fc92 Remove unused LiveVars and SRT fields of StgCase da19c13 Print * has Unicode star with -fprint-unicode-syntax 16cf460 testsuite: Un-break T5642 4ec6141 Fix the removal of unnecessary stack checks 04fb781 Early error when crosscompiling + haddock/docs bfec4a6 Unset GREP_OPTIONS in build system 1f894f2 Restore derived Eq instance for SrcLoc c8702e3 TcErrors: Fix plural form of "instance" error 99cb627 TcPatSyn: Fix spelling of "pattern" in error message 7953b27 DynFlags: drop tracking of '-#include' flags 2f9931e add Template Haskell regression test for #9022. 93e2c8f Expand users' guide TH declaration groups section (#9813) d80caca Error early when you register with too old a version of Cabal. c57d019 docs: add newline after '.. ghc-flag::' a824972 mkUserGuide: fix option wrapping in a table b565830 Wrap solveEqualities in checkNoErrs d27da53 Replace mkTvSubstPrs (a `zip` b) with zipTvSubst a b 8500855 Always do eta-reduction 62d1888 Comments about ru_auto 023bf8d Ignore untracked in nofib 51a3392 sizeExpr: fix a bug in the size calculation 46af683 compiler: Do not suggest nor complete deprecated flags fix trac issue #11454 efba41e Another batch of typo fixes in non-code dbf72db Build the substitution correctly in piResultTy b7dfbb4 Add test for #11319 8da6a16 Revert "sizeExpr: fix a bug in the size calculation" be3d7f6 Add IsList instance for CallStack, restore Show instance for CallStack f3b9db3 Revert "Build the substitution correctly in piResultTy" c6485d5 Simplify AbsBinds wrapping 1251518 Beef up tc124 d084624 Improve pretty-printing of HsWrappers 24305be Minor refactoring to tauifyMultipleMatches 6cf9b06 User manual improvments f37bb54 testsuite: tweak error messages for new Show instance cd4a7d0 renamer discards name location for HsRecField 4bba19a Update directory submodule to v1.2.5.1 release 18cd712 Improve error message suppression bb7f230 Comments only 160765f Document -dynamic-too (#11488) f6b98ea Tiny refactor; use guards instead of 'if' 0057125 Comments and white space e2f7d77 A tiny, outright bug in tcDataFamInstDecl 023742e Add a testcase for #11362 426a25c Make T11361 actually run with reversed uniques 3c39bec Rename missing-pat-syn-sigs to missing-pat-syn-signatures ed69b21 Add missing newlines at end of file [skip ci] d066e68 Testsuite: delete only_compiler_types, assume ghc c8df3f1 Bump haddock submodule 525a304 Make bootstrapping more robust 693a54e Improved error message about exported type operators. af5a0e5 Fix two wrong uses of "data constructor" in error msgs 3116003 PowerPC: Improve float register assignment. 49c5cb4 Fix typos 5fc06b9 Suggest candidate instances in error message ad30c76 Remove documentation for -Wlazy-unlifted-bindings 2b906af DynFlags: Don't panic on incompatible Safe Haskell flags 6f25fb3 Testsuite: delete compiler_lt/le/gt/ge setup functions 34c9523 Comments only 21b4228 Simplify the defn of coreViewOneStarKind 4c6e95e Small refactor and comments b962bcc Make exactTyCoVarsOfTypes closed over kinds. 90f3561 Existentials should be specified. aff5bb4 Add missing kind cast to pure unifier. 7d8031b Remove extraneous fundeps on (~) 6f952f5 Use CoercionN and friends in TyCoRep 43468fe Fix #11241. 489e6ab Fix #11246. a615215 Fix #11313. 67d2226 Derive Eq and Ord instance for SrcLoc and RealSrcLoc a82956d Remove superfluous code when deriving Foldable/Traversable 525b54c users-guide: Fix typos 0c420cb Comments only (#11513) 27842ec Fix thinko that crept into D1908 01449eb Fix desugaring of bang-pattern let-bindings b529255 (Another) minor refactoring of substitutions 4d031cf Improve piResultTys and friends a008ead Take type-function arity into account 206a8bf Unwire Typeable representation types 0b68cbe Bump haddock submodule 8b073f6 A few more typos in non-code 2f733b3 Delete support for deprecated "-- # ..."-style haddock options d738e66 Modifier letter in middle of identifier is ok c6007fe Pass -haddock to tests in should_compile_*flag*_nohaddock a8653c8 Docs: no space in `-i⟨dir1⟩:⟨dir2⟩` [skip ci] 6cec905 Refactoring only: use ExprLStmt 3259bf6 Fix a bug in ApplicativeDo (#11612) 2340485 Fix a double-free bug in -fexternal-interpreter 80d35be Use a better test for profiling 1ef7add Add test (only) to assure that #11535 is fixed 9634e24 unexport MAKEFLAGS when running tests (#11569) 0b00add Add test for #6132: hash bang + CPP 6e691ca Testsuite: pass '-s --no-print-directory' to MAKE f451039 Build system: fix sed expression (#11537) bb9cd45 Fix GHC.Stats documentation markup (#11619) ed11909 Docs: -keep-llvm-file(s)/-ddump-llvm imply -fllvm d3cf2a9 Add missing files 31c312e Testsuite: delete Windows line endings [skip ci] (#11631) 8626ac9 Testsuite: delete Windows line endings [skip ci] (#11631) 754a2f2 Testsuite: delete Windows line endings [skip ci] (#11631) 6074c10 Testsuite: delete Windows line endings [skip ci] (#11631) d5e8b39 Testsuite: delete Windows line endings [skip ci] (#11631) 978c3ea Testsuite: accept output without Windows line endings (#11631) 42f06f6 Testsuite: accept output without Windows line endings (#11631) 28620ba Testsuite: delete Windows line endings [skip ci] (#11631) 6d0aa9f Testsuite: delete Windows line endings [skip ci] (#11631) 73e4095 Testsuite: cleanup profiling/should_run/all.T (#11521) 176be87 Filter out -prof callstacks from test output (#11521) 661aa07 Testsuite: failing profiling tests (#10037) 2aee419 Allow combining characters in identifiers (#7650) a3e0e93 Testsuite: MAKEFLAGS is magic, do not unexport it 32a9a7f Extend `-Wunrecognised-warning-flag` to cover `-f(no-)warn-*` ce36115 Follow-up to 32a9a7f514bdd33ff72a673ade d8c64e8 Address #11471 by putting RuntimeRep in kinds. a9dc62a Remove "use mask" from StgAlt syntax 009a999 TyCoRep: Add haddock sections c1efdcc Overload the static form to reduce verbosity. feb19ea testsuite: mark tests broken on powerpc64 8e19d3a base: A selection of fixes to the comments in GHC.Stats 0c7db61 ApplicativeDo: Handle terminal `pure` statements 6319a8c HscMain: Delete some unused code 673efcc Add more type class instances for GHC.Generics 6658491 Make warning names more consistent 52879d1 Reconstruct record expression in bidir pattern synonym ebaa638 Bump haddock.base allocations 073e20e cmpTypeX: Avoid kind comparison when possible 6739397 (Alternative way to) address #8710 6350eb1 Handle multiline named haddock comments properly e38c07b Improve accuracy of suggestion to use TypeApplications 20ab2ad Note new GHC.Generics instances in release notes 116528c Improve pattern synonym error messages (add `PatSynOrigin`) 8e6e022 Testsuite: Introduce config.plugin_way_flags. e02b8c8 Testsuite: for tests that use TH, omit *all* prof_ways 90fa8cf Mark tests for #11643, #11644, #11645 and #9406 expect_broken 9b49c65 Testsuite: delete empty files [skip ci] 1badf15 Testsuite: do not write empty files on 'make accept' bb5afd3 Print which warning-flag controls an emitted warning bbfff22 Unconditionally handle TH known key names. a026112 Typos in comments, etc. e3f341f Fix and refactor strict pattern bindings a81e9d5 Special case for desugaring AbsBinds 4ddfe13 Get the right in-scope set in specUnfolding 7496be5 Exclude TyVars from the constraint solver 253ccdf Comments and white space only b4dfe04 Fix kind generalisation for pattern synonyms e193f66 Filter out BuiltinRules in occurrence analysis ef7b1d5 Test Trac #11611 eee040c Update transformer submodule to v0.5.2.0 release 890e2bb GHC.Generics: Ensure some, many for U1 don't bottom 3ee4fc0 rts: drop unused global 'blackhole_queue' b9c697e Print which flag controls emitted desugaring warnings 869d9c6 Print which flag controls emitted lexer warnings 82f200b Annotate `[-Wredundant-constraints]` in warnings (re #10752) b6c61e3 Print which flag controls emitted SafeHaskell warnings 3cd4c9c Annotate `[-Wdeferred-type-errors]` in warnings (re #10752) 46f3775 Default to -fno-show-warning-groups (re #10752) 171d95d Missing Proxy instances, make U1 instance more Proxy-like ad4428d base: Mark Data.Type.Equality as Trustworthy 2535c82 Fix bug where reexports of wired-in packages don't work. f72bdbd Refactor `warnMissingSignatures` in `RnNames.hs` 16e97c1 Build system: Correctly pass `TARGETPLATFORM` as host 2e49a31 DynFlags: Add -Wredundant-constraints to -Wall e3b9dbf Testsuite: check actual_prof_file only when needed de01de7 Remove some more Windows line endings [skip ci] f8a5dd0 Only add -fshow-warning-groups for ghc >= 7.11 (#10752) 49c55e6 Skip TEST=TcCoercibleFail when compiler_debugged 3c29c77 Do not check synonym RHS for ambiguity 243e2ab Comments only 2d52c3a A bit more tracing in TcHsType.tcTyVar a0899b2 Remove unnecessary isTyVar tests in TcType 57b4c55 Don't complain about unused Rule binders 286dc02 Fix an outright bug in expandTypeSynonyms aea1e5d Use tyConArity rather than (length tvs) 91a6a9c Add Monoid instance for FastString 15517f3 SimplEnv: Add Haddock headings to export list 1f3d953 users-guide: Mention #11558 in release notes 120b9cd rts/timer: use timerfd_* on Linux instead of alarm signals 6ca9b15 GHCi: Fix load/reload space leaks (#4029) 3801262 Fix printing of an `IfacePatSyn` 1d6177b Using unsafe foreign import for rtsSupportsBoundThreads (part of #9696) bd681bc Drop module qualifier from punned record fields (#11662) ade1a46 Fix minimum alignment for StgClosure (Trac #11395) 5e2605e GhcMake: Clang/ASSERT fix 13a801a Revert "Mark tests for #11643, #11644, #11645 and #9406 expect_broken" 82e36ed Reduce fragmentation from m32_allocator 90e1e16 Split external symbol prototypes (EF_) (Trac #11395) 1a9734a template-haskell: Drop use of Rank2Types/PolymorphicComponents 941b8f5 template-haskell: remove redundant CPP use 1c76e16 template-haskell: define `MonadFail Q` instance 4c3a0a4 Fix the implementation of lazyId 5a494d8 Refactoring around TcPatSyn.tcPatToExpr 374f919 Update Cabal submodule to latest HEAD snapshot c42cdb7 fix Float/Double unreg cross-compilation fc16690 Fix #11624, cannot declare hs-boot if already one in scope. c937f42 Add regression test for #11555 a1c4230 Use catchException in a few more places 30ee910 Make `catch` lazy in the action f3def76 add regression test for #11145. 767ff7c Document Quasi-quotes/list comprehension ambiguity a74a384 Include version in AC_PACKAGE_TARNAME f8056fc Make integer-gmp operations more strict d48220e Add Note [Running splices in the Renamer] 90b8af0 Fix readme link to FixingBugs wiki page 06b70ff Add doc to (<$>) explaining its relationship to ($) 8626d76 rtx/posix/Itimer.c: Handle return value of `read` 6a2992d Add MonadUnique instance for LlvmM e764ede Add ghc-flag directory for -XPatternGuards 2908ae8 Handle unset HOME environment variable more gracefully 3ea11eb Move getOccFS to Name 7ba817c Bump allocations for T6048 2f45cf3 Add -foptimal-applicative-do e46742f rts: fix threadStackUnderflow type in cmm 4d791b4 Simplify: Make generated names more useful 41051dd ghci: add message when reusing compiled code #9887 92821ec LlvmCodeGen: Fix generation of malformed LLVM blocks 9ee51da users_guide: Break up -fprint-* description d12166a Fix the name of the Word16ElemRep wired-in datacon 3f60ce8 Add regression test for #11702 18fbfa3 Move and expand (slightly) TypeApplications docs e9bf7bb Fix #11407. 84c773e Fix #11334. 35d37ff Fix #11401. 972730c Refactor visible type application. 6c768fc Expand Note [Non-trivial definitional equality] 693b38c Test case for #11699 in typecheck/should_compile e7a8cb1 Document TypeInType (#11614) 55577a9 Fix #11648. 3f5d1a1 Allow eager unification with type families. de4df6b Testsuite wibbles from previous commits. 19be538 Remove redundant anonymiseTyBinders (#11648) 857e9b0 Incorporate bgamari's suggestions for #11614. 1eefedf Fix #11357. aade111 Fix #11473. f602f4a Fix printing of "kind" vs. "type" 5d98b8b Clean up some pretty-printing in errors. 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) f703fd6 Add +RTS -AL 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) 3910306 Add -XStaticPointers to the flag reference. 08e47ca FunDep printer: Fix unicode arrow 43589f5 testsuite: add CmmSwitchTest for 32-bit platforms ae7e9cb Fix Windows build after Ticky changes 8e92974 Testsuite: mark T8761 expect_broken #12077 a1f3bb8 Fix failing T12010 d9cb7a8 compiler/iface: compress .hi files e44a6f9 users-guide: Vector version of Thomson-Wheeler logo 6d6d6e4 rules/sphinx: Add missing dependency on conf.py for pdf rule cf1efc7 users-guide: Fix index in PDF output da3c1eb Enable checkProddableBlock on x86_64 527ed72 Fix deriving Ord when RebindableSyntax is enabled c81e7b2 Build system: temp solution for parallelisation bug (#11960) f669764 Use `setSession` instead of `modifySession` when setting `HscEnv` a70a6da rts/Linker.c: Fix compile error on Arm fa58710 Update format specifiers for Tickey.c 2230c88 Testsuite: fix T12010 for real 8c9b8a3 Allow unlifted types in pattern synonym result type d835ee6 Fix build by removing unused import. 785b38f testsuite: Update max_bytes_used for T4029 9bb2772 Revert "compiler/iface: compress .hi files" 4f5b335 Suppress the warning about __sync_fetch_and_nand (#9678) 03d8960 Don't split the arg types in a PatSyn signature eb8eb02 Spelling in comment 839b424 Remove unused Type.splitFunTysN 9c3e55b Comments only 35053eb Testsuite: delete check_files_written 1bf5c12 Spelling 8f7d016 Add support for unicode TH quotes (#11743) 4c6e69d Document some benign nondeterminism 9d06ef1 Make Arrow desugaring deterministic 95dfdce Remove 'deriving Typeable' statements fe8a4e5 Runtime linker: Break m32 allocator out into its own file 1956cbf Fix: #12084 deprecate old profiling flags 31f1804 Testsuite: delete drvfail015.stderr-7.0 [skip ci] 1319363 Always use native-Haskell de/encoders for ASCII and latin1 ac38c02 Update submodule vector [skip ci] 961ed26 Fix broken links to mdo papers eec88ee RTS: simplify read_heap_profiling_flag bdc5558 Testsuite: introduce TEST_HC_OPTS_INTERACTIVE (#11468) 8408d84 Spelling in comments 6a5bce1 Testsuite: also normalise platform-dependent .stdout/stderr f07bf19 Testsuite: fix enum01/02/03 on Windows (#9399) 5020bc8 Testsuite: add a test for #5522 (-fliberate-case -fspec-constr) 0f1e315 Fix bytecode gen to deal with rep-polymorphism e9e61f1 Reduce special-casing for nullary unboxed tuple 5b8bec2 StgCmmExpr: Fix a duplication 5b145c9 Coverage.hs: Fix a duplication cd50d23 StgCmmCon: Do not generate moves from unused fields to local variables b43a793 More fixes for unboxed tuples 72fd407 Comments and white space only 59250dc StgCmmExpr: Remove a redundant list 3a00ff9 Do not init record accessors as exported 3f20da1 Typos in comments d0dd572 Clarify users' guide section on GeneralizedNewtypeDeriving d40682e Testsuite: don't use --interactive in Makefiles 1e67010 RtsFlags.c: Const correct fixes 7e4f3dc StgCmmUtils.emitMultiAssign: Make assertion msg more helpful 0ffa23d Remove unused FAST_STRING_NOT_NEEDED macro defs 930e74f Update a Cmm note 0676e68 Fix detection and use of `USE_LIBDW` cb2c042 Use nameSetAny in findUses f2b3be0 Improve failed knot-tying error message. 99ace83 Kill nameSetElems in getInfo 36d254a Testsuite: run tests in /tmp/ghctest-xxx instead of /tmp/ghctest/xxx 940229c Travis: llvm's apt repository is offline cb9f635 Localize orphan-related nondeterminism d348acd Serialize vParallelTyCons in a stable order 3eac3a0 Add nameSetElemsStable and fix the build dad39ff Remove dead generics-related code from OccName d753ea2 Use UniqDSet for finding free names in the Linker e2446c0 Kill nameSetElems in findImportUsage be47085 Kill nameSetElems in rnCmdTop 060c176 Whitespace only 1d1987e HscMain: Minor simplification 9cc6fac Make FieldLabelEnv a deterministic set 2046297 Document putSymbolTable determinism 4842a80 Derive instances in Data.Data 1dadd9a testsuite: Mark broken tests on powerpc64le 3747372 Refactored SymbolInfo to lower memory usage in RTS 079c1b8 Use useful names for Symbol Addr and Names in Linker.c 02f893e integer-gmp: Make minusInteger more efficient 4aa299d PrelInfo: Ensure that tuple promoted datacon names are in knownKeyNames eda73a3 RTS SMP: Use compiler built-ins on all platforms. 4dbacbc Rename isPinnedByteArray# to isByteArrayPinned# b948a1d Refactor the SymbolName and SymbolAddr types to be pointers 5965117 Replace hand-written Bounded instances with derived ones 0d963ca Add relocation type R_X86_64_REX_GOTPCRELX 4848ab9 Testsuite: fixup comments for T9872d [skip ci] 886f4c1 Better comment for orIfNotFound. f91d87d Failing test-case for #12135. 3042a9d Use UniqDFM for HomePackageTable 48e9a1f Implement deterministic CallInfoSet a90085b Add @since annotations to base instances e684f54 Desugar ApplicativeDo and RecDo deterministically 31ba8d6 Kill nameSetElems 46d2da0 Document putDictionary determinism 3e7a876 Kill foldUniqSet 1937ef1 Make UnitIdMap a deterministic map a13cb27 Merge MatchFixity and HsMatchContext 77ccdf3 Kill occSetElts 7fea712 Use a deterministic map for imp_dep_mods d05dee3 CoreToStg: Remove hand-written Eq instances of HowBound and LetInfo 4426c5f Kill two instances of uniqSetToList 0d6f428 Fix build by removing unused import c148212 Kill varSetElems in checkValidInferredKinds ad8e203 Use DVarSet in Vectorise.Exp 3b698e8 Document determinism in pprintClosureCommand 5db93d2 Make vectInfoParallelVars a DVarSet 7008515 Kill varSetElems 7d58a97 Use pprUFM in pprStgLVs 00e3a5d Typofix. 4d5b2f6 Testsuite driver: always quote opts.testdir f5f5a8a Testsuite Windows: mark T8308 expect_broken (#8308) d4b548e Add some determinism tests dd33245 Desugar: Display resulting program stats with -v2 44a3c18 Revert "Desugar: Display resulting program stats with -v2" c2bbc8b Report term sizes with -v3 even when -ddump is enabled 80cf4cf Literal: Remove unused hashLiteral function d7933cb Show sources of cost centers in .prof 8f6d292 Fix #12064 by making IfaceClass typechecking more lazy. acb9e85 Minor performance note about IdInfo. 11ff1df Fix #12076 by inlining trivial expressions in CorePrep. 48385cb Remove special casing of Windows in generic files ceaf7f1 Implement Eq TyCon directly 68c1c29 Remove Ord (CoAxiom br) 9dbf354 Testsuite: delete dead code [skip ci] e703a23 Docs: fix links to ghc-flags 70e0a56 Remove Ord Class b2624ee Remove Ord PatSyn 77b8c29 Remove Ord AltCon c22ab1a Docs: delete PatternGuards documentation b020db2 Fix Ticky histogram on Windows e9dfb6e Improve the error messages for static forms. b0a7664 prettyPrintClosure(): Untag the closure before accessing fields 47d8173 Remove Printer.c:prettyPrintClosure() bcb419a Fix #12099: Remove bogus flags 6adff01 Comments only 6905ce2 Refine imports slightly 0f0b002 Comments only 3ae18df Minor refactoring b9fa72a Small refactor to mkRuntimErrorId 9e5ea67 NUMA support c88f31a Rts flags cleanup 5990016 ModuleSet: Use an actual set instead of map to units 6ace660 rts: Fix build when USE_LARGE_ADDRESS_SPACE is undefined 9130867 Skip retc001 on OSX b40e1b4 Fix incorrect calculated relocations on Windows x86_64 29e1464 Disable T12031 on linux 2bb6ba6 rts: Fix NUMA when cross compiling d25cb61 Kill off redundant SigTv check in occurCheckExpand 15b9bf4 Improve typechecking of let-bindings c28dde3 Tidy up zonkQuantifiedTyVar 7afb7ad Get in-scope set right in top_instantiate 35c9de7 Move the constraint-kind validity check 1f66128 Beef up mkNakedCastTy 15fc528 Fix the in-scope set for extendTvSubstWithClone 599d912 Beef up isPredTy 8104f7c Remove some traceTc calls e064f50 Add to .gitignore 921ebc9 Test Trac #12055 1dcb32d A second test for Trac #12055 5cee88d Add thin library support to Windows too 7de776c Kill unused foldModuleEnv 586d558 Use UniqFM for SigOf 0497ee5 Make the Ord Module independent of Unique order d55a9b4 Update Haddock to follow change in LHsSigWcType 4f35646 Adjust error message slightly 8dfd4ae Build system: mention ghc version in bindist's `configure --help` docdir a2deee0 Testsuite: enable ghci.prog010 (#2542) 23b73c9 Don't GC sparks for CAFs 9d22fbe Rename cmpType to nonDetCmpType 753c5b2 Simplify readProcessEnvWithExitCode + set LANGUAGE=C 70a4589 Revert "Make the Ord Module independent of Unique order" e33ca0e Fix testsuite wibble 77bb092 Re-add FunTy (big patch) e368f32 Major patch to introduce TyConBinder c56f8bd CoreMonad: Update error msg function docs 930a525 Abort the build when a Core plugin pass is specified in stage1 compiler a7f65b8 Remove dead code: countOnce, countMany 498ed26 NUMA cleanups 8d33af9 CoreLint: Slightly improve case type annotation error msgs 3e8c495 CmmNode: Make CmmTickScope's Unique strict 2396d9b llvmGen: Make metadata ids a newtype 85e09b1 llvmGen: Consolidate MetaExpr pretty-printing 9bb0578 Revert accidental submodule updates e02beb1 Driver: `ghc ../Test` (without file extension) should work f72f23f Testsuite: run tests in .run instead of /tmp 6f6f515 Testsuite: write "\n" instead of "\r\n" when using mingw Python d94c405 Testsuite: validate the tests/stage1 directory with the stage1 compiler a4c8532 Validate: use `rm -f` instead of `rm` 6354991 VarEnv: Comment only 270d545 Add Bifoldable and Bitraversable to base 9649fc0 Refactor derived Generic instances to reduce allocations 4d71cc8 Avoid find_tycon panic if datacon is not in scope f12fb8a Fix trac #10647: Notice about lack of SIMD support 2897be7 PPC NCG: Fix float parameter passing on 64-bit. f4b0488 PPC NCG: Fix and refactor TOC handling. 0be38a2 llvmGen: Add strictness to metadata fields 0e92af9 Remove use of KProxy in GHC.Generics 0ba34b6 ApplicativeDo: allow "return $ e" e7e42c8 Fix double-free in T5644 (#12208) cdc14b4 Testsuite: remove Windows CR again.. [skip ci] 9cdde38 Testsuite: remove Windows CR [skip ci] cf6e656 Testsuite: remove Windows CR [skip ci] 3dc1202 Testsuite: tabs -> spaces [skip ci] 7e7094f Testsuite: tabs -> spaces [skip ci] 46ff80f Testsuite: tabs -> spaces [skip ci] 915e07c Testsuite: tabs -> spaces [skip ci] 5b03dc6 Testsuite: tabs -> spaces [skip ci] a7160fa Testsuite: tabs -> spaces [skip ci] 4a4bdda Testsuite: recover from utf8 decoding errors 6d0a4fc Testsuite: fix WAY=ghci when LOCAL=0 1ddc10b Testsuite: *do* replace backslashes in config.libdir 1d938aa Testsuite: mark tests expect broken 3b49f8f Testsuite: remove `-fforce-recomp` from default flags (#11980) 82f7f18 Testsuite: delete TEST_HC_OPTS_NO_RECOMP 135fc86 Testsuite: remove `-Wno-warn-tabs` from default flags ebaf26b Testsuite: delete dead code + cleanup e170d19 Testsuite: assume timeout_prog always exists ee3bde7 Expand and clarify the docs for ApplicativeDo (#11835) 7301404 Typos in comments d09e982 Don't quantify over Refl in a RULE 97a50f8 Delete commented-out code 1230629 Make checkFamInstConsistency less expensive a47b62c Second attempt to fix sizeExpr c0583a9 Fix build breakage due to rebase 9d62d09 Hopefully fix all the rebase-induced breakage 4e7d835 Typos in comments [skip ci] 6199588 More typos in comments [skip ci] 93f40cb Don't error on GCC inlining warning in rts 348f2db Make the Ord Module independent of Unique order (2nd try) 15641b0 Accept new (lower) allocations for T7257 7e7aeab Comments only cc92a44 Improve error message in deriving( Functor ) a1b3359 Remove unused arg to tcSuperClasses ce97b72 Expand given superclasses more eagerly 210a2e1 Test Trac #12163 3e0af46 Give lookupGRE_Name a better API e556f76 Remove unused import 643706e Narrow the warning for simplifiable constraints 2f8cd14 Narrow the use of record wildcards slightly 7fc20b0 Have Core linter accept programs using StaticPointers and -fhpc. 35d1564 Provide Uniquable version of SCC bb74021 Remove Ord TyCon 7f5d560 Very confusing typo in error message. 9a34bf1 Fix #11974 by adding a more smarts to TcDefaults. 8035d1a Fix #10963 and #11975 by adding new cmds to GHCi. 4ae950f Release notes for #11975 and #10963 df9611e Testsuite: do not copy .hi/.o files to testdir (#12112) d2958bd Improve typechecking of instance defaults c871ce4 Comments around invisibility 393928d Fix renamer panic f86a337 Remove bogus comment on ForAllTy bb84ee4 Improve pretty-printing of Avail 12c4449 Implement ReifyConStrictness for -fexternal-interpreter (#12219) d2006d0 Run all TH tests with -fexternal-interpreter (#12219) bdb0d24 Remote GHCi: separate out message types eb73219 Remote GHCi: comments only 0bab375 Fix T8761 (#12219, #12077) dadd8b8 Test Trac #12229 9bc2233 Fix typo in Data.Bitraverse Haddocks 31b5806 Clean up outdated comments in template-haskell changelog a33b498 Add template-haskell changelog note for #8761 5fdb854 s/Invisible/Inferred/g s/Visible/Required/g 4cc5a39 Refactor tcInferArgs and add comments. 8c1cedd Allow building static libs. da60e3e rts/Linker.c: Improve ugly C pre-processor hack 7843c71 Make T8761 deterministic, I hope ff1cc26 Don't run the run_command tests with ext-interp 82282e8 Remove some `undefined`s 60c24b2 Typos in user manual and code: recurisve -> recursive afa6e83 rts/Linker.c: Rename ONLY_USED_x86_64_HOST_ARCH macro bbf0aa2 Testsuite: never pick up .T files in .run directories 7593c2f Testsuite: report duplicate testnames when `make TEST=` 1f45bce Testsuite: remove one level of indentation [skip ci] 206b4a1 Testsuite: simplify extra_file handling bafd615 Testsuite: do not print timeout message 58f0086 Testsuite: open/close stdin/stdout/stderr explicitly d8e9b87 Testsuite: cleanup printing of summary 782cacf Testsuite: framework failure improvements (#11165) 6b3b631 Testsuite: run all indexed-types ways on ./validate --slow 0eb0378 Testsuite: do not add -debug explicitly in .T file 3fb9837 Testsuite: mark tests expect_broken af21e38 Don't omit any evidence bindings 23b80ac Deal correctly with unused imports for 'coerce' dc62a22 Wibble error message for #11471 dd92c67 Stop the simplifier from removing StaticPtr binds. 2e9079f Test Trac #12185 848e3ce Testsuite: fixes for python2.6 support 9a645a1 Refactor match to not use Unique order 8f7194f Double the file descriptor limit for openFile008 1084d37 Testsuite: use ignore_stderr/stdout instead of ignore_output 24194a6 Fix pretty-printer for IfaceCo e8d6271 Testsuite: do not depend on sys.stdout.encoding fb6e2c7 Delete Ord Unique 9854f14 Add a new determinism test b6b20a5 Reorganize some determinism tests 480e066 Remove ufmToList b8b3e30 Axe RecFlag on TyCons. 0701db1 Updates to handle new Cabal 430f5c8 Trac #11554 fix loopy GADTs 6a5d13c nativeGen: Allow -fregs-graph to be used f68d40c ghc-pkg: Drop trailing slashes in computing db paths f1e16e9 CmmExpr: remove unused `vgcFlag` function b65363d Fix check_uniques in non-unicode locale 0afc41b Testsuite: be less strict about topHandler03's stderr c27ce26 users-guide: Fix markup in release notes 81b437b Add NamedThing (GenLocated l e) instance b412d82 Allow one type signature for multiple pattern synonyms 6ba4197 rules/sphinx.mk: stop xelatex on error ee8d1fa Remove unused oc->isImportLib (#12230) 6377757 Linker: some extra debugging / logging cbfeff4 Remove uniqSetToList 0d522b8 Document some benign nondeterminism 0ab63cf Kill varEnvElts in seqDmdEnv 01f449f Fix 32-bit build failures 9031382 MkCore: Fix some note names a6819a0 base: Add release date to changelog bf7cbe7 users-guide: Note multiple pattern signature change in relnotes afec447 testsuite: Add testcase for #12355 2a3af15 Treat duplicate pattern synonym signatures as an error 3b2deca users-guide: Remove static field type from rts-flag 331febf CallArity: Use not . null instead of length > 0 0bd7c4b Enum: Ensure that operations on Word fuse 18e71e4 Revert "Fix 32-bit build failures" 890ec98 Revert "Linker: some extra debugging / logging" e10497b Kill some varEnvElts 85aa6ef Check generic-default method for ambiguity 1267048 Extra ASSERTs for nameModule 55e43a6 Use DVarEnv for vectInfoVar 5f79394 Delete out-of-date comment 895eefa Make unique auxiliary function names in deriving cbe30fd Tidy up tidying f2d36ea White space only 6cedef0 Test Trac #12133 27fc75b Document codegen nondeterminism 18b782e Kill varEnvElts in zonkEnvIds 1b058d4 Remove varEnvElts b7b130c Fix GetTime.c on Darwin with clock_gettime f560a03 Adds x86_64-apple-darwin14 target. 567dbd9 Have addModFinalizer expose the local type environment. 56f47d4 Mention addModFinalizer changes in release notes. 672314c Switch to LLVM version 3.8 b9cea81 Show testcase where demand analysis abortion code fails 979baec --without-libcharset disables the use of libcharset bedd620 Style changes for UniqFM 6ed7c47 Document some codegen nondeterminism 9858552 Use deterministic maps for FamInstEnv 34085b5 Correct the message displayed for syntax error (#12146) 64bce8c Add Note [FamInstEnv determinism] 6e280c2 Utils: Fix `lengthIs` and `lengthExceeds` for negative args 0481324 Use UniqDFM for InstEnv b8cd94d GHC.Stack.CCS: Fix typo in Haddocks 91fd87e FastString: Reduce allocations of concatFS 15751f2 FastString: Add IsString instance c4a9dca FastString: Supply mconcat implementation fc53d36 OccName: Implement startsWithUnderscore in terms of headFS 83e899a TysWiredIn: Use map lookup for built-in OccNames 5446684 DsExpr: Remove unnecessary usage of concatFS From git at git.haskell.org Fri Jul 8 14:12:48 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 8 Jul 2016 14:12:48 +0000 (UTC) Subject: [commit: ghc] ghc-7.10: release notes: takes url attribute, not href (f4e783e) Message-ID: <20160708141248.7B1253A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-7.10 Link : http://ghc.haskell.org/trac/ghc/changeset/f4e783e6cdcb83592643ad3f726f5d607f78e1e1/ghc >--------------------------------------------------------------- commit f4e783e6cdcb83592643ad3f726f5d607f78e1e1 Author: Ben Gamari Date: Thu Dec 10 11:03:42 2015 +0100 release notes: takes url attribute, not href >--------------------------------------------------------------- f4e783e6cdcb83592643ad3f726f5d607f78e1e1 docs/users_guide/7.10.3-notes.xml | 32 ++++++++++++++++---------------- 1 file changed, 16 insertions(+), 16 deletions(-) diff --git a/docs/users_guide/7.10.3-notes.xml b/docs/users_guide/7.10.3-notes.xml index 90464a3..f605028 100644 --- a/docs/users_guide/7.10.3-notes.xml +++ b/docs/users_guide/7.10.3-notes.xml @@ -20,10 +20,10 @@ Starting with 7.10.2 GHC would simplify both the left- and right-hand-sides of rewrite rules, causing a variety of unexpected behavior. Simplification of the LHS resulted in various rules to fail to fire (Trac #10528, in + url="https://ghc.haskell.org/trac/ghc/ticket/10528">Trac #10528, in particular affecting the widely used text library) whereas rewrites of the RHS broke some of the more exotic uses of rewrite rules - (e.g. HERMIT, Trac + (e.g. HERMIT, Trac #10829). @@ -32,7 +32,7 @@ A bug in the simplifier's treatment of phantom type variables in rules resulting in a compiler-crash has been fixed. (Trac #10689). + url="https://ghc.haskell.org/trac/ghc/ticket/10689">Trac #10689). @@ -40,7 +40,7 @@ A simplifier bug resulting in incorrect results when comparing against -0.0 has been fixed (Trac #9238). + url="https://ghc.haskell.org/trac/ghc/ticket/9238">Trac #9238). @@ -48,9 +48,9 @@ The compiler is now better able to work around platform limits on command-line length on Windows thanks to support for response files - (Trac + (Trac #10375) and an upgrade to the GCC toolchain (Trac + url="https://ghc.haskell.org/trac/ghc/ticket/10726">Trac #10726) @@ -58,7 +58,7 @@ The linker is now far less verbose when faced with certain warning conditions on Windows. - (Trac + (Trac #9297). @@ -66,7 +66,7 @@ Framework flags are now included in the linker command line on Mac OS X - (Trac + (Trac #10568). @@ -75,7 +75,7 @@ Compiler error messages containing Unicode characters no longer crash the compiler on platforms without Unicode support. - (Trac + (Trac #6037). @@ -84,7 +84,7 @@ ARM support should be substantially more reliable as the compiler now takes precautions to avoid linking against Thumb code (Trac #10375). + url="https://ghc.haskell.org/trac/ghc/ticket/10375">Trac #10375). Unfortunately the fix involved breaking some configurations. See the entry in the "Known Bugs" section below. @@ -95,20 +95,20 @@ A bug in the typechecker's treatment of PartialTypeSignatures which previously resulted in a compile-time crash has been fixed. (Trac #10438). + url="https://ghc.haskell.org/trac/ghc/ticket/10438">Trac #10438). A typechecker bug leading to the compiler crashing has been resolved - (Trac + (Trac #10489). - Due to a + Due to a security issue , Safe Haskell now forbids annotations in programs marked as -XSafe @@ -119,7 +119,7 @@ The Template Haskell getQ and putQ functions are fixed (having been broken since GHC - 7.10.1, (Trac + 7.10.1, (Trac #10596). @@ -157,9 +157,9 @@ Unfortunately the fix for - Trac #10375 + Trac #10375 required that support for the ARM Thumb instruction set be disabled. - See Trac + See Trac #11058 for details. From git at git.haskell.org Fri Jul 8 14:12:51 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 8 Jul 2016 14:12:51 +0000 (UTC) Subject: [commit: ghc] ghc-8.0: rules/sphinx.mk: stop xelatex on error (b819d44) Message-ID: <20160708141251.22CC93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.0 Link : http://ghc.haskell.org/trac/ghc/changeset/b819d4464ee835fef21a4dd403dc18c14db27426/ghc >--------------------------------------------------------------- commit b819d4464ee835fef21a4dd403dc18c14db27426 Author: Markus Rothe Date: Sun Jun 26 11:28:36 2016 +0200 rules/sphinx.mk: stop xelatex on error This avoids the interactive prompt of xelatex on error. (cherry picked from commit 6ba4197e006b6d6bc2657141d4c10c91bd806cb3) >--------------------------------------------------------------- b819d4464ee835fef21a4dd403dc18c14db27426 rules/sphinx.mk | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/rules/sphinx.mk b/rules/sphinx.mk index f3c46b4..4929f3c 100644 --- a/rules/sphinx.mk +++ b/rules/sphinx.mk @@ -58,12 +58,12 @@ pdf : pdf_$1 ifneq "$$(BINDIST)" "YES" $1/$2.pdf: $1/conf.py $$($1_RST_SOURCES) $(SPHINXBUILD) -b latex -d $1/.doctrees-pdf $(SPHINXOPTS) $1 $1/build-pdf/$2 - cd $1/build-pdf/$2 ; xelatex $2.tex - cd $1/build-pdf/$2 ; xelatex $2.tex - cd $1/build-pdf/$2 ; xelatex $2.tex + cd $1/build-pdf/$2 ; xelatex -halt-on-error $2.tex + cd $1/build-pdf/$2 ; xelatex -halt-on-error $2.tex + cd $1/build-pdf/$2 ; xelatex -halt-on-error $2.tex cd $1/build-pdf/$2 ; makeindex $2.idx - cd $1/build-pdf/$2 ; xelatex $2.tex - cd $1/build-pdf/$2 ; xelatex $2.tex + cd $1/build-pdf/$2 ; xelatex -halt-on-error $2.tex + cd $1/build-pdf/$2 ; xelatex -halt-on-error $2.tex cp $1/build-pdf/$2/$2.pdf $1/$2.pdf endif From git at git.haskell.org Fri Jul 8 14:12:53 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 8 Jul 2016 14:12:53 +0000 (UTC) Subject: [commit: ghc] ghc-8.0: Fix check_uniques in non-unicode locale (454542f) Message-ID: <20160708141253.C09E73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.0 Link : http://ghc.haskell.org/trac/ghc/changeset/454542ff0e15eb41fc460d151814ffccb43eca84/ghc >--------------------------------------------------------------- commit 454542ff0e15eb41fc460d151814ffccb43eca84 Author: Thomas Miedema Date: Thu Jun 30 10:32:00 2016 +0200 Fix check_uniques in non-unicode locale Testcase: `LC_ALL=C make -C utils/checkUniques`. Works with python2 and python3. Reviewed by: bgamari Differential Revision: https://phabricator.haskell.org/D2372 (cherry picked from commit b65363d3eaffd453ca0790b34a5a4dc4354e176a) >--------------------------------------------------------------- 454542ff0e15eb41fc460d151814ffccb43eca84 utils/checkUniques/check-uniques.py | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/utils/checkUniques/check-uniques.py b/utils/checkUniques/check-uniques.py index 42b375e..67322c2 100755 --- a/utils/checkUniques/check-uniques.py +++ b/utils/checkUniques/check-uniques.py @@ -5,6 +5,7 @@ import os.path import sys import re import glob +import io from collections import defaultdict # keyed on unique type, values are lists of (unique, name) pairs @@ -12,7 +13,7 @@ def find_uniques(source_files): uniques = defaultdict(lambda: defaultdict(lambda: set())) unique_re = re.compile(r"([\w\d]+)\s*=\s*mk([\w\d']+)Unique\s+(\d+)") for f in source_files: - ms = unique_re.findall(open(f).read()) + ms = unique_re.findall(io.open(f, encoding='utf8').read()) for m in ms: name = m[0] _type = m[1] From git at git.haskell.org Fri Jul 8 14:12:56 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 8 Jul 2016 14:12:56 +0000 (UTC) Subject: [commit: ghc] ghc-8.0: ghc-pkg: Drop trailing slashes in computing db paths (f3bca8f) Message-ID: <20160708141256.740F83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.0 Link : http://ghc.haskell.org/trac/ghc/changeset/f3bca8f124f0f2d5e26dac083b1fe2d3ad69242a/ghc >--------------------------------------------------------------- commit f3bca8f124f0f2d5e26dac083b1fe2d3ad69242a Author: Ben Gamari Date: Mon Jun 20 09:25:05 2016 +0200 ghc-pkg: Drop trailing slashes in computing db paths Test Plan: Validate, try tests in ticket Reviewers: austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2336 GHC Trac Issues: #12194 (cherry picked from commit f68d40cbfc832a1dfc7742d02f76129ed80506e4) >--------------------------------------------------------------- f3bca8f124f0f2d5e26dac083b1fe2d3ad69242a utils/ghc-pkg/Main.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/utils/ghc-pkg/Main.hs b/utils/ghc-pkg/Main.hs index af3032d..a105ab3 100644 --- a/utils/ghc-pkg/Main.hs +++ b/utils/ghc-pkg/Main.hs @@ -789,7 +789,7 @@ mungePackageDBPaths :: FilePath -> PackageDB -> PackageDB mungePackageDBPaths top_dir db at PackageDB { packages = pkgs } = db { packages = map (mungePackagePaths top_dir pkgroot) pkgs } where - pkgroot = takeDirectory (locationAbsolute db) + pkgroot = takeDirectory $ dropTrailingPathSeparator (locationAbsolute db) -- It so happens that for both styles of package db ("package.conf" -- files and "package.conf.d" dirs) the pkgroot is the parent directory -- ${pkgroot}/package.conf or ${pkgroot}/package.conf.d/ From git at git.haskell.org Fri Jul 8 14:12:59 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 8 Jul 2016 14:12:59 +0000 (UTC) Subject: [commit: ghc] ghc-8.0: nativeGen: Allow -fregs-graph to be used (3ae474d) Message-ID: <20160708141259.1EAE83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.0 Link : http://ghc.haskell.org/trac/ghc/changeset/3ae474d18251d4e9184bf5d6cbce6ac86fdd46c1/ghc >--------------------------------------------------------------- commit 3ae474d18251d4e9184bf5d6cbce6ac86fdd46c1 Author: Ben Gamari Date: Mon Jun 20 09:24:41 2016 +0200 nativeGen: Allow -fregs-graph to be used Previously the flag was silently ignored due the #7679 and #8657. This, however, seems unnecessarily brutal and makes experimentation unduly difficult for users. Test Plan: Validate Reviewers: austin, simonmar Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2335 GHC Trac Issues: #7679, #8657 (cherry picked from commit 6a5d13c4ade5bbb84873970065a1acd1546f6c31) >--------------------------------------------------------------- 3ae474d18251d4e9184bf5d6cbce6ac86fdd46c1 compiler/nativeGen/AsmCodeGen.hs | 6 ++---- docs/users_guide/using-optimisation.rst | 28 +++++++++++++++++----------- 2 files changed, 19 insertions(+), 15 deletions(-) diff --git a/compiler/nativeGen/AsmCodeGen.hs b/compiler/nativeGen/AsmCodeGen.hs index 2285d94..9e90c43 100644 --- a/compiler/nativeGen/AsmCodeGen.hs +++ b/compiler/nativeGen/AsmCodeGen.hs @@ -538,10 +538,8 @@ cmmNativeGen dflags this_mod modLoc ncgImpl us fileIds dbgMap cmm count -- allocate registers (alloced, usAlloc, ppr_raStatsColor, ppr_raStatsLinear) <- - if False - -- Disabled, see #7679, #8657 - -- ( gopt Opt_RegsGraph dflags - -- || gopt Opt_RegsIterative dflags) + if ( gopt Opt_RegsGraph dflags + || gopt Opt_RegsIterative dflags ) then do -- the regs usable for allocation let (alloc_regs :: UniqFM (UniqSet RealReg)) diff --git a/docs/users_guide/using-optimisation.rst b/docs/users_guide/using-optimisation.rst index 5e4995d..7047f4c 100644 --- a/docs/users_guide/using-optimisation.rst +++ b/docs/users_guide/using-optimisation.rst @@ -412,20 +412,26 @@ list. .. ghc-flag:: -fregs-graph - *Off by default due to a performance regression bug. Only applies in - combination with the native code generator.* Use the graph colouring - register allocator for register allocation in the native code - generator. By default, GHC uses a simpler, faster linear register - allocator. The downside being that the linear register allocator - usually generates worse code. + :default: off due to a performance regression bug (:ghc-ticket:`7679`) + + *Only applies in combination with the native code generator.* Use the graph + colouring register allocator for register allocation in the native code + generator. By default, GHC uses a simpler, faster linear register allocator. + The downside being that the linear register allocator usually generates + worse code. + + Note that the graph colouring allocator is a bit experimental and may fail + when faced with code with high register pressure :ghc-ticket:`8657`. .. ghc-flag:: -fregs-iterative - *Off by default, only applies in combination with the native code - generator.* Use the iterative coalescing graph colouring register - allocator for register allocation in the native code generator. This - is the same register allocator as the ``-fregs-graph`` one but also - enables iterative coalescing during register allocation. + :default: off + + *Only applies in combination with the native code generator.* Use the + iterative coalescing graph colouring register allocator for register + allocation in the native code generator. This is the same register allocator + as the :ghc-flag:`-fregs-graph` one but also enables iterative coalescing + during register allocation. .. ghc-flag:: -fsimplifier-phases= From git at git.haskell.org Fri Jul 8 14:13:01 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 8 Jul 2016 14:13:01 +0000 (UTC) Subject: [commit: ghc] master: OccName: Avoid re-encoding derived OccNames (eb3d659) Message-ID: <20160708141301.BC9003A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/eb3d6595735671605c5d6294a796dc0f16f784a4/ghc >--------------------------------------------------------------- commit eb3d6595735671605c5d6294a796dc0f16f784a4 Author: Ben Gamari Date: Fri Jul 8 15:38:23 2016 +0200 OccName: Avoid re-encoding derived OccNames Previously we would form derived OccNames by first decoding the name being derived from, manipulating it in [Char] form, and then re-encoding. This is all very wasteful as we essentially always just want to concatenate. Instead we now take care to form the final name with only one concatFS. Test Plan: Validate, examing compiler allocations Reviewers: simonpj, austin Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2387 GHC Trac Issues: #12357 >--------------------------------------------------------------- eb3d6595735671605c5d6294a796dc0f16f784a4 compiler/basicTypes/OccName.hs | 42 ++++++++++++++++++++++++++++-------------- 1 file changed, 28 insertions(+), 14 deletions(-) diff --git a/compiler/basicTypes/OccName.hs b/compiler/basicTypes/OccName.hs index caaf90b..65195ab 100644 --- a/compiler/basicTypes/OccName.hs +++ b/compiler/basicTypes/OccName.hs @@ -3,7 +3,9 @@ (c) The GRASP/AQUA Project, Glasgow University, 1992-1998 -} -{-# LANGUAGE DeriveDataTypeable, BangPatterns #-} +{-# LANGUAGE DeriveDataTypeable #-} +{-# LANGUAGE BangPatterns #-} +{-# LANGUAGE OverloadedStrings #-} -- | -- #name_types# @@ -559,12 +561,19 @@ This knowledge is encoded in the following functions. NB: The string must already be encoded! -} +-- | Build an 'OccName' derived from another 'OccName'. +-- +-- Note that the pieces of the name are passed in as a @[FastString]@ so that +-- the whole name can be constructed with a single 'concatFS', minimizing +-- unnecessary intermediate allocations. mk_deriv :: NameSpace - -> String -- Distinguishes one sort of derived name from another - -> String + -> FastString -- ^ A prefix which distinguishes one sort of + -- derived name from another + -> [FastString] -- ^ The name we are deriving from in pieces which + -- will be concatenated. -> OccName - -mk_deriv occ_sp sys_prefix str = mkOccName occ_sp (sys_prefix ++ str) +mk_deriv occ_sp sys_prefix str = + mkOccNameFS occ_sp (concatFS $ sys_prefix : str) isDerivedOccName :: OccName -> Bool -- ^ Test for definitions internally generated by GHC. This predicte @@ -638,14 +647,19 @@ mkPDatasDataConOcc = mk_simple_deriv_with dataName "VPDs:" -- Overloaded record field selectors mkRecFldSelOcc :: String -> OccName -mkRecFldSelOcc = mk_deriv varName "$sel" +mkRecFldSelOcc s = mk_deriv varName "$sel" [fsLit s] -mk_simple_deriv :: NameSpace -> String -> OccName -> OccName -mk_simple_deriv sp px occ = mk_deriv sp px (occNameString occ) +mk_simple_deriv :: NameSpace -> FastString -> OccName -> OccName +mk_simple_deriv sp px occ = mk_deriv sp px [occNameFS occ] -mk_simple_deriv_with :: NameSpace -> String -> Maybe String -> OccName -> OccName -mk_simple_deriv_with sp px Nothing occ = mk_deriv sp px (occNameString occ) -mk_simple_deriv_with sp px (Just with) occ = mk_deriv sp (px ++ with ++ "_") (occNameString occ) +mk_simple_deriv_with :: NameSpace -- ^ the namespace + -> FastString -- ^ an identifying prefix + -> Maybe String -- ^ another optional prefix + -> OccName -- ^ the 'OccName' to derive from + -> OccName +mk_simple_deriv_with sp px Nothing occ = mk_deriv sp px [occNameFS occ] +mk_simple_deriv_with sp px (Just with) occ = + mk_deriv sp px [fsLit with, fsLit "_", occNameFS occ] -- Data constructor workers are made by setting the name space -- of the data constructor OccName (which should be a DataName) @@ -654,19 +668,19 @@ mkDataConWorkerOcc datacon_occ = setOccNameSpace varName datacon_occ mkSuperDictAuxOcc :: Int -> OccName -> OccName mkSuperDictAuxOcc index cls_tc_occ - = mk_deriv varName "$cp" (show index ++ occNameString cls_tc_occ) + = mk_deriv varName "$cp" [fsLit $ show index, occNameFS cls_tc_occ] mkSuperDictSelOcc :: Int -- ^ Index of superclass, e.g. 3 -> OccName -- ^ Class, e.g. @Ord@ -> OccName -- ^ Derived 'Occname', e.g. @$p3Ord@ mkSuperDictSelOcc index cls_tc_occ - = mk_deriv varName "$p" (show index ++ occNameString cls_tc_occ) + = mk_deriv varName "$p" [fsLit $ show index, occNameFS cls_tc_occ] mkLocalOcc :: Unique -- ^ Unique to combine with the 'OccName' -> OccName -- ^ Local name, e.g. @sat@ -> OccName -- ^ Nice unique version, e.g. @$L23sat@ mkLocalOcc uniq occ - = mk_deriv varName ("$L" ++ show uniq) (occNameString occ) + = mk_deriv varName "$L" [fsLit $ show uniq, occNameFS occ] -- The Unique might print with characters -- that need encoding (e.g. 'z'!) From git at git.haskell.org Fri Jul 8 14:30:12 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 8 Jul 2016 14:30:12 +0000 (UTC) Subject: [commit: ghc] wip/ttypeable: HACK: CoreLint: Kill unsaturated unlifted types check (89a68ea) Message-ID: <20160708143012.EC77F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttypeable Link : http://ghc.haskell.org/trac/ghc/changeset/89a68eafc1a6dd094c79d01c0e35ef1999581e0e/ghc >--------------------------------------------------------------- commit 89a68eafc1a6dd094c79d01c0e35ef1999581e0e Author: Ben Gamari Date: Sat Jan 30 19:53:05 2016 +0100 HACK: CoreLint: Kill unsaturated unlifted types check >--------------------------------------------------------------- 89a68eafc1a6dd094c79d01c0e35ef1999581e0e compiler/coreSyn/CoreLint.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/coreSyn/CoreLint.hs b/compiler/coreSyn/CoreLint.hs index 73e93ea..1322400 100644 --- a/compiler/coreSyn/CoreLint.hs +++ b/compiler/coreSyn/CoreLint.hs @@ -1083,7 +1083,7 @@ lintType ty@(TyConApp tc tys) = lintType ty' -- Expand type synonyms, so that we do not bogusly complain -- about un-saturated type synonyms - | isUnliftedTyCon tc || isTypeSynonymTyCon tc || isTypeFamilyTyCon tc + | isTypeSynonymTyCon tc || isTypeFamilyTyCon tc -- Also type synonyms and type families , length tys < tyConArity tc = failWithL (hang (text "Un-saturated type application") 2 (ppr ty)) From git at git.haskell.org Fri Jul 8 14:30:15 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 8 Jul 2016 14:30:15 +0000 (UTC) Subject: [commit: ghc] wip/ttypeable: Outputable: Refactor handling of CallStacks (e6ab5e5) Message-ID: <20160708143015.ACA973A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttypeable Link : http://ghc.haskell.org/trac/ghc/changeset/e6ab5e5b272b5cb6722e0e8d1a5df9882f264694/ghc >--------------------------------------------------------------- commit e6ab5e5b272b5cb6722e0e8d1a5df9882f264694 Author: Ben Gamari Date: Sun Jan 31 20:29:18 2016 +0100 Outputable: Refactor handling of CallStacks Provide callstacks in more places and consolidate handling >--------------------------------------------------------------- e6ab5e5b272b5cb6722e0e8d1a5df9882f264694 compiler/utils/Outputable.hs | 39 +++++++++++++++++++++++++++++---------- 1 file changed, 29 insertions(+), 10 deletions(-) diff --git a/compiler/utils/Outputable.hs b/compiler/utils/Outputable.hs index d61b1ec..06f1055 100644 --- a/compiler/utils/Outputable.hs +++ b/compiler/utils/Outputable.hs @@ -1,4 +1,7 @@ -{-# LANGUAGE CPP, ImplicitParams #-} +{-# LANGUAGE CPP #-} +{-# LANGUAGE ImplicitParams #-} +{-# LANGUAGE KindSignatures #-} +{-# LANGUAGE ConstraintKinds #-} {- (c) The University of Glasgow 2006-2012 (c) The GRASP Project, Glasgow University, 1992-1998 @@ -79,6 +82,9 @@ module Outputable ( pprTrace, pprTraceIt, warnPprTrace, pprSTrace, trace, pgmError, panic, sorry, assertPanic, pprDebugAndThen, + + -- * Re-exported + HasCallStack, ) where import {-# SOURCE #-} DynFlags( DynFlags, @@ -116,8 +122,9 @@ import Data.Graph (SCC(..)) import GHC.Fingerprint import GHC.Show ( showMultiLineString ) +import GHC.Exts (Constraint) #if __GLASGOW_HASKELL__ > 710 -import GHC.Stack +import GHC.Exception (CallStack, prettyCallStackLines) #endif {- @@ -1066,9 +1073,21 @@ doOrDoes _ = text "do" ************************************************************************ -} -pprPanic :: String -> SDoc -> a +#if __GLASGOW_HASKELL__ > 710 +type HasCallStack = ((?callStack :: CallStack) :: Constraint) + +pprCallStack :: (?callStack :: CallStack) => SDoc +pprCallStack = vcat $ map text $ prettyCallStackLines ?callStack +#else +type HasCallStack = (() :: Constraint) + +pprCallStack :: SDoc +pprCallStack = empty +#endif + +pprPanic :: HasCallStack => String -> SDoc -> a -- ^ Throw an exception saying "bug in GHC" -pprPanic = panicDoc +pprPanic msg doc = panicDoc msg (pprCallStack $$ doc) pprSorry :: String -> SDoc -> a -- ^ Throw an exception saying "this isn't finished yet" @@ -1094,11 +1113,11 @@ pprTraceIt desc x = pprTrace desc (ppr x) x -- | If debug output is on, show some 'SDoc' on the screen along -- with a call stack when available. #if __GLASGOW_HASKELL__ > 710 -pprSTrace :: (?callStack :: CallStack) => SDoc -> a -> a -pprSTrace = pprTrace (prettyCallStack ?callStack) +pprSTrace :: HasCallStack => String -> SDoc -> a -> a +pprSTrace msg doc = pprTrace msg (pprCallStack $$ doc) #else -pprSTrace :: SDoc -> a -> a -pprSTrace = pprTrace "no callstack info" +pprSTrace :: String -> SDoc -> a -> a +pprSTrace msg doc = pprTrace msg (text "no callstack info" $$ doc) #endif warnPprTrace :: Bool -> String -> Int -> SDoc -> a -> a @@ -1115,11 +1134,11 @@ warnPprTrace True file line msg x -- | Panic with an assertation failure, recording the given file and -- line number. Should typically be accessed with the ASSERT family of macros #if __GLASGOW_HASKELL__ > 710 -assertPprPanic :: (?callStack :: CallStack) => String -> Int -> SDoc -> a +assertPprPanic :: HasCallStack => String -> Int -> SDoc -> a assertPprPanic _file _line msg = pprPanic "ASSERT failed!" doc where - doc = sep [ text (prettyCallStack ?callStack) + doc = sep [ pprCallStack , msg ] #else assertPprPanic :: String -> Int -> SDoc -> a From git at git.haskell.org Fri Jul 8 14:30:18 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 8 Jul 2016 14:30:18 +0000 (UTC) Subject: [commit: ghc] wip/ttypeable: CoreLint: Improve debug output (b892440) Message-ID: <20160708143018.5C59A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttypeable Link : http://ghc.haskell.org/trac/ghc/changeset/b8924408e74f97b4e0e60cb90160a232060abbdb/ghc >--------------------------------------------------------------- commit b8924408e74f97b4e0e60cb90160a232060abbdb Author: Ben Gamari Date: Sun Jan 31 21:35:20 2016 +0100 CoreLint: Improve debug output >--------------------------------------------------------------- b8924408e74f97b4e0e60cb90160a232060abbdb compiler/coreSyn/CoreLint.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/coreSyn/CoreLint.hs b/compiler/coreSyn/CoreLint.hs index 1322400..f3401ee 100644 --- a/compiler/coreSyn/CoreLint.hs +++ b/compiler/coreSyn/CoreLint.hs @@ -859,7 +859,7 @@ lintTyKind tyvar arg_ty -- and then apply it to both boxed and unboxed types. = do { arg_kind <- lintType arg_ty ; unless (arg_kind `eqType` tyvar_kind) - (addErrL (mkKindErrMsg tyvar arg_ty $$ (text "xx" <+> ppr arg_kind))) } + (addErrL (mkKindErrMsg tyvar arg_ty $$ (text "Linted Arg kind:" <+> ppr arg_kind))) } where tyvar_kind = tyVarKind tyvar From git at git.haskell.org Fri Jul 8 14:30:21 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 8 Jul 2016 14:30:21 +0000 (UTC) Subject: [commit: ghc] wip/ttypeable: TcSMonad: Introduce tcLookupId (9b6a125) Message-ID: <20160708143021.0B23A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttypeable Link : http://ghc.haskell.org/trac/ghc/changeset/9b6a125113b0075182c6af055b798b969cc9519d/ghc >--------------------------------------------------------------- commit 9b6a125113b0075182c6af055b798b969cc9519d Author: Ben Gamari Date: Sun Jan 31 17:42:57 2016 +0100 TcSMonad: Introduce tcLookupId >--------------------------------------------------------------- 9b6a125113b0075182c6af055b798b969cc9519d compiler/typecheck/TcSMonad.hs | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/compiler/typecheck/TcSMonad.hs b/compiler/typecheck/TcSMonad.hs index 4c854c2..7130cce 100644 --- a/compiler/typecheck/TcSMonad.hs +++ b/compiler/typecheck/TcSMonad.hs @@ -43,7 +43,7 @@ module TcSMonad ( getTopEnv, getGblEnv, getLclEnv, getTcEvBinds, getTcEvBindsFromVar, getTcLevel, getTcEvBindsMap, - tcLookupClass, + tcLookupClass, tcLookupId, -- Inerts InertSet(..), InertCans(..), @@ -122,7 +122,7 @@ import FamInstEnv import qualified TcRnMonad as TcM import qualified TcMType as TcM import qualified TcEnv as TcM - ( checkWellStaged, topIdLvl, tcGetDefaultTys, tcLookupClass ) + ( checkWellStaged, topIdLvl, tcGetDefaultTys, tcLookupClass, tcLookupId ) import Kind import TcType import DynFlags @@ -2727,6 +2727,9 @@ getLclEnv = wrapTcS $ TcM.getLclEnv tcLookupClass :: Name -> TcS Class tcLookupClass c = wrapTcS $ TcM.tcLookupClass c +tcLookupId :: Name -> TcS Id +tcLookupId n = wrapTcS $ TcM.tcLookupId n + -- Setting names as used (used in the deriving of Coercible evidence) -- Too hackish to expose it to TcS? In that case somehow extract the used -- constructors from the result of solveInteract From git at git.haskell.org Fri Jul 8 14:30:23 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 8 Jul 2016 14:30:23 +0000 (UTC) Subject: [commit: ghc] wip/ttypeable: Fix a few TTypeRep references (0176683) Message-ID: <20160708143023.B400C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttypeable Link : http://ghc.haskell.org/trac/ghc/changeset/01766833bb1f7e14b6486897e101a7fdf386d1b2/ghc >--------------------------------------------------------------- commit 01766833bb1f7e14b6486897e101a7fdf386d1b2 Author: Ben Gamari Date: Wed Mar 16 11:51:00 2016 +0100 Fix a few TTypeRep references >--------------------------------------------------------------- 01766833bb1f7e14b6486897e101a7fdf386d1b2 compiler/deSugar/DsBinds.hs | 12 ++++++------ 1 file changed, 6 insertions(+), 6 deletions(-) diff --git a/compiler/deSugar/DsBinds.hs b/compiler/deSugar/DsBinds.hs index 95fe296..bd49e11 100644 --- a/compiler/deSugar/DsBinds.hs +++ b/compiler/deSugar/DsBinds.hs @@ -1131,10 +1131,10 @@ type TypeRepExpr = CoreExpr ds_ev_typeable :: Type -> EvTypeable -> DsM CoreExpr ds_ev_typeable ty (EvTypeableTyCon tc kind_ev) = do { mkTrCon <- dsLookupGlobalId mkTrConName - -- mkTrCon :: forall k (a :: k). TyCon -> TTypeRep k -> TTypeRep a + -- mkTrCon :: forall k (a :: k). TyCon -> TypeRep k -> TypeRep a ; tc_rep <- tyConRep tc -- :: TyCon - ; kind_rep <- getRep kind_ev (typeKind ty) -- :: TTypeRep k + ; kind_rep <- getRep kind_ev (typeKind ty) -- :: TypeRep k -- Note that we use the kind of the type, not the TyCon from which it is -- constructed since the latter may be kind polymorphic whereas the @@ -1165,8 +1165,8 @@ ds_ev_typeable ty (EvTypeableTyLit ev) ty_kind = typeKind ty -- tr_fun is the Name of - -- typeNatTypeRep :: KnownNat a => Proxy# a -> TTypeRep a - -- of typeSymbolTypeRep :: KnownSymbol a => Proxy# a -> TTypeRep a + -- typeNatTypeRep :: KnownNat a => Proxy# a -> TypeRep a + -- of typeSymbolTypeRep :: KnownSymbol a => Proxy# a -> TypeRep a tr_fun | ty_kind `eqType` typeNatKind = typeNatTypeRepName | ty_kind `eqType` typeSymbolKind = typeSymbolTypeRepName | otherwise = panic "dsEvTypeable: unknown type lit kind" @@ -1180,10 +1180,10 @@ ds_ev_typeable ty ev getRep :: EvTerm -- ^ EvTerm for @Typeable ty@ -> Type -- ^ The type @ty@ - -> DsM TypeRepExpr -- ^ Return @CoreExpr :: TTypeRep ty@ + -> DsM TypeRepExpr -- ^ Return @CoreExpr :: TypeRep ty@ -- namely @typeRep# dict@ -- Remember that --- typeRep# :: forall k (a::k). Typeable k a -> TTypeRep a +-- typeRep# :: forall k (a::k). Typeable k a -> TypeRep a getRep ev ty = do { typeable_expr <- dsEvTerm ev ; typeRepId <- dsLookupGlobalId typeRepIdName From git at git.haskell.org Fri Jul 8 14:30:26 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 8 Jul 2016 14:30:26 +0000 (UTC) Subject: [commit: ghc] wip/ttypeable: Add quick compatibility note (7a0910a) Message-ID: <20160708143026.6C28E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttypeable Link : http://ghc.haskell.org/trac/ghc/changeset/7a0910a6de9b5346cd38471a27ba08f1158e3601/ghc >--------------------------------------------------------------- commit 7a0910a6de9b5346cd38471a27ba08f1158e3601 Author: Ben Gamari Date: Fri Mar 11 17:32:13 2016 +0100 Add quick compatibility note >--------------------------------------------------------------- 7a0910a6de9b5346cd38471a27ba08f1158e3601 libraries/base/Data/Typeable.hs | 5 +++++ 1 file changed, 5 insertions(+) diff --git a/libraries/base/Data/Typeable.hs b/libraries/base/Data/Typeable.hs index f33ac48..486c5b8 100644 --- a/libraries/base/Data/Typeable.hs +++ b/libraries/base/Data/Typeable.hs @@ -28,6 +28,11 @@ -- -- == Compatibility Notes -- +-- Since GHC 8.2, GHC has supported type-indexed type representations. +-- "Data.Typeable" provides type representations which are qualified over this +-- index, providing an interface very similar to the "Typeable" notion seen in +-- previous releases. For the type-indexed interface, see "Data.Reflection". +-- -- Since GHC 7.8, 'Typeable' is poly-kinded. The changes required for this might -- break some old programs involving 'Typeable'. More details on this, including -- how to fix your code, can be found on the From git at git.haskell.org Fri Jul 8 14:30:29 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 8 Jul 2016 14:30:29 +0000 (UTC) Subject: [commit: ghc] wip/ttypeable: Various fixes (5698aa3) Message-ID: <20160708143029.1A2C33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttypeable Link : http://ghc.haskell.org/trac/ghc/changeset/5698aa3e2904a7ddbf31268ebe0dadb9b518bcb4/ghc >--------------------------------------------------------------- commit 5698aa3e2904a7ddbf31268ebe0dadb9b518bcb4 Author: Ben Gamari Date: Fri Mar 11 19:16:55 2016 +0100 Various fixes >--------------------------------------------------------------- 5698aa3e2904a7ddbf31268ebe0dadb9b518bcb4 compiler/utils/Binary.hs | 6 +++--- libraries/ghci/GHCi/TH/Binary.hs | 14 +++++++------- 2 files changed, 10 insertions(+), 10 deletions(-) diff --git a/compiler/utils/Binary.hs b/compiler/utils/Binary.hs index 97b14f8..32d8c6c 100644 --- a/compiler/utils/Binary.hs +++ b/compiler/utils/Binary.hs @@ -81,7 +81,7 @@ import Data.Time #if MIN_VERSION_base(4,9,0) import Type.Reflection import Type.Reflection.Unsafe -import GHC.Exts ( TYPE, Levity(..) ) +import Data.Kind (Type) #else import Data.Typeable #endif @@ -594,7 +594,7 @@ getTypeRepX bh = do case tag of 0 -> do con <- get bh TypeRepX rep_k <- getTypeRepX bh - Just HRefl <- pure $ eqTypeRep rep_k (typeRep :: TypeRep (TYPE 'Lifted)) + Just HRefl <- pure $ eqTypeRep rep_k (typeRep :: TypeRep Type) pure $ TypeRepX $ mkTrCon con rep_k 1 -> do TypeRepX f <- getTypeRepX bh TypeRepX x <- getTypeRepX bh @@ -608,7 +608,7 @@ instance Typeable a => Binary (TypeRep (a :: k)) where put_ = putTypeRep get bh = do TypeRepX rep <- getTypeRepX bh - case rep `eqTypeRep` typeRep of + case rep `eqTypeRep` (typeRep :: TypeRep a) of Just HRefl -> pure rep Nothing -> fail "Binary: Type mismatch" diff --git a/libraries/ghci/GHCi/TH/Binary.hs b/libraries/ghci/GHCi/TH/Binary.hs index 7851e33..2a8432b 100644 --- a/libraries/ghci/GHCi/TH/Binary.hs +++ b/libraries/ghci/GHCi/TH/Binary.hs @@ -14,10 +14,10 @@ import qualified Data.ByteString as B import Control.Monad (when) import Type.Reflection import Type.Reflection.Unsafe +import Data.Kind (Type) #else import Data.Typeable #endif -import GHC.Exts (TYPE, Levity(..)) import GHC.Serialized import qualified Language.Haskell.TH as TH import qualified Language.Haskell.TH.Syntax as TH @@ -97,11 +97,11 @@ getTypeRepX = do tag <- get :: Get Word8 case tag of 0 -> do con <- get :: Get TyCon - TypeRep rep_k <- getTypeRepX - Just HRefl <- pure $ eqTypeRep rep_k (typeRep :: TypeRep (TYPE 'Lifted)) + TypeRepX rep_k <- getTypeRepX + Just HRefl <- pure $ eqTypeRep rep_k (typeRep :: TypeRep Type) pure $ TypeRepX $ mkTrCon con rep_k - 1 -> do TypeRep f <- getTypeRepX - TypeRep x <- getTypeRepX + 1 -> do TypeRepX f <- getTypeRepX + TypeRepX x <- getTypeRepX case typeRepKind f of TRFun arg _ -> do Just HRefl <- pure $ eqTypeRep arg x @@ -112,13 +112,13 @@ instance Typeable a => Binary (TypeRep (a :: k)) where put = putTypeRep get = do TypeRepX rep <- getTypeRepX - case rep `eqTypeRep` typeRef of + case rep `eqTypeRep` (typeRep :: TypeRep a) of Just HRefl -> pure rep Nothing -> fail "Binary: Type mismatch" instance Binary TypeRepX where put (TypeRepX rep) = putTypeRep rep - get = getTypeRep + get = getTypeRepX #else instance Binary TyCon where put tc = put (tyConPackage tc) >> put (tyConModule tc) >> put (tyConName tc) From git at git.haskell.org Fri Jul 8 14:30:31 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 8 Jul 2016 14:30:31 +0000 (UTC) Subject: [commit: ghc] wip/ttypeable: Finally serialization is both general and correct (e762e12) Message-ID: <20160708143031.BB7553A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttypeable Link : http://ghc.haskell.org/trac/ghc/changeset/e762e1242cde7fcd12b1d2560ea2bd07bd3b44fb/ghc >--------------------------------------------------------------- commit e762e1242cde7fcd12b1d2560ea2bd07bd3b44fb Author: Ben Gamari Date: Wed Mar 16 12:16:20 2016 +0100 Finally serialization is both general and correct >--------------------------------------------------------------- e762e1242cde7fcd12b1d2560ea2bd07bd3b44fb compiler/utils/Binary.hs | 13 +++++-------- libraries/ghci/GHCi/TH/Binary.hs | 11 ++++------- 2 files changed, 9 insertions(+), 15 deletions(-) diff --git a/compiler/utils/Binary.hs b/compiler/utils/Binary.hs index 52bc33f..e7f0183 100644 --- a/compiler/utils/Binary.hs +++ b/compiler/utils/Binary.hs @@ -603,15 +603,12 @@ getTypeRepX bh = do TypeRepX x <- getTypeRepX bh case typeRepKind f of TRFun arg _ -> - case (typeRep :: TypeRep Type) `eqTypeRep` arg of - Just HRefl -> -- FIXME: Generalize (->) - case x `eqTypeRep` arg of - Just HRefl -> - pure $ TypeRepX $ mkTrApp f x - _ -> fail "getTypeRepX: Kind mismatch" - Nothing -> fail "getTypeRepX: Arrow of non-Type argument" + case arg `eqTypeRep` typeRepKind x of + Just HRefl -> + pure $ TypeRepX $ mkTrApp f x + _ -> fail "getTypeRepX: Kind mismatch" _ -> fail "getTypeRepX: Applied non-arrow type" - _ -> fail "Binary: Invalid TypeRepX" + _ -> fail "getTypeRepX: Invalid TypeRepX" instance Typeable a => Binary (TypeRep (a :: k)) where put_ = putTypeRep diff --git a/libraries/ghci/GHCi/TH/Binary.hs b/libraries/ghci/GHCi/TH/Binary.hs index 8d297a1..573a9e4 100644 --- a/libraries/ghci/GHCi/TH/Binary.hs +++ b/libraries/ghci/GHCi/TH/Binary.hs @@ -106,13 +106,10 @@ getTypeRepX = do TypeRepX x <- getTypeRepX case typeRepKind f of TRFun arg _ -> - case (typeRep :: TypeRep Type) `eqTypeRep` arg of - Just HRefl -> -- FIXME: Generalize (->) - case arg `eqTypeRep` x of - Just HRefl -> - pure $ TypeRepX $ mkTrApp f x - _ -> fail "getTypeRepX: Kind mismatch" - _ -> fail "getTypeRepX: Arrow of non-Type argument" + case arg `eqTypeRep` typeRepKind x of + Just HRefl -> + pure $ TypeRepX $ mkTrApp f x + _ -> fail "getTypeRepX: Kind mismatch" _ -> fail "getTypeRepX: Applied non-arrow type" _ -> fail "getTypeRepX: Invalid TypeRepX" From git at git.haskell.org Fri Jul 8 14:30:34 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 8 Jul 2016 14:30:34 +0000 (UTC) Subject: [commit: ghc] wip/ttypeable: Break recursive loop in serialization (48eeb01) Message-ID: <20160708143034.6F4613A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttypeable Link : http://ghc.haskell.org/trac/ghc/changeset/48eeb01baaab6426ec15de23be76b8e42c6b6877/ghc >--------------------------------------------------------------- commit 48eeb01baaab6426ec15de23be76b8e42c6b6877 Author: Ben Gamari Date: Wed Mar 16 13:01:45 2016 +0100 Break recursive loop in serialization >--------------------------------------------------------------- 48eeb01baaab6426ec15de23be76b8e42c6b6877 compiler/utils/Binary.hs | 18 ++++++++++++++---- libraries/ghci/GHCi/TH/Binary.hs | 18 ++++++++++++++---- 2 files changed, 28 insertions(+), 8 deletions(-) diff --git a/compiler/utils/Binary.hs b/compiler/utils/Binary.hs index e7f0183..d3ea219 100644 --- a/compiler/utils/Binary.hs +++ b/compiler/utils/Binary.hs @@ -82,6 +82,7 @@ import Data.Time import Type.Reflection import Type.Reflection.Unsafe import Data.Kind (Type) +import GHC.Exts (RuntimeRep) #else import Data.Typeable #endif @@ -579,12 +580,19 @@ instance Binary TyCon where #if MIN_VERSION_base(4,9,0) putTypeRep :: BinHandle -> TypeRep a -> IO () +-- Special handling for Type and RuntimeRep due to recursive kind relations. +-- See Note [Mutually recursive representations of primitive types] +putTypeRep bh rep + | Just HRefl <- rep `eqTypeRep` (typeRep :: TypeRep Type) + = put_ bh (0 :: Word8) + | Just HRefl <- rep `eqTypeRep` (typeRep :: TypeRep RuntimeRep) + = put_ bh (1 :: Word8) putTypeRep bh rep@(TRCon con) = do - put_ bh (0 :: Word8) + put_ bh (2 :: Word8) put_ bh con putTypeRep bh (typeRepKind rep) putTypeRep bh (TRApp f x) = do - put_ bh (1 :: Word8) + put_ bh (3 :: Word8) putTypeRep bh f putTypeRep bh x putTypeRep _ _ = fail "putTypeRep: Impossible" @@ -593,13 +601,15 @@ getTypeRepX :: BinHandle -> IO TypeRepX getTypeRepX bh = do tag <- get bh :: IO Word8 case tag of - 0 -> do con <- get bh :: IO TyCon + 0 -> return $ TypeRepX (typeRep :: TypeRep Type) + 1 -> return $ TypeRepX (typeRep :: TypeRep RuntimeRep) + 2 -> do con <- get bh :: IO TyCon TypeRepX rep_k <- getTypeRepX bh case rep_k `eqTypeRep` (typeRep :: TypeRep Type) of Just HRefl -> pure $ TypeRepX $ mkTrCon con rep_k Nothing -> fail "getTypeRepX: Kind mismatch" - 1 -> do TypeRepX f <- getTypeRepX bh + 3 -> do TypeRepX f <- getTypeRepX bh TypeRepX x <- getTypeRepX bh case typeRepKind f of TRFun arg _ -> diff --git a/libraries/ghci/GHCi/TH/Binary.hs b/libraries/ghci/GHCi/TH/Binary.hs index 573a9e4..bcf58bb 100644 --- a/libraries/ghci/GHCi/TH/Binary.hs +++ b/libraries/ghci/GHCi/TH/Binary.hs @@ -14,6 +14,7 @@ import qualified Data.ByteString as B import Type.Reflection import Type.Reflection.Unsafe import Data.Kind (Type) +import GHC.Exts (RuntimeRep) #else import Data.Typeable #endif @@ -82,12 +83,19 @@ instance Binary TyCon where get = mkTyCon <$> get <*> get <*> get putTypeRep :: TypeRep a -> Put +-- Special handling for Type and RuntimeRep due to recursive kind relations. +-- See Note [Mutually recursive representations of primitive types] +putTypeRep rep + | Just HRefl <- rep `eqTypeRep` (typeRep :: TypeRep Type) + = put (0 :: Word8) + | Just HRefl <- rep `eqTypeRep` (typeRep :: TypeRep RuntimeRep) + = put (1 :: Word8) putTypeRep rep@(TRCon con) = do - put (0 :: Word8) + put (2 :: Word8) put con putTypeRep (typeRepKind rep) putTypeRep (TRApp f x) = do - put (1 :: Word8) + put (3 :: Word8) putTypeRep f putTypeRep x putTypeRep _ = fail "putTypeRep: Impossible" @@ -96,13 +104,15 @@ getTypeRepX :: Get TypeRepX getTypeRepX = do tag <- get :: Get Word8 case tag of - 0 -> do con <- get :: Get TyCon + 0 -> return $ TypeRepX (typeRep :: TypeRep Type) + 1 -> return $ TypeRepX (typeRep :: TypeRep RuntimeRep) + 2 -> do con <- get :: Get TyCon TypeRepX rep_k <- getTypeRepX case rep_k `eqTypeRep` (typeRep :: TypeRep Type) of Just HRefl -> pure $ TypeRepX $ mkTrCon con rep_k Nothing -> fail "getTypeRepX: Kind mismatch" - 1 -> do TypeRepX f <- getTypeRepX + 3 -> do TypeRepX f <- getTypeRepX TypeRepX x <- getTypeRepX case typeRepKind f of TRFun arg _ -> From git at git.haskell.org Fri Jul 8 14:30:37 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 8 Jul 2016 14:30:37 +0000 (UTC) Subject: [commit: ghc] wip/ttypeable: TcInteract: Unused parameter (3475bde) Message-ID: <20160708143037.2DFF33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttypeable Link : http://ghc.haskell.org/trac/ghc/changeset/3475bdede97c87aa726c1f51d3e6975daddef172/ghc >--------------------------------------------------------------- commit 3475bdede97c87aa726c1f51d3e6975daddef172 Author: Ben Gamari Date: Wed Mar 16 11:04:54 2016 +0100 TcInteract: Unused parameter >--------------------------------------------------------------- 3475bdede97c87aa726c1f51d3e6975daddef172 compiler/typecheck/TcInteract.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/compiler/typecheck/TcInteract.hs b/compiler/typecheck/TcInteract.hs index 1117385..277ab6a 100644 --- a/compiler/typecheck/TcInteract.hs +++ b/compiler/typecheck/TcInteract.hs @@ -2022,7 +2022,7 @@ matchTypeable clas [k,t] -- clas = Typeable | t `eqType` liftedTypeKind = doPrimRep trTYPE'PtrRepLiftedName t | t `eqType` runtimeRepTy = doPrimRep trRuntimeRepName t | Just (tc, ks) <- splitTyConApp_maybe t -- See Note [Typeable (T a b c)] - , onlyNamedBndrsApplied tc ks = doTyConApp clas t tc ks + , onlyNamedBndrsApplied tc ks = doTyConApp clas t tc | Just (arg,ret) <- splitFunTy_maybe t = doFunTy clas t arg ret | Just (f,kt) <- splitAppTy_maybe t = doTyApp clas t f kt @@ -2057,8 +2057,8 @@ doPrimRep rep_name ty -- kind variables have been instantiated). -- -- TODO: Do we want to encode the applied kinds in the representation? -doTyConApp :: Class -> Type -> TyCon -> [Kind] -> TcS LookupInstResult -doTyConApp clas ty tc ks +doTyConApp :: Class -> Type -> TyCon -> TcS LookupInstResult +doTyConApp clas ty tc = return $ GenInst [mk_typeable_pred clas $ typeKind ty] (\[ev] -> EvTypeable ty $ EvTypeableTyCon tc ev) True From git at git.haskell.org Fri Jul 8 14:30:39 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 8 Jul 2016 14:30:39 +0000 (UTC) Subject: [commit: ghc] wip/ttypeable: Message: Import Data.Typeable.TypeRep (b7ff4de) Message-ID: <20160708143039.CDA7A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttypeable Link : http://ghc.haskell.org/trac/ghc/changeset/b7ff4dec49c8ef31a6151a4833b388305df06a6c/ghc >--------------------------------------------------------------- commit b7ff4dec49c8ef31a6151a4833b388305df06a6c Author: Ben Gamari Date: Wed Mar 16 10:35:59 2016 +0100 Message: Import Data.Typeable.TypeRep >--------------------------------------------------------------- b7ff4dec49c8ef31a6151a4833b388305df06a6c libraries/ghci/GHCi/Message.hs | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/libraries/ghci/GHCi/Message.hs b/libraries/ghci/GHCi/Message.hs index b14fca4..342c035 100644 --- a/libraries/ghci/GHCi/Message.hs +++ b/libraries/ghci/GHCi/Message.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE GADTs, DeriveGeneric, StandaloneDeriving, +{-# LANGUAGE GADTs, DeriveGeneric, StandaloneDeriving, CPP, GeneralizedNewtypeDeriving, ExistentialQuantification, RecordWildCards #-} {-# OPTIONS_GHC -fno-warn-name-shadowing -fno-warn-orphans #-} @@ -37,6 +37,10 @@ import Data.ByteString (ByteString) import qualified Data.ByteString as B import qualified Data.ByteString.Lazy as LB import Data.Dynamic +#if MIN_VERSION_base(4,9,0) +-- Previously this was re-exported by Data.Dynamic +import Data.Typeable (TypeRep) +#endif import Data.IORef import Data.Map (Map) import GHC.Generics From git at git.haskell.org Fri Jul 8 14:30:42 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 8 Jul 2016 14:30:42 +0000 (UTC) Subject: [commit: ghc] wip/ttypeable: Fix warnings (0b183c3) Message-ID: <20160708143042.88E313A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttypeable Link : http://ghc.haskell.org/trac/ghc/changeset/0b183c338b28a39c8b5d1db693efcabab97b5c86/ghc >--------------------------------------------------------------- commit 0b183c338b28a39c8b5d1db693efcabab97b5c86 Author: Ben Gamari Date: Fri Mar 11 17:51:26 2016 +0100 Fix warnings >--------------------------------------------------------------- 0b183c338b28a39c8b5d1db693efcabab97b5c86 libraries/base/Data/Typeable/Internal.hs | 17 ++++++++++++----- libraries/ghc-boot/GHC/Serialized.hs | 1 - 2 files changed, 12 insertions(+), 6 deletions(-) diff --git a/libraries/base/Data/Typeable/Internal.hs b/libraries/base/Data/Typeable/Internal.hs index c72a6f6..fc425a0 100644 --- a/libraries/base/Data/Typeable/Internal.hs +++ b/libraries/base/Data/Typeable/Internal.hs @@ -68,7 +68,7 @@ module Data.Typeable.Internal ( -- * Construction -- | These are for internal use only - mkTrCon, mkTrApp, mkTyCon, + mkTrCon, mkTrApp, mkTyCon, mkTyCon#, typeSymbolTypeRep, typeNatTypeRep, -- * Representations for primitive types @@ -223,6 +223,7 @@ mkTrCon tc kind = TrTyCon fpr tc kind fpr = fingerprintFingerprints [fpr_tc, fpr_k] -- | Construct a representation for a type application. +-- TODO: Is this necessary? mkTrApp :: forall k1 k2 (a :: k1 -> k2) (b :: k1). TypeRep (a :: k1 -> k2) -> TypeRep (b :: k1) @@ -253,7 +254,7 @@ pattern TRCon con <- TrTyCon _ con _ -- | Splits a type application. splitApp :: TypeRep a -> Maybe (AppResult a) -splitApp (TrTyCon _ a _) = Nothing +splitApp (TrTyCon _ _ _) = Nothing splitApp (TrApp _ f x) = Just $ App f x ----------------- Observation --------------------- @@ -262,7 +263,9 @@ typeRepKind :: forall k (a :: k). TypeRep a -> TypeRep k typeRepKind (TrTyCon _ _ k) = k typeRepKind (TrApp _ f _) = case typeRepKind f of - TRFun arg res -> res + TRFun _arg res -> res + -- TODO: why is this case needed? + _ -> error "typeRepKind: impossible" -- | Observe the type constructor of a quantified type representation. typeRepXTyCon :: TypeRepX -> TyCon @@ -320,14 +323,17 @@ typeRepXFingerprint (TypeRepX t) = typeRepFingerprint t -- | @since 2.01 instance Show (TypeRep a) where - showsPrec p (TrTyCon _ tycon _) = shows tycon - showsPrec p (TrApp _ f x) = shows f . showString " " . shows x + showsPrec p (TrTyCon _ tycon _) = showsPrec p tycon + showsPrec p (TrApp _ f x) = showsPrec p f . showString " " . showsPrec p x + -- TODO: Reconsider precedence -- | @since 4.10.0.0 instance Show TypeRepX where showsPrec p (TypeRepX ty) = showsPrec p ty -- Some (Show.TypeRepX) helpers: +{- +-- FIXME: Handle tuples, etc. showArgs :: Show a => ShowS -> [a] -> ShowS showArgs _ [] = id showArgs _ [a] = showsPrec 10 a @@ -337,6 +343,7 @@ showTuple :: [TypeRepX] -> ShowS showTuple args = showChar '(' . showArgs (showChar ',') args . showChar ')' +-} -- | Helper to fully evaluate 'TypeRep' for use as @NFData(rnf)@ implementation -- diff --git a/libraries/ghc-boot/GHC/Serialized.hs b/libraries/ghc-boot/GHC/Serialized.hs index 7f86df9..8653049 100644 --- a/libraries/ghc-boot/GHC/Serialized.hs +++ b/libraries/ghc-boot/GHC/Serialized.hs @@ -22,7 +22,6 @@ module GHC.Serialized ( import Data.Bits import Data.Word ( Word8 ) import Data.Data -import Data.Typeable -- | Represents a serialized value of a particular type. Attempts can be made to deserialize it at certain types From git at git.haskell.org Fri Jul 8 14:30:45 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 8 Jul 2016 14:30:45 +0000 (UTC) Subject: [commit: ghc] wip/ttypeable: Fix serialization (18e1f45) Message-ID: <20160708143045.418723A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttypeable Link : http://ghc.haskell.org/trac/ghc/changeset/18e1f450b7fd5211fe4eb00b1dbf5782c6c49230/ghc >--------------------------------------------------------------- commit 18e1f450b7fd5211fe4eb00b1dbf5782c6c49230 Author: Ben Gamari Date: Fri Mar 11 19:23:16 2016 +0100 Fix serialization >--------------------------------------------------------------- 18e1f450b7fd5211fe4eb00b1dbf5782c6c49230 compiler/utils/Binary.hs | 12 +++++++----- libraries/ghci/GHCi/TH/Binary.hs | 14 ++++++++------ 2 files changed, 15 insertions(+), 11 deletions(-) diff --git a/compiler/utils/Binary.hs b/compiler/utils/Binary.hs index 32d8c6c..5382084 100644 --- a/compiler/utils/Binary.hs +++ b/compiler/utils/Binary.hs @@ -594,14 +594,16 @@ getTypeRepX bh = do case tag of 0 -> do con <- get bh TypeRepX rep_k <- getTypeRepX bh - Just HRefl <- pure $ eqTypeRep rep_k (typeRep :: TypeRep Type) - pure $ TypeRepX $ mkTrCon con rep_k + case rep_k `eqTypeRep` (typeRep :: TypeRep Type) of + Just HRefl -> pure $ TypeRepX $ mkTrCon con rep_k + Nothing -> fail "getTypeRepX: Kind mismatch" + 1 -> do TypeRepX f <- getTypeRepX bh TypeRepX x <- getTypeRepX bh case typeRepKind f of - TRFun arg _ -> do - Just HRefl <- pure $ eqTypeRep arg x - pure $ TypeRepX $ mkTrApp f x + TRFun arg _ | Just HRefl <- arg `eqTypeRep` x -> + pure $ TypeRepX $ mkTrApp f x + _ -> fail "getTypeRepX: Kind mismatch" _ -> fail "Binary: Invalid TypeRepX" instance Typeable a => Binary (TypeRep (a :: k)) where diff --git a/libraries/ghci/GHCi/TH/Binary.hs b/libraries/ghci/GHCi/TH/Binary.hs index 2a8432b..9a4d314 100644 --- a/libraries/ghci/GHCi/TH/Binary.hs +++ b/libraries/ghci/GHCi/TH/Binary.hs @@ -98,15 +98,17 @@ getTypeRepX = do case tag of 0 -> do con <- get :: Get TyCon TypeRepX rep_k <- getTypeRepX - Just HRefl <- pure $ eqTypeRep rep_k (typeRep :: TypeRep Type) - pure $ TypeRepX $ mkTrCon con rep_k + case rep_k `eqTypeRep` (typeRep :: TypeRep Type) of + Just HRefl -> pure $ TypeRepX $ mkTrCon con rep_k + Nothing -> fail "getTypeRepX: Kind mismatch" + 1 -> do TypeRepX f <- getTypeRepX TypeRepX x <- getTypeRepX case typeRepKind f of - TRFun arg _ -> do - Just HRefl <- pure $ eqTypeRep arg x - pure $ TypeRepX $ mkTrApp f x - _ -> fail "Binary: Invalid TTypeRep" + TRFun arg _ | Just HRefl <- arg `eqTypeRep` x -> + pure $ TypeRepX $ mkTrApp f x + _ -> fail "getTypeRepX: Kind mismatch" + _ -> fail "getTypeRepX: Invalid TypeRepX" instance Typeable a => Binary (TypeRep (a :: k)) where put = putTypeRep From git at git.haskell.org Fri Jul 8 14:30:48 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 8 Jul 2016 14:30:48 +0000 (UTC) Subject: [commit: ghc] wip/ttypeable: Fix recursive fingerprints (42b3de3) Message-ID: <20160708143048.28D073A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttypeable Link : http://ghc.haskell.org/trac/ghc/changeset/42b3de31be95c2202cea91b92e9f111d159f39fc/ghc >--------------------------------------------------------------- commit 42b3de31be95c2202cea91b92e9f111d159f39fc Author: Ben Gamari Date: Wed Mar 16 11:53:01 2016 +0100 Fix recursive fingerprints >--------------------------------------------------------------- 42b3de31be95c2202cea91b92e9f111d159f39fc libraries/base/Data/Typeable/Internal.hs | 17 +++++++++++++---- 1 file changed, 13 insertions(+), 4 deletions(-) diff --git a/libraries/base/Data/Typeable/Internal.hs b/libraries/base/Data/Typeable/Internal.hs index fc425a0..0d69f7a 100644 --- a/libraries/base/Data/Typeable/Internal.hs +++ b/libraries/base/Data/Typeable/Internal.hs @@ -434,11 +434,20 @@ For this reason we are forced to define their representations manually. -} +-- | We can't use 'mkTrCon' here as it requires the fingerprint of the kind +-- which is knot-tied. +mkPrimTrCon :: forall k (a :: k). TyCon -> TypeRep k -> TypeRep a +mkPrimTrCon tc kind = TrTyCon fpr tc kind + where + fpr_tc = tyConFingerprint tc + fpr_tag = fingerprintString "prim" + fpr = fingerprintFingerprints [fpr_tag, fpr_tc] + mkPrimTyCon :: String -> TyCon mkPrimTyCon = mkTyCon "ghc-prim" "GHC.Prim" trTYPE :: TypeRep TYPE -trTYPE = mkTrCon (mkPrimTyCon "TYPE") runtimeRep_arr_type +trTYPE = mkPrimTrCon (mkPrimTyCon "TYPE") runtimeRep_arr_type where runtimeRep_arr :: TypeRep ((->) RuntimeRep) runtimeRep_arr = mkTrApp trArrow trRuntimeRep @@ -447,10 +456,10 @@ trTYPE = mkTrCon (mkPrimTyCon "TYPE") runtimeRep_arr_type runtimeRep_arr_type = mkTrApp runtimeRep_arr star trRuntimeRep :: TypeRep RuntimeRep -trRuntimeRep = mkTrCon (mkPrimTyCon "RuntimeRep") star +trRuntimeRep = mkPrimTrCon (mkPrimTyCon "RuntimeRep") star tr'PtrRepLifted :: TypeRep 'PtrRepLifted -tr'PtrRepLifted = mkTrCon (mkPrimTyCon "'PtrRepLifted") trRuntimeRep +tr'PtrRepLifted = mkPrimTrCon (mkPrimTyCon "'PtrRepLifted") trRuntimeRep trTYPE'PtrRepLifted :: TypeRep (TYPE 'PtrRepLifted) trTYPE'PtrRepLifted = mkTrApp trTYPE tr'PtrRepLifted @@ -459,7 +468,7 @@ trArrowTyCon :: TyCon trArrowTyCon = mkPrimTyCon "->" trArrow :: TypeRep (->) -trArrow = mkTrCon trArrowTyCon star_arr_star_arr_star +trArrow = mkPrimTrCon trArrowTyCon star_arr_star_arr_star -- Some useful aliases star :: TypeRep (TYPE 'PtrRepLifted) From git at git.haskell.org Fri Jul 8 14:30:50 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 8 Jul 2016 14:30:50 +0000 (UTC) Subject: [commit: ghc] wip/ttypeable: Implement Data.Typeable.funResultTy (70501cd) Message-ID: <20160708143050.D5FA73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttypeable Link : http://ghc.haskell.org/trac/ghc/changeset/70501cd3ba0455881809f666d4667721c8c2cfc5/ghc >--------------------------------------------------------------- commit 70501cd3ba0455881809f666d4667721c8c2cfc5 Author: Ben Gamari Date: Tue Mar 15 16:21:58 2016 +0100 Implement Data.Typeable.funResultTy >--------------------------------------------------------------- 70501cd3ba0455881809f666d4667721c8c2cfc5 libraries/base/Data/Typeable.hs | 15 +++++++++++++++ 1 file changed, 15 insertions(+) diff --git a/libraries/base/Data/Typeable.hs b/libraries/base/Data/Typeable.hs index 486c5b8..7718cf3 100644 --- a/libraries/base/Data/Typeable.hs +++ b/libraries/base/Data/Typeable.hs @@ -69,6 +69,9 @@ module Data.Typeable , rnfTypeRep , showsTypeRep + -- * Observing type representations + , funResultTy + -- * Type constructors , I.TyCon -- abstract, instance of: Eq, Show, Typeable -- For now don't export Module to avoid name clashes @@ -147,6 +150,18 @@ gcast2 x = fmap (\Refl -> x) (eqT :: Maybe (t :~: t')) typeRepTyCon :: TypeRep -> TyCon typeRepTyCon = I.typeRepXTyCon +-- | Applies a type to a function type. Returns: @Just u@ if the first argument +-- represents a function of type @t -> u@ and the second argument represents a +-- function of type @t at . Otherwise, returns @Nothing at . +funResultTy :: TypeRep -> TypeRep -> Maybe TypeRep +funResultTy (I.TypeRepX f) (I.TypeRepX x) + | Just HRefl <- (I.typeRep :: I.TypeRep Type) `I.eqTypeRep` I.typeRepKind f + , I.TRFun arg res <- f + , Just HRefl <- arg `I.eqTypeRep` x + = Just (I.TypeRepX res) + | otherwise + = Nothing + -- | Force a 'TypeRep' to normal form. rnfTypeRep :: TypeRep -> () rnfTypeRep = I.rnfTypeRepX From git at git.haskell.org Fri Jul 8 14:30:53 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 8 Jul 2016 14:30:53 +0000 (UTC) Subject: [commit: ghc] wip/ttypeable: Binary: More explicit pattern matching (e1aefb4) Message-ID: <20160708143053.84DAB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttypeable Link : http://ghc.haskell.org/trac/ghc/changeset/e1aefb4ff4c29672e65fe9d8ec8c632ba0c02788/ghc >--------------------------------------------------------------- commit e1aefb4ff4c29672e65fe9d8ec8c632ba0c02788 Author: Ben Gamari Date: Wed Mar 16 09:40:54 2016 +0100 Binary: More explicit pattern matching >--------------------------------------------------------------- e1aefb4ff4c29672e65fe9d8ec8c632ba0c02788 compiler/utils/Binary.hs | 9 ++++++--- libraries/ghci/GHCi/TH/Binary.hs | 9 ++++++--- 2 files changed, 12 insertions(+), 6 deletions(-) diff --git a/compiler/utils/Binary.hs b/compiler/utils/Binary.hs index 5382084..328b4a9 100644 --- a/compiler/utils/Binary.hs +++ b/compiler/utils/Binary.hs @@ -601,9 +601,12 @@ getTypeRepX bh = do 1 -> do TypeRepX f <- getTypeRepX bh TypeRepX x <- getTypeRepX bh case typeRepKind f of - TRFun arg _ | Just HRefl <- arg `eqTypeRep` x -> - pure $ TypeRepX $ mkTrApp f x - _ -> fail "getTypeRepX: Kind mismatch" + TRFun arg _ -> + case arg `eqTypeRep` x of + Just HRefl -> + pure $ TypeRepX $ mkTrApp f x + _ -> fail "getTypeRepX: Kind mismatch" + _ -> fail "getTypeRepX: Applied non-arrow type" _ -> fail "Binary: Invalid TypeRepX" instance Typeable a => Binary (TypeRep (a :: k)) where diff --git a/libraries/ghci/GHCi/TH/Binary.hs b/libraries/ghci/GHCi/TH/Binary.hs index 9a4d314..7ecc746 100644 --- a/libraries/ghci/GHCi/TH/Binary.hs +++ b/libraries/ghci/GHCi/TH/Binary.hs @@ -105,9 +105,12 @@ getTypeRepX = do 1 -> do TypeRepX f <- getTypeRepX TypeRepX x <- getTypeRepX case typeRepKind f of - TRFun arg _ | Just HRefl <- arg `eqTypeRep` x -> - pure $ TypeRepX $ mkTrApp f x - _ -> fail "getTypeRepX: Kind mismatch" + TRFun arg _ -> + case arg `eqTypeRep` x of + Just HRefl -> + pure $ TypeRepX $ mkTrApp f x + _ -> fail "getTypeRepX: Kind mismatch" + _ -> fail "getTypeRepX: Applied non-arrow type" _ -> fail "getTypeRepX: Invalid TypeRepX" instance Typeable a => Binary (TypeRep (a :: k)) where From git at git.haskell.org Fri Jul 8 14:30:56 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 8 Jul 2016 14:30:56 +0000 (UTC) Subject: [commit: ghc] wip/ttypeable: Kill todo (abc44be) Message-ID: <20160708143056.2F0823A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttypeable Link : http://ghc.haskell.org/trac/ghc/changeset/abc44be747f4add452b643b7874c0c2193d3c2a5/ghc >--------------------------------------------------------------- commit abc44be747f4add452b643b7874c0c2193d3c2a5 Author: Ben Gamari Date: Wed Mar 16 13:36:24 2016 +0100 Kill todo >--------------------------------------------------------------- abc44be747f4add452b643b7874c0c2193d3c2a5 libraries/base/Data/Typeable/Internal.hs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/libraries/base/Data/Typeable/Internal.hs b/libraries/base/Data/Typeable/Internal.hs index 0d69f7a..11612fd 100644 --- a/libraries/base/Data/Typeable/Internal.hs +++ b/libraries/base/Data/Typeable/Internal.hs @@ -264,8 +264,7 @@ typeRepKind (TrTyCon _ _ k) = k typeRepKind (TrApp _ f _) = case typeRepKind f of TRFun _arg res -> res - -- TODO: why is this case needed? - _ -> error "typeRepKind: impossible" + _ -> error "typeRepKind: impossible" -- | Observe the type constructor of a quantified type representation. typeRepXTyCon :: TypeRepX -> TyCon From git at git.haskell.org Fri Jul 8 14:30:58 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 8 Jul 2016 14:30:58 +0000 (UTC) Subject: [commit: ghc] wip/ttypeable: Fix rebase (be43621) Message-ID: <20160708143058.D43CC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttypeable Link : http://ghc.haskell.org/trac/ghc/changeset/be43621081db28983c591566ce105320994c0958/ghc >--------------------------------------------------------------- commit be43621081db28983c591566ce105320994c0958 Author: Ben Gamari Date: Fri Mar 11 17:23:30 2016 +0100 Fix rebase >--------------------------------------------------------------- be43621081db28983c591566ce105320994c0958 compiler/prelude/PrelNames.hs | 38 +++++++++++++-------------- compiler/typecheck/TcInteract.hs | 14 +++++----- libraries/base/Data/Typeable/Internal.hs | 44 ++++++++++++++++---------------- 3 files changed, 48 insertions(+), 48 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc be43621081db28983c591566ce105320994c0958 From git at git.haskell.org Fri Jul 8 14:31:01 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 8 Jul 2016 14:31:01 +0000 (UTC) Subject: [commit: ghc] wip/ttypeable: More serialization (b7887c2) Message-ID: <20160708143101.878253A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttypeable Link : http://ghc.haskell.org/trac/ghc/changeset/b7887c255e7c39b7fdda478d0827bdf48221d3ce/ghc >--------------------------------------------------------------- commit b7887c255e7c39b7fdda478d0827bdf48221d3ce Author: Ben Gamari Date: Wed Mar 16 10:33:37 2016 +0100 More serialization >--------------------------------------------------------------- b7887c255e7c39b7fdda478d0827bdf48221d3ce compiler/utils/Binary.hs | 14 +++++++++----- libraries/base/Data/Typeable.hs | 20 +++++++++++++------- libraries/ghci/GHCi/TH/Binary.hs | 13 ++++++++----- 3 files changed, 30 insertions(+), 17 deletions(-) diff --git a/compiler/utils/Binary.hs b/compiler/utils/Binary.hs index 328b4a9..52bc33f 100644 --- a/compiler/utils/Binary.hs +++ b/compiler/utils/Binary.hs @@ -587,12 +587,13 @@ putTypeRep bh (TRApp f x) = do put_ bh (1 :: Word8) putTypeRep bh f putTypeRep bh x +putTypeRep _ _ = fail "putTypeRep: Impossible" getTypeRepX :: BinHandle -> IO TypeRepX getTypeRepX bh = do tag <- get bh :: IO Word8 case tag of - 0 -> do con <- get bh + 0 -> do con <- get bh :: IO TyCon TypeRepX rep_k <- getTypeRepX bh case rep_k `eqTypeRep` (typeRep :: TypeRep Type) of Just HRefl -> pure $ TypeRepX $ mkTrCon con rep_k @@ -602,10 +603,13 @@ getTypeRepX bh = do TypeRepX x <- getTypeRepX bh case typeRepKind f of TRFun arg _ -> - case arg `eqTypeRep` x of - Just HRefl -> - pure $ TypeRepX $ mkTrApp f x - _ -> fail "getTypeRepX: Kind mismatch" + case (typeRep :: TypeRep Type) `eqTypeRep` arg of + Just HRefl -> -- FIXME: Generalize (->) + case x `eqTypeRep` arg of + Just HRefl -> + pure $ TypeRepX $ mkTrApp f x + _ -> fail "getTypeRepX: Kind mismatch" + Nothing -> fail "getTypeRepX: Arrow of non-Type argument" _ -> fail "getTypeRepX: Applied non-arrow type" _ -> fail "Binary: Invalid TypeRepX" diff --git a/libraries/base/Data/Typeable.hs b/libraries/base/Data/Typeable.hs index 7718cf3..21f93d2 100644 --- a/libraries/base/Data/Typeable.hs +++ b/libraries/base/Data/Typeable.hs @@ -154,13 +154,19 @@ typeRepTyCon = I.typeRepXTyCon -- represents a function of type @t -> u@ and the second argument represents a -- function of type @t at . Otherwise, returns @Nothing at . funResultTy :: TypeRep -> TypeRep -> Maybe TypeRep -funResultTy (I.TypeRepX f) (I.TypeRepX x) - | Just HRefl <- (I.typeRep :: I.TypeRep Type) `I.eqTypeRep` I.typeRepKind f - , I.TRFun arg res <- f - , Just HRefl <- arg `I.eqTypeRep` x - = Just (I.TypeRepX res) - | otherwise - = Nothing +{- +funResultTy (I.TypeRepX f) (I.TypeRepX x) = + case (I.typeRep :: I.TypeRep Type) `I.eqTypeRep` I.typeRepKind f of + Just HRefl -> + case f of + I.TRFun arg res -> + case arg `I.eqTypeRep` x of + Just HRefl -> Just (I.TypeRepX res) + Nothing -> Nothing + _ -> Nothing + Nothing -> Nothing +-} +funResultTy _ _ = Nothing -- | Force a 'TypeRep' to normal form. rnfTypeRep :: TypeRep -> () diff --git a/libraries/ghci/GHCi/TH/Binary.hs b/libraries/ghci/GHCi/TH/Binary.hs index 7ecc746..8d297a1 100644 --- a/libraries/ghci/GHCi/TH/Binary.hs +++ b/libraries/ghci/GHCi/TH/Binary.hs @@ -11,7 +11,6 @@ module GHCi.TH.Binary () where import Data.Binary import qualified Data.ByteString as B #if MIN_VERSION_base(4,9,0) -import Control.Monad (when) import Type.Reflection import Type.Reflection.Unsafe import Data.Kind (Type) @@ -91,6 +90,7 @@ putTypeRep (TRApp f x) = do put (1 :: Word8) putTypeRep f putTypeRep x +putTypeRep _ = fail "putTypeRep: Impossible" getTypeRepX :: Get TypeRepX getTypeRepX = do @@ -106,10 +106,13 @@ getTypeRepX = do TypeRepX x <- getTypeRepX case typeRepKind f of TRFun arg _ -> - case arg `eqTypeRep` x of - Just HRefl -> - pure $ TypeRepX $ mkTrApp f x - _ -> fail "getTypeRepX: Kind mismatch" + case (typeRep :: TypeRep Type) `eqTypeRep` arg of + Just HRefl -> -- FIXME: Generalize (->) + case arg `eqTypeRep` x of + Just HRefl -> + pure $ TypeRepX $ mkTrApp f x + _ -> fail "getTypeRepX: Kind mismatch" + _ -> fail "getTypeRepX: Arrow of non-Type argument" _ -> fail "getTypeRepX: Applied non-arrow type" _ -> fail "getTypeRepX: Invalid TypeRepX" From git at git.haskell.org Fri Jul 8 14:31:04 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 8 Jul 2016 14:31:04 +0000 (UTC) Subject: [commit: ghc] wip/ttypeable: Start implementing library side of TTypeable (13cee20) Message-ID: <20160708143104.CD8FB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttypeable Link : http://ghc.haskell.org/trac/ghc/changeset/13cee20752dee7cbfc94f071e13392175bef9424/ghc >--------------------------------------------------------------- commit 13cee20752dee7cbfc94f071e13392175bef9424 Author: Ben Gamari Date: Sat Jan 30 00:04:54 2016 +0100 Start implementing library side of TTypeable >--------------------------------------------------------------- 13cee20752dee7cbfc94f071e13392175bef9424 compiler/deSugar/DsBinds.hs | 79 +++-- compiler/prelude/PrelNames.hs | 72 +++-- compiler/typecheck/TcEvidence.hs | 20 +- compiler/typecheck/TcHsSyn.hs | 8 +- compiler/typecheck/TcInteract.hs | 65 +++- compiler/utils/Binary.hs | 55 +++- libraries/Win32 | 2 +- libraries/array | 2 +- libraries/base/Data/Dynamic.hs | 51 +-- libraries/base/Data/Type/Equality.hs | 6 + libraries/base/Data/Typeable.hs | 192 ++++++++---- libraries/base/Data/Typeable/Internal.hs | 518 +++++++++++++++++-------------- libraries/base/GHC/Conc/Sync.hs | 4 - libraries/base/GHC/Show.hs | 2 +- libraries/base/Type/Reflection.hs | 43 +++ libraries/base/Type/Reflection/Unsafe.hs | 20 ++ libraries/base/base.cabal | 4 +- libraries/binary | 2 +- libraries/bytestring | 2 +- libraries/deepseq | 2 +- libraries/directory | 2 +- libraries/ghc-boot/GHC/Serialized.hs | 16 +- libraries/ghc-prim/GHC/Types.hs | 15 +- libraries/ghci/GHCi/TH/Binary.hs | 57 ++++ libraries/haskeline | 2 +- libraries/hpc | 2 +- libraries/pretty | 2 +- libraries/time | 2 +- libraries/unix | 2 +- nofib | 2 +- utils/haddock | 2 +- utils/hsc2hs | 2 +- 32 files changed, 810 insertions(+), 445 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 13cee20752dee7cbfc94f071e13392175bef9424 From git at git.haskell.org Fri Jul 8 14:31:07 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 8 Jul 2016 14:31:07 +0000 (UTC) Subject: [commit: ghc] wip/ttypeable: Fix up representation pretty-printer (3cb2c52) Message-ID: <20160708143107.779E03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttypeable Link : http://ghc.haskell.org/trac/ghc/changeset/3cb2c52f414e92a9738b68643f7c64c53358e467/ghc >--------------------------------------------------------------- commit 3cb2c52f414e92a9738b68643f7c64c53358e467 Author: Ben Gamari Date: Wed Mar 16 13:36:30 2016 +0100 Fix up representation pretty-printer >--------------------------------------------------------------- 3cb2c52f414e92a9738b68643f7c64c53358e467 libraries/base/Data/Typeable/Internal.hs | 44 +++++++++++++++++++++++--------- 1 file changed, 32 insertions(+), 12 deletions(-) diff --git a/libraries/base/Data/Typeable/Internal.hs b/libraries/base/Data/Typeable/Internal.hs index 11612fd..ce028e3 100644 --- a/libraries/base/Data/Typeable/Internal.hs +++ b/libraries/base/Data/Typeable/Internal.hs @@ -321,29 +321,49 @@ typeRepXFingerprint (TypeRepX t) = typeRepFingerprint t ----------------- Showing TypeReps -------------------- -- | @since 2.01 -instance Show (TypeRep a) where +instance Show (TypeRep (a :: k)) where + showsPrec _ rep + | isListTyCon tc, [ty] <- tys = + showChar '[' . shows ty . showChar ']' + | isTupleTyCon tc = + showChar '(' . showArgs (showChar ',') tys . showChar ')' + where (tc, tys) = splitApps rep showsPrec p (TrTyCon _ tycon _) = showsPrec p tycon - showsPrec p (TrApp _ f x) = showsPrec p f . showString " " . showsPrec p x - -- TODO: Reconsider precedence + showsPrec p (TrApp _ f x) + | Just HRefl <- f `eqTypeRep` (typeRep :: TypeRep (->)) = + shows x . showString " -> " + | otherwise = + showsPrec p f . space . showParen need_parens (showsPrec 10 x) + where + space = showChar ' ' + need_parens = case x of + TrApp {} -> True + TrTyCon {} -> False -- | @since 4.10.0.0 instance Show TypeRepX where showsPrec p (TypeRepX ty) = showsPrec p ty --- Some (Show.TypeRepX) helpers: -{- --- FIXME: Handle tuples, etc. +splitApps :: TypeRep a -> (TyCon, [TypeRepX]) +splitApps = go [] + where + go :: [TypeRepX] -> TypeRep a -> (TyCon, [TypeRepX]) + go xs (TrTyCon _ tc _) = (tc, xs) + go xs (TrApp _ f x) = go (TypeRepX x : xs) f + +isListTyCon :: TyCon -> Bool +isListTyCon tc = tc == typeRepTyCon (typeRep :: TypeRep [Int]) + +isTupleTyCon :: TyCon -> Bool +isTupleTyCon tc + | ('(':',':_) <- tyConName tc = True + | otherwise = False + showArgs :: Show a => ShowS -> [a] -> ShowS showArgs _ [] = id showArgs _ [a] = showsPrec 10 a showArgs sep (a:as) = showsPrec 10 a . sep . showArgs sep as -showTuple :: [TypeRepX] -> ShowS -showTuple args = showChar '(' - . showArgs (showChar ',') args - . showChar ')' --} - -- | Helper to fully evaluate 'TypeRep' for use as @NFData(rnf)@ implementation -- -- @since 4.8.0.0 From git at git.haskell.org Fri Jul 8 14:31:10 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 8 Jul 2016 14:31:10 +0000 (UTC) Subject: [commit: ghc] wip/ttypeable: Move special tycons (5f3d10f) Message-ID: <20160708143110.1FCE93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttypeable Link : http://ghc.haskell.org/trac/ghc/changeset/5f3d10f9bd795fc264e8c7962cc8d96f6bc92a7e/ghc >--------------------------------------------------------------- commit 5f3d10f9bd795fc264e8c7962cc8d96f6bc92a7e Author: Ben Gamari Date: Wed Mar 16 17:51:01 2016 +0100 Move special tycons >--------------------------------------------------------------- 5f3d10f9bd795fc264e8c7962cc8d96f6bc92a7e compiler/prelude/TysPrim.hs | 16 +++++++++++++++- compiler/typecheck/TcTypeable.hs | 18 +++--------------- 2 files changed, 18 insertions(+), 16 deletions(-) diff --git a/compiler/prelude/TysPrim.hs b/compiler/prelude/TysPrim.hs index 376a0bb..1e81004 100644 --- a/compiler/prelude/TysPrim.hs +++ b/compiler/prelude/TysPrim.hs @@ -31,6 +31,7 @@ module TysPrim( funTyCon, funTyConName, primTyCons, + primTypeableTyCons, charPrimTyCon, charPrimTy, intPrimTyCon, intPrimTy, @@ -80,7 +81,7 @@ module TysPrim( #include "HsVersions.h" import {-# SOURCE #-} TysWiredIn - ( runtimeRepTy, liftedTypeKind + ( runtimeRepTyCon, runtimeRepTy, liftedTypeKind , vecRepDataConTyCon, ptrRepUnliftedDataConTyCon , voidRepDataConTy, intRepDataConTy , wordRepDataConTy, int64RepDataConTy, word64RepDataConTy, addrRepDataConTy @@ -94,6 +95,7 @@ import {-# SOURCE #-} TysWiredIn import Var ( TyVar, mkTyVar ) import Name +import NameEnv import TyCon import SrcLoc import Unique @@ -155,6 +157,18 @@ primTyCons #include "primop-vector-tycons.hs-incl" ] +-- | The names of the 'TyCon's which we define 'Typeable' bindings for +-- explicitly in "Data.Typeable.Internal" +-- and should not generate bindings for in "GHC.Types". +-- +-- See Note [Mutually recursive representations of primitive types] +primTypeableTyCons :: NameEnv TyConRepName +primTypeableTyCons = mkNameEnv + [ (tYPETyConName, trTYPEName) + , (tyConName runtimeRepTyCon, trRuntimeRepName) + , (funTyConName, trArrowName) + ] + mkPrimTc :: FastString -> Unique -> TyCon -> Name mkPrimTc fs unique tycon = mkWiredInName gHC_PRIM (mkTcOccFS fs) diff --git a/compiler/typecheck/TcTypeable.hs b/compiler/typecheck/TcTypeable.hs index cb79e08..061d22f 100644 --- a/compiler/typecheck/TcTypeable.hs +++ b/compiler/typecheck/TcTypeable.hs @@ -13,8 +13,7 @@ import IfaceEnv( newGlobalBinder ) import TcEnv import TcRnMonad import PrelNames -import TysPrim ( primTyCons, tYPETyConName, funTyConName ) -import TysWiredIn ( runtimeRepTyCon ) +import TysPrim ( primTyCons, primTypeableTyCons ) import Id import Type import TyCon @@ -22,7 +21,7 @@ import DataCon import Name( getOccName ) import OccName import Module -import NameSet +import NameEnv import HsSyn import DynFlags import Bag @@ -168,17 +167,6 @@ mkTypeableTyConBinds tycons ; gbl_env <- tcExtendGlobalValEnv tycon_rep_ids getGblEnv ; return (gbl_env `addTypecheckedBinds` tc_binds) } --- | The names of the 'TyCon's which we handle explicitly in "Data.Typeable.Internal" --- and should not generate bindings for in "GHC.Types". --- --- See Note [Mutually recursive representations of primitive types] -specialPrimTyCons :: NameSet -specialPrimTyCons = mkNameSet - [ tYPETyConName - , tyConName runtimeRepTyCon - , funTyConName - ] - -- | Generate bindings for the type representation of a wired-in TyCon defined -- by the virtual "GHC.Prim" module. This is where we inject the representation -- bindings for primitive types into "GHC.Types" @@ -223,7 +211,7 @@ ghcPrimTypeableBinds stuff all_prim_tys :: [TyCon] all_prim_tys = [ tc' | tc <- funTyCon : primTyCons , tc' <- tc : tyConATs tc - , not $ tyConName tc' `elemNameSet` specialPrimTyCons + , not $ tyConName tc' `elemNameEnv` primTypeableTyCons ] mkBind :: TyCon -> LHsBinds Id From git at git.haskell.org Fri Jul 8 14:31:12 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 8 Jul 2016 14:31:12 +0000 (UTC) Subject: [commit: ghc] wip/ttypeable: Another recursive serialization case (4eed289) Message-ID: <20160708143112.C27713A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttypeable Link : http://ghc.haskell.org/trac/ghc/changeset/4eed289b7ba2acf13ebd51977a243522b05cb976/ghc >--------------------------------------------------------------- commit 4eed289b7ba2acf13ebd51977a243522b05cb976 Author: Ben Gamari Date: Wed Mar 16 14:05:43 2016 +0100 Another recursive serialization case >--------------------------------------------------------------- 4eed289b7ba2acf13ebd51977a243522b05cb976 compiler/utils/Binary.hs | 14 +++++++++----- libraries/ghci/GHCi/TH/Binary.hs | 14 +++++++++----- 2 files changed, 18 insertions(+), 10 deletions(-) diff --git a/compiler/utils/Binary.hs b/compiler/utils/Binary.hs index d3ea219..b85fb3c 100644 --- a/compiler/utils/Binary.hs +++ b/compiler/utils/Binary.hs @@ -580,19 +580,22 @@ instance Binary TyCon where #if MIN_VERSION_base(4,9,0) putTypeRep :: BinHandle -> TypeRep a -> IO () --- Special handling for Type and RuntimeRep due to recursive kind relations. +-- Special handling for Type, (->), and RuntimeRep due to recursive kind +-- relations. -- See Note [Mutually recursive representations of primitive types] putTypeRep bh rep | Just HRefl <- rep `eqTypeRep` (typeRep :: TypeRep Type) = put_ bh (0 :: Word8) | Just HRefl <- rep `eqTypeRep` (typeRep :: TypeRep RuntimeRep) = put_ bh (1 :: Word8) + | Just HRefl <- rep `eqTypeRep` (typeRep :: TypeRep (->)) + = put_ bh (2 :: Word8) putTypeRep bh rep@(TRCon con) = do - put_ bh (2 :: Word8) + put_ bh (3 :: Word8) put_ bh con putTypeRep bh (typeRepKind rep) putTypeRep bh (TRApp f x) = do - put_ bh (3 :: Word8) + put_ bh (4 :: Word8) putTypeRep bh f putTypeRep bh x putTypeRep _ _ = fail "putTypeRep: Impossible" @@ -603,13 +606,14 @@ getTypeRepX bh = do case tag of 0 -> return $ TypeRepX (typeRep :: TypeRep Type) 1 -> return $ TypeRepX (typeRep :: TypeRep RuntimeRep) - 2 -> do con <- get bh :: IO TyCon + 2 -> return $ TypeRepX (typeRep :: TypeRep (->)) + 3 -> do con <- get bh :: IO TyCon TypeRepX rep_k <- getTypeRepX bh case rep_k `eqTypeRep` (typeRep :: TypeRep Type) of Just HRefl -> pure $ TypeRepX $ mkTrCon con rep_k Nothing -> fail "getTypeRepX: Kind mismatch" - 3 -> do TypeRepX f <- getTypeRepX bh + 4 -> do TypeRepX f <- getTypeRepX bh TypeRepX x <- getTypeRepX bh case typeRepKind f of TRFun arg _ -> diff --git a/libraries/ghci/GHCi/TH/Binary.hs b/libraries/ghci/GHCi/TH/Binary.hs index bcf58bb..c351cd1 100644 --- a/libraries/ghci/GHCi/TH/Binary.hs +++ b/libraries/ghci/GHCi/TH/Binary.hs @@ -83,19 +83,22 @@ instance Binary TyCon where get = mkTyCon <$> get <*> get <*> get putTypeRep :: TypeRep a -> Put --- Special handling for Type and RuntimeRep due to recursive kind relations. +-- Special handling for Type, (->), and RuntimeRep due to recursive kind +-- relations. -- See Note [Mutually recursive representations of primitive types] putTypeRep rep | Just HRefl <- rep `eqTypeRep` (typeRep :: TypeRep Type) = put (0 :: Word8) | Just HRefl <- rep `eqTypeRep` (typeRep :: TypeRep RuntimeRep) = put (1 :: Word8) + | Just HRefl <- rep `eqTypeRep` (typeRep :: TypeRep (->)) + = put (2 :: Word8) putTypeRep rep@(TRCon con) = do - put (2 :: Word8) + put (3 :: Word8) put con putTypeRep (typeRepKind rep) putTypeRep (TRApp f x) = do - put (3 :: Word8) + put (4 :: Word8) putTypeRep f putTypeRep x putTypeRep _ = fail "putTypeRep: Impossible" @@ -106,13 +109,14 @@ getTypeRepX = do case tag of 0 -> return $ TypeRepX (typeRep :: TypeRep Type) 1 -> return $ TypeRepX (typeRep :: TypeRep RuntimeRep) - 2 -> do con <- get :: Get TyCon + 2 -> return $ TypeRepX (typeRep :: TypeRep (->)) + 3 -> do con <- get :: Get TyCon TypeRepX rep_k <- getTypeRepX case rep_k `eqTypeRep` (typeRep :: TypeRep Type) of Just HRefl -> pure $ TypeRepX $ mkTrCon con rep_k Nothing -> fail "getTypeRepX: Kind mismatch" - 3 -> do TypeRepX f <- getTypeRepX + 4 -> do TypeRepX f <- getTypeRepX TypeRepX x <- getTypeRepX case typeRepKind f of TRFun arg _ -> From git at git.haskell.org Fri Jul 8 14:31:15 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 8 Jul 2016 14:31:15 +0000 (UTC) Subject: [commit: ghc] wip/ttypeable: TcTypeable: Don't generate bindings for special primitive tycons (69dbfe0) Message-ID: <20160708143115.74C1C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttypeable Link : http://ghc.haskell.org/trac/ghc/changeset/69dbfe079ca32bf968e6dbb9acae7a484f11862a/ghc >--------------------------------------------------------------- commit 69dbfe079ca32bf968e6dbb9acae7a484f11862a Author: Ben Gamari Date: Wed Mar 16 15:34:03 2016 +0100 TcTypeable: Don't generate bindings for special primitive tycons >--------------------------------------------------------------- 69dbfe079ca32bf968e6dbb9acae7a484f11862a compiler/typecheck/TcTypeable.hs | 19 +++++++++++++++++-- 1 file changed, 17 insertions(+), 2 deletions(-) diff --git a/compiler/typecheck/TcTypeable.hs b/compiler/typecheck/TcTypeable.hs index 04d07d1..cb79e08 100644 --- a/compiler/typecheck/TcTypeable.hs +++ b/compiler/typecheck/TcTypeable.hs @@ -13,7 +13,8 @@ import IfaceEnv( newGlobalBinder ) import TcEnv import TcRnMonad import PrelNames -import TysPrim ( primTyCons ) +import TysPrim ( primTyCons, tYPETyConName, funTyConName ) +import TysWiredIn ( runtimeRepTyCon ) import Id import Type import TyCon @@ -21,6 +22,7 @@ import DataCon import Name( getOccName ) import OccName import Module +import NameSet import HsSyn import DynFlags import Bag @@ -166,6 +168,17 @@ mkTypeableTyConBinds tycons ; gbl_env <- tcExtendGlobalValEnv tycon_rep_ids getGblEnv ; return (gbl_env `addTypecheckedBinds` tc_binds) } +-- | The names of the 'TyCon's which we handle explicitly in "Data.Typeable.Internal" +-- and should not generate bindings for in "GHC.Types". +-- +-- See Note [Mutually recursive representations of primitive types] +specialPrimTyCons :: NameSet +specialPrimTyCons = mkNameSet + [ tYPETyConName + , tyConName runtimeRepTyCon + , funTyConName + ] + -- | Generate bindings for the type representation of a wired-in TyCon defined -- by the virtual "GHC.Prim" module. This is where we inject the representation -- bindings for primitive types into "GHC.Types" @@ -209,7 +222,9 @@ ghcPrimTypeableBinds stuff where all_prim_tys :: [TyCon] all_prim_tys = [ tc' | tc <- funTyCon : primTyCons - , tc' <- tc : tyConATs tc ] + , tc' <- tc : tyConATs tc + , not $ tyConName tc' `elemNameSet` specialPrimTyCons + ] mkBind :: TyCon -> LHsBinds Id mkBind = mk_typeable_binds stuff From git at git.haskell.org Fri Jul 8 14:31:18 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 8 Jul 2016 14:31:18 +0000 (UTC) Subject: [commit: ghc] wip/ttypeable: Fix pretty-printer (eaffd46) Message-ID: <20160708143118.2D5543A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttypeable Link : http://ghc.haskell.org/trac/ghc/changeset/eaffd46a7be3b277cef2763d112630d1ffb987c8/ghc >--------------------------------------------------------------- commit eaffd46a7be3b277cef2763d112630d1ffb987c8 Author: Ben Gamari Date: Wed Mar 16 22:07:23 2016 +0100 Fix pretty-printer >--------------------------------------------------------------- eaffd46a7be3b277cef2763d112630d1ffb987c8 libraries/base/Data/Typeable/Internal.hs | 10 +++++++--- 1 file changed, 7 insertions(+), 3 deletions(-) diff --git a/libraries/base/Data/Typeable/Internal.hs b/libraries/base/Data/Typeable/Internal.hs index d879905..a2431ac 100644 --- a/libraries/base/Data/Typeable/Internal.hs +++ b/libraries/base/Data/Typeable/Internal.hs @@ -347,14 +347,18 @@ instance Show (TypeRep (a :: k)) where showChar '(' . showArgs (showChar ',') tys . showChar ')' where (tc, tys) = splitApps rep showsPrec p (TrTyCon _ tycon _) = showsPrec p tycon - showsPrec _ (TrApp _ (TrTyCon _ tycon _) x) + --showsPrec p (TRFun x r) = + -- showParen (p > 8) $ + -- showsPrec 9 x . showString " -> " . showsPrec 8 r + showsPrec p (TrApp _ (TrApp _ (TrTyCon _ tycon _) x) r) | isArrowTyCon tycon = - shows x . showString " ->" + showParen (p > 8) $ + showsPrec 9 x . showString " -> " . showsPrec p r showsPrec p (TrApp _ f x) | otherwise = showParen (p > 9) $ - showsPrec p f . + showsPrec 8 f . space . showsPrec 9 x where From git at git.haskell.org Fri Jul 8 14:31:20 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 8 Jul 2016 14:31:20 +0000 (UTC) Subject: [commit: ghc] wip/ttypeable: Internal things (a6bbaf2) Message-ID: <20160708143120.DE92D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttypeable Link : http://ghc.haskell.org/trac/ghc/changeset/a6bbaf232c926a1536cd6c246daaece8dc404025/ghc >--------------------------------------------------------------- commit a6bbaf232c926a1536cd6c246daaece8dc404025 Author: Ben Gamari Date: Wed Mar 16 17:51:27 2016 +0100 Internal things >--------------------------------------------------------------- a6bbaf232c926a1536cd6c246daaece8dc404025 libraries/base/Data/Typeable/Internal.hs | 35 ++++++++++++++++++++++++++------ libraries/base/Type/Reflection.hs | 1 + 2 files changed, 30 insertions(+), 6 deletions(-) diff --git a/libraries/base/Data/Typeable/Internal.hs b/libraries/base/Data/Typeable/Internal.hs index ce028e3..d879905 100644 --- a/libraries/base/Data/Typeable/Internal.hs +++ b/libraries/base/Data/Typeable/Internal.hs @@ -71,6 +71,8 @@ module Data.Typeable.Internal ( mkTrCon, mkTrApp, mkTyCon, mkTyCon#, typeSymbolTypeRep, typeNatTypeRep, + debugShow, + -- * Representations for primitive types trTYPE, trTYPE'PtrRepLifted, @@ -320,6 +322,22 @@ typeRepXFingerprint (TypeRepX t) = typeRepFingerprint t ----------------- Showing TypeReps -------------------- +debugShow :: TypeRep a -> String +debugShow rep + | Just HRefl <- rep `eqTypeRep` (typeRep :: TypeRep Type) = "Type" + | Just HRefl <- rep `eqTypeRep` (typeRep :: TypeRep RuntimeRep) = "RuntimeRep" + | (tc, _) <- splitApps rep + , isArrowTyCon tc = "Arrow" +debugShow (TrApp _ f x) = "App ("++debugShow f++") ("++debugShow x++")" +debugShow (TrTyCon _ x k) + | isArrowTyCon x = "Arrow" + | "->" <- show x = "Arrow #" ++ show ( tyConFingerprint x + , tyConFingerprint trArrowTyCon + , tyConFingerprint $ typeRepTyCon (typeRep :: TypeRep (->)) + , typeRepTyCon (typeRep :: TypeRep (->)) + ) + | otherwise = show x++" :: "++debugShow k + -- | @since 2.01 instance Show (TypeRep (a :: k)) where showsPrec _ rep @@ -329,16 +347,18 @@ instance Show (TypeRep (a :: k)) where showChar '(' . showArgs (showChar ',') tys . showChar ')' where (tc, tys) = splitApps rep showsPrec p (TrTyCon _ tycon _) = showsPrec p tycon + showsPrec _ (TrApp _ (TrTyCon _ tycon _) x) + | isArrowTyCon tycon = + shows x . showString " ->" + showsPrec p (TrApp _ f x) - | Just HRefl <- f `eqTypeRep` (typeRep :: TypeRep (->)) = - shows x . showString " -> " | otherwise = - showsPrec p f . space . showParen need_parens (showsPrec 10 x) + showParen (p > 9) $ + showsPrec p f . + space . + showsPrec 9 x where space = showChar ' ' - need_parens = case x of - TrApp {} -> True - TrTyCon {} -> False -- | @since 4.10.0.0 instance Show TypeRepX where @@ -351,6 +371,9 @@ splitApps = go [] go xs (TrTyCon _ tc _) = (tc, xs) go xs (TrApp _ f x) = go (TypeRepX x : xs) f +isArrowTyCon :: TyCon -> Bool +isArrowTyCon tc = tc == typeRepTyCon (typeRep :: TypeRep (->)) + isListTyCon :: TyCon -> Bool isListTyCon tc = tc == typeRepTyCon (typeRep :: TypeRep [Int]) diff --git a/libraries/base/Type/Reflection.hs b/libraries/base/Type/Reflection.hs index 8057a2e..480e148 100644 --- a/libraries/base/Type/Reflection.hs +++ b/libraries/base/Type/Reflection.hs @@ -37,6 +37,7 @@ module Type.Reflection , I.tyConModule , I.tyConName , I.rnfTyCon + , I.debugShow ) where import qualified Data.Typeable.Internal as I From git at git.haskell.org Fri Jul 8 14:31:23 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 8 Jul 2016 14:31:23 +0000 (UTC) Subject: [commit: ghc] wip/ttypeable: Fix primitive types (221620e) Message-ID: <20160708143123.992903A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttypeable Link : http://ghc.haskell.org/trac/ghc/changeset/221620edc26d6dbb1879d08021f5ddc8013f4192/ghc >--------------------------------------------------------------- commit 221620edc26d6dbb1879d08021f5ddc8013f4192 Author: Ben Gamari Date: Wed Mar 16 19:52:17 2016 +0100 Fix primitive types >--------------------------------------------------------------- 221620edc26d6dbb1879d08021f5ddc8013f4192 compiler/prelude/TysPrim.hs | 2 +- compiler/typecheck/TcInteract.hs | 6 ++++-- 2 files changed, 5 insertions(+), 3 deletions(-) diff --git a/compiler/prelude/TysPrim.hs b/compiler/prelude/TysPrim.hs index 1e81004..04a0677 100644 --- a/compiler/prelude/TysPrim.hs +++ b/compiler/prelude/TysPrim.hs @@ -24,7 +24,7 @@ module TysPrim( openAlphaTy, openBetaTy, openAlphaTyVar, openBetaTyVar, -- Kind constructors... - tYPETyConName, unliftedTypeKindTyConName, + tYPETyCon, tYPETyConName, unliftedTypeKindTyConName, -- Kinds tYPE, diff --git a/compiler/typecheck/TcInteract.hs b/compiler/typecheck/TcInteract.hs index 277ab6a..2d3a17a 100644 --- a/compiler/typecheck/TcInteract.hs +++ b/compiler/typecheck/TcInteract.hs @@ -24,10 +24,10 @@ import Name import PrelNames ( knownNatClassName, knownSymbolClassName, typeableClassName, coercibleTyConKey, heqTyConKey, ipClassKey, - trTYPE'PtrRepLiftedName, trRuntimeRepName, trArrowName ) + trTYPEName, trTYPE'PtrRepLiftedName, trRuntimeRepName, trArrowName ) import TysWiredIn ( typeNatKind, typeSymbolKind, heqDataCon, coercibleDataCon, runtimeRepTy ) -import TysPrim ( eqPrimTyCon, eqReprPrimTyCon ) +import TysPrim ( eqPrimTyCon, eqReprPrimTyCon, tYPETyCon ) import Id( idType ) import CoAxiom ( Eqn, CoAxiom(..), CoAxBranch(..), fromBranches ) import Class @@ -2020,7 +2020,9 @@ matchTypeable clas [k,t] -- clas = Typeable | k `eqType` typeNatKind = doTyLit knownNatClassName t | k `eqType` typeSymbolKind = doTyLit knownSymbolClassName t | t `eqType` liftedTypeKind = doPrimRep trTYPE'PtrRepLiftedName t + | t `eqType` mkTyConTy tYPETyCon = doPrimRep trTYPEName t | t `eqType` runtimeRepTy = doPrimRep trRuntimeRepName t + | t `eqType` mkTyConTy funTyCon = doPrimRep trArrowName t | Just (tc, ks) <- splitTyConApp_maybe t -- See Note [Typeable (T a b c)] , onlyNamedBndrsApplied tc ks = doTyConApp clas t tc | Just (arg,ret) <- splitFunTy_maybe t = doFunTy clas t arg ret From git at git.haskell.org Fri Jul 8 14:31:26 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 8 Jul 2016 14:31:26 +0000 (UTC) Subject: [commit: ghc] wip/ttypeable: Bump base to 4.10.0 (a9b5b00) Message-ID: <20160708143126.49BA13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttypeable Link : http://ghc.haskell.org/trac/ghc/changeset/a9b5b00b6d8fc1db27b8b42430e1d74eadfb1f89/ghc >--------------------------------------------------------------- commit a9b5b00b6d8fc1db27b8b42430e1d74eadfb1f89 Author: Ben Gamari Date: Fri May 20 16:53:57 2016 +0200 Bump base to 4.10.0 >--------------------------------------------------------------- a9b5b00b6d8fc1db27b8b42430e1d74eadfb1f89 compiler/utils/Binary.hs | 6 +++--- libraries/base/base.cabal | 2 +- libraries/base/tests/dynamic002.hs | 2 +- libraries/ghc-boot/GHC/Serialized.hs | 2 +- libraries/ghci/GHCi/Message.hs | 2 +- libraries/ghci/GHCi/TH/Binary.hs | 4 ++-- 6 files changed, 9 insertions(+), 9 deletions(-) diff --git a/compiler/utils/Binary.hs b/compiler/utils/Binary.hs index b85fb3c..29d3049 100644 --- a/compiler/utils/Binary.hs +++ b/compiler/utils/Binary.hs @@ -78,7 +78,7 @@ import qualified Data.ByteString.Unsafe as BS import Data.IORef import Data.Char ( ord, chr ) import Data.Time -#if MIN_VERSION_base(4,9,0) +#if MIN_VERSION_base(4,10,0) import Type.Reflection import Type.Reflection.Unsafe import Data.Kind (Type) @@ -572,13 +572,13 @@ instance Binary TyCon where p <- get bh m <- get bh n <- get bh -#if MIN_VERSION_base(4,9,0) +#if MIN_VERSION_base(4,10,0) return (mkTyCon p m n) #else return (mkTyCon3 p m n) #endif -#if MIN_VERSION_base(4,9,0) +#if MIN_VERSION_base(4,10,0) putTypeRep :: BinHandle -> TypeRep a -> IO () -- Special handling for Type, (->), and RuntimeRep due to recursive kind -- relations. diff --git a/libraries/base/base.cabal b/libraries/base/base.cabal index e8899fb..45b152b 100644 --- a/libraries/base/base.cabal +++ b/libraries/base/base.cabal @@ -1,5 +1,5 @@ name: base -version: 4.9.0.0 +version: 4.10.0.0 -- NOTE: Don't forget to update ./changelog.md license: BSD3 license-file: LICENSE diff --git a/libraries/base/tests/dynamic002.hs b/libraries/base/tests/dynamic002.hs index fff14ec..560c4b4 100644 --- a/libraries/base/tests/dynamic002.hs +++ b/libraries/base/tests/dynamic002.hs @@ -4,7 +4,7 @@ module Main(main) where import Data.Dynamic -#if MIN_VERSION_base(4,9,0) +#if MIN_VERSION_base(4,10,0) import Data.Typeable (TypeCon, TypeRep) #endif import Data.Array diff --git a/libraries/ghc-boot/GHC/Serialized.hs b/libraries/ghc-boot/GHC/Serialized.hs index 8653049..42a9604 100644 --- a/libraries/ghc-boot/GHC/Serialized.hs +++ b/libraries/ghc-boot/GHC/Serialized.hs @@ -36,7 +36,7 @@ toSerialized serialize what = Serialized rep (serialize what) -- | If the 'Serialized' value contains something of the given type, then use the specified deserializer to return @Just@ that. -- Otherwise return @Nothing at . fromSerialized :: forall a. Typeable a => ([Word8] -> a) -> Serialized -> Maybe a -#if MIN_VERSION_base(4,9,0) +#if MIN_VERSION_base(4,10,0) fromSerialized deserialize (Serialized the_type bytes) | the_type == rep = Just (deserialize bytes) | otherwise = Nothing diff --git a/libraries/ghci/GHCi/Message.hs b/libraries/ghci/GHCi/Message.hs index 342c035..a6192fe 100644 --- a/libraries/ghci/GHCi/Message.hs +++ b/libraries/ghci/GHCi/Message.hs @@ -37,7 +37,7 @@ import Data.ByteString (ByteString) import qualified Data.ByteString as B import qualified Data.ByteString.Lazy as LB import Data.Dynamic -#if MIN_VERSION_base(4,9,0) +#if MIN_VERSION_base(4,10,0) -- Previously this was re-exported by Data.Dynamic import Data.Typeable (TypeRep) #endif diff --git a/libraries/ghci/GHCi/TH/Binary.hs b/libraries/ghci/GHCi/TH/Binary.hs index c351cd1..c60b513 100644 --- a/libraries/ghci/GHCi/TH/Binary.hs +++ b/libraries/ghci/GHCi/TH/Binary.hs @@ -10,7 +10,7 @@ module GHCi.TH.Binary () where import Data.Binary import qualified Data.ByteString as B -#if MIN_VERSION_base(4,9,0) +#if MIN_VERSION_base(4,10,0) import Type.Reflection import Type.Reflection.Unsafe import Data.Kind (Type) @@ -77,7 +77,7 @@ instance Binary TH.PatSynArgs -- We need Binary TypeRep for serializing annotations -#if MIN_VERSION_base(4,9,0) +#if MIN_VERSION_base(4,10,0) instance Binary TyCon where put tc = put (tyConPackage tc) >> put (tyConModule tc) >> put (tyConName tc) get = mkTyCon <$> get <*> get <*> get From git at git.haskell.org Fri Jul 8 14:31:28 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 8 Jul 2016 14:31:28 +0000 (UTC) Subject: [commit: ghc] wip/ttypeable: Accept easy test output (ddfe7e3) Message-ID: <20160708143128.EC7573A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttypeable Link : http://ghc.haskell.org/trac/ghc/changeset/ddfe7e3a8cd71169d67c03797187f502c70c03af/ghc >--------------------------------------------------------------- commit ddfe7e3a8cd71169d67c03797187f502c70c03af Author: Ben Gamari Date: Wed Mar 16 22:58:53 2016 +0100 Accept easy test output >--------------------------------------------------------------- ddfe7e3a8cd71169d67c03797187f502c70c03af testsuite/tests/ghci.debugger/scripts/print019.stderr | 6 +++--- testsuite/tests/typecheck/should_fail/TcStaticPointersFail02.stderr | 4 ++-- 2 files changed, 5 insertions(+), 5 deletions(-) diff --git a/testsuite/tests/ghci.debugger/scripts/print019.stderr b/testsuite/tests/ghci.debugger/scripts/print019.stderr index cc62fa1..c266bc8 100644 --- a/testsuite/tests/ghci.debugger/scripts/print019.stderr +++ b/testsuite/tests/ghci.debugger/scripts/print019.stderr @@ -5,10 +5,10 @@ Use :print or :force to determine these types Relevant bindings include it :: a1 (bound at :10:1) These potential instances exist: - instance Show TypeRep -- Defined in ‘Data.Typeable.Internal’ instance Show Ordering -- Defined in ‘GHC.Show’ instance Show TyCon -- Defined in ‘GHC.Show’ - ...plus 30 others - ...plus 10 instances involving out-of-scope types + instance Show Integer -- Defined in ‘GHC.Show’ + ...plus 29 others + ...plus 12 instances involving out-of-scope types (use -fprint-potential-instances to see them all) • In a stmt of an interactive GHCi command: print it diff --git a/testsuite/tests/typecheck/should_fail/TcStaticPointersFail02.stderr b/testsuite/tests/typecheck/should_fail/TcStaticPointersFail02.stderr index e6e637c..b48d63f 100644 --- a/testsuite/tests/typecheck/should_fail/TcStaticPointersFail02.stderr +++ b/testsuite/tests/typecheck/should_fail/TcStaticPointersFail02.stderr @@ -1,13 +1,13 @@ TcStaticPointersFail02.hs:9:6: error: - • No instance for (Data.Typeable.Internal.Typeable b) + • No instance for (base-4.9.0.0:Data.Typeable.Internal.Typeable b) arising from a static form • In the expression: static (undefined :: (forall a. a -> a) -> b) In an equation for ‘f1’: f1 = static (undefined :: (forall a. a -> a) -> b) TcStaticPointersFail02.hs:12:6: error: - • No instance for (Data.Typeable.Internal.Typeable + • No instance for (base-4.9.0.0:Data.Typeable.Internal.Typeable (Monad m => a -> m a)) arising from a static form (maybe you haven't applied a function to enough arguments?) From git at git.haskell.org Fri Jul 8 14:31:31 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 8 Jul 2016 14:31:31 +0000 (UTC) Subject: [commit: ghc] wip/ttypeable: Internal: Rename type variable (2c33fe8) Message-ID: <20160708143131.9A4883A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttypeable Link : http://ghc.haskell.org/trac/ghc/changeset/2c33fe8da9fa335b03e480022ef322ad17ee14b2/ghc >--------------------------------------------------------------- commit 2c33fe8da9fa335b03e480022ef322ad17ee14b2 Author: Ben Gamari Date: Fri Mar 18 11:49:43 2016 +0100 Internal: Rename type variable >--------------------------------------------------------------- 2c33fe8da9fa335b03e480022ef322ad17ee14b2 libraries/base/Data/Typeable/Internal.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/libraries/base/Data/Typeable/Internal.hs b/libraries/base/Data/Typeable/Internal.hs index 8a58d4e..b2d7726 100644 --- a/libraries/base/Data/Typeable/Internal.hs +++ b/libraries/base/Data/Typeable/Internal.hs @@ -240,9 +240,9 @@ data AppResult (t :: k) where App :: TypeRep a -> TypeRep b -> AppResult (a b) -- | Pattern match on a type application -pattern TRApp :: forall k2 (fun :: k2). () - => forall k1 (a :: k1 -> k2) (b :: k1). (fun ~ a b) - => TypeRep a -> TypeRep b -> TypeRep fun +pattern TRApp :: forall k2 (t :: k2). () + => forall k1 (a :: k1 -> k2) (b :: k1). (t ~ a b) + => TypeRep a -> TypeRep b -> TypeRep t pattern TRApp f x <- TrApp _ f x withTypeable :: TypeRep a -> (Typeable a => b) -> b From git at git.haskell.org Fri Jul 8 14:31:34 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 8 Jul 2016 14:31:34 +0000 (UTC) Subject: [commit: ghc] wip/ttypeable: Bump base (152c249) Message-ID: <20160708143134.4A9E43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttypeable Link : http://ghc.haskell.org/trac/ghc/changeset/152c249b1f5722606876c3b85d07a300b50ec2ce/ghc >--------------------------------------------------------------- commit 152c249b1f5722606876c3b85d07a300b50ec2ce Author: Ben Gamari Date: Sat Jun 4 09:48:57 2016 +0200 Bump base >--------------------------------------------------------------- 152c249b1f5722606876c3b85d07a300b50ec2ce libraries/ghc-boot-th/ghc-boot-th.cabal.in | 2 +- libraries/ghc-boot/ghc-boot.cabal.in | 2 +- libraries/ghci/ghci.cabal.in | 2 +- libraries/template-haskell/template-haskell.cabal | 2 +- 4 files changed, 4 insertions(+), 4 deletions(-) diff --git a/libraries/ghc-boot-th/ghc-boot-th.cabal.in b/libraries/ghc-boot-th/ghc-boot-th.cabal.in index 3aebfbf..50b07db 100644 --- a/libraries/ghc-boot-th/ghc-boot-th.cabal.in +++ b/libraries/ghc-boot-th/ghc-boot-th.cabal.in @@ -34,4 +34,4 @@ Library GHC.LanguageExtensions.Type GHC.Lexeme - build-depends: base >= 4.7 && < 4.10 + build-depends: base >= 4.7 && < 4.11 diff --git a/libraries/ghc-boot/ghc-boot.cabal.in b/libraries/ghc-boot/ghc-boot.cabal.in index eed11e3..4d162f0 100644 --- a/libraries/ghc-boot/ghc-boot.cabal.in +++ b/libraries/ghc-boot/ghc-boot.cabal.in @@ -44,7 +44,7 @@ Library GHC.LanguageExtensions.Type, GHC.Lexeme - build-depends: base >= 4.7 && < 4.10, + build-depends: base >= 4.7 && < 4.11, binary == 0.8.*, bytestring == 0.10.*, directory == 1.2.*, diff --git a/libraries/ghci/ghci.cabal.in b/libraries/ghci/ghci.cabal.in index 547374a..32ebb99 100644 --- a/libraries/ghci/ghci.cabal.in +++ b/libraries/ghci/ghci.cabal.in @@ -58,7 +58,7 @@ library Build-Depends: array == 0.5.*, - base == 4.9.*, + base == 4.10.*, binary == 0.8.*, bytestring == 0.10.*, containers == 0.5.*, diff --git a/libraries/template-haskell/template-haskell.cabal b/libraries/template-haskell/template-haskell.cabal index 0d9f468..b90f53d 100644 --- a/libraries/template-haskell/template-haskell.cabal +++ b/libraries/template-haskell/template-haskell.cabal @@ -49,7 +49,7 @@ Library Language.Haskell.TH.Lib.Map build-depends: - base >= 4.8 && < 4.10, + base >= 4.8 && < 4.11, ghc-boot-th == 8.1, pretty == 1.1.* From git at git.haskell.org Fri Jul 8 14:31:36 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 8 Jul 2016 14:31:36 +0000 (UTC) Subject: [commit: ghc] wip/ttypeable: Kill debugShow (5849617) Message-ID: <20160708143136.F1B483A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttypeable Link : http://ghc.haskell.org/trac/ghc/changeset/58496177c49462f0c3ee6ce0eeeb9651341430d2/ghc >--------------------------------------------------------------- commit 58496177c49462f0c3ee6ce0eeeb9651341430d2 Author: Ben Gamari Date: Wed Mar 16 22:08:49 2016 +0100 Kill debugShow >--------------------------------------------------------------- 58496177c49462f0c3ee6ce0eeeb9651341430d2 libraries/base/Data/Typeable/Internal.hs | 19 ------------------- libraries/base/Type/Reflection.hs | 1 - 2 files changed, 20 deletions(-) diff --git a/libraries/base/Data/Typeable/Internal.hs b/libraries/base/Data/Typeable/Internal.hs index a2431ac..f671f0b 100644 --- a/libraries/base/Data/Typeable/Internal.hs +++ b/libraries/base/Data/Typeable/Internal.hs @@ -71,8 +71,6 @@ module Data.Typeable.Internal ( mkTrCon, mkTrApp, mkTyCon, mkTyCon#, typeSymbolTypeRep, typeNatTypeRep, - debugShow, - -- * Representations for primitive types trTYPE, trTYPE'PtrRepLifted, @@ -322,23 +320,6 @@ typeRepXFingerprint (TypeRepX t) = typeRepFingerprint t ----------------- Showing TypeReps -------------------- -debugShow :: TypeRep a -> String -debugShow rep - | Just HRefl <- rep `eqTypeRep` (typeRep :: TypeRep Type) = "Type" - | Just HRefl <- rep `eqTypeRep` (typeRep :: TypeRep RuntimeRep) = "RuntimeRep" - | (tc, _) <- splitApps rep - , isArrowTyCon tc = "Arrow" -debugShow (TrApp _ f x) = "App ("++debugShow f++") ("++debugShow x++")" -debugShow (TrTyCon _ x k) - | isArrowTyCon x = "Arrow" - | "->" <- show x = "Arrow #" ++ show ( tyConFingerprint x - , tyConFingerprint trArrowTyCon - , tyConFingerprint $ typeRepTyCon (typeRep :: TypeRep (->)) - , typeRepTyCon (typeRep :: TypeRep (->)) - ) - | otherwise = show x++" :: "++debugShow k - --- | @since 2.01 instance Show (TypeRep (a :: k)) where showsPrec _ rep | isListTyCon tc, [ty] <- tys = diff --git a/libraries/base/Type/Reflection.hs b/libraries/base/Type/Reflection.hs index 480e148..8057a2e 100644 --- a/libraries/base/Type/Reflection.hs +++ b/libraries/base/Type/Reflection.hs @@ -37,7 +37,6 @@ module Type.Reflection , I.tyConModule , I.tyConName , I.rnfTyCon - , I.debugShow ) where import qualified Data.Typeable.Internal as I From git at git.haskell.org Fri Jul 8 14:31:39 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 8 Jul 2016 14:31:39 +0000 (UTC) Subject: [commit: ghc] wip/ttypeable: Add mkFunTy (1c6abb5) Message-ID: <20160708143139.9FC663A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttypeable Link : http://ghc.haskell.org/trac/ghc/changeset/1c6abb517d2f019ad367caf36a0cd5798cfabce1/ghc >--------------------------------------------------------------- commit 1c6abb517d2f019ad367caf36a0cd5798cfabce1 Author: Ben Gamari Date: Wed Mar 16 23:15:36 2016 +0100 Add mkFunTy >--------------------------------------------------------------- 1c6abb517d2f019ad367caf36a0cd5798cfabce1 libraries/base/Data/Typeable.hs | 14 ++++++++++++++ libraries/base/Data/Typeable/Internal.hs | 3 ++- 2 files changed, 16 insertions(+), 1 deletion(-) diff --git a/libraries/base/Data/Typeable.hs b/libraries/base/Data/Typeable.hs index 21f93d2..3eb53c5 100644 --- a/libraries/base/Data/Typeable.hs +++ b/libraries/base/Data/Typeable.hs @@ -68,6 +68,7 @@ module Data.Typeable , typeRepTyCon , rnfTypeRep , showsTypeRep + , mkFunTy -- * Observing type representations , funResultTy @@ -168,6 +169,19 @@ funResultTy (I.TypeRepX f) (I.TypeRepX x) = -} funResultTy _ _ = Nothing +-- | Build a function type. +mkFunTy :: TypeRep -> TypeRep -> TypeRep +mkFunTy (I.TypeRepX arg) (I.TypeRepX res) + | Just HRefl <- arg `I.eqTypeRep` liftedTy + , Just HRefl <- res `I.eqTypeRep` liftedTy + = I.TypeRepX (I.TRFun arg res) + | otherwise + = error $ "mkFunTy: Attempted to construct function type from non-lifted "++ + "type: arg="++show arg++", res="++show res + where liftedTy = I.typeRep :: I.TypeRep * + -- TODO: We should be able to support this but the kind of (->) must be + -- generalized + -- | Force a 'TypeRep' to normal form. rnfTypeRep :: TypeRep -> () rnfTypeRep = I.rnfTypeRepX diff --git a/libraries/base/Data/Typeable/Internal.hs b/libraries/base/Data/Typeable/Internal.hs index 8e1c565..108aa71 100644 --- a/libraries/base/Data/Typeable/Internal.hs +++ b/libraries/base/Data/Typeable/Internal.hs @@ -190,7 +190,8 @@ pattern TRFun :: forall fun. () => TypeRep arg -> TypeRep res -> TypeRep fun -pattern TRFun arg res <- TrApp _ (TrApp _ (eqTypeRep trArrow -> Just HRefl) arg) res +pattern TRFun arg res <- TrApp _ (TrApp _ (eqTypeRep trArrow -> Just HRefl) arg) res where + TRFun arg res = mkTrApp (mkTrApp trArrow arg) res decomposeFun :: forall fun r. TypeRep fun From git at git.haskell.org Fri Jul 8 14:31:42 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 8 Jul 2016 14:31:42 +0000 (UTC) Subject: [commit: ghc] wip/ttypeable: Implement withTypeable (913ccde) Message-ID: <20160708143142.571EC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttypeable Link : http://ghc.haskell.org/trac/ghc/changeset/913ccde1938ca3704aacb43f1ab37f3ae1a8f110/ghc >--------------------------------------------------------------- commit 913ccde1938ca3704aacb43f1ab37f3ae1a8f110 Author: Ben Gamari Date: Wed Apr 13 00:02:51 2016 +0200 Implement withTypeable >--------------------------------------------------------------- 913ccde1938ca3704aacb43f1ab37f3ae1a8f110 libraries/base/Data/Typeable/Internal.hs | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/libraries/base/Data/Typeable/Internal.hs b/libraries/base/Data/Typeable/Internal.hs index b2d7726..c72e41a 100644 --- a/libraries/base/Data/Typeable/Internal.hs +++ b/libraries/base/Data/Typeable/Internal.hs @@ -85,6 +85,7 @@ import Data.Type.Equality import GHC.Word import GHC.Show import GHC.TypeLits( KnownNat, KnownSymbol, natVal', symbolVal' ) +import Unsafe.Coerce import GHC.Fingerprint.Type import {-# SOURCE #-} GHC.Fingerprint @@ -245,8 +246,11 @@ pattern TRApp :: forall k2 (t :: k2). () => TypeRep a -> TypeRep b -> TypeRep t pattern TRApp f x <- TrApp _ f x +-- | Use a 'TypeRep' as 'Typeable' evidence. withTypeable :: TypeRep a -> (Typeable a => b) -> b -withTypeable = undefined +withTypeable rep f = f' rep + where f' :: TypeRep a -> b + f' = unsafeCoerce rep -- | Pattern match on a type constructor -- TODO: do we want to expose kinds in these patterns? From git at git.haskell.org Fri Jul 8 14:31:45 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 8 Jul 2016 14:31:45 +0000 (UTC) Subject: [commit: ghc] wip/ttypeable: More test fixes (9159bc6) Message-ID: <20160708143145.081D63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttypeable Link : http://ghc.haskell.org/trac/ghc/changeset/9159bc69fc5acb7e7d51b133e237dcdcf118cf37/ghc >--------------------------------------------------------------- commit 9159bc69fc5acb7e7d51b133e237dcdcf118cf37 Author: Ben Gamari Date: Wed Mar 16 23:15:48 2016 +0100 More test fixes >--------------------------------------------------------------- 9159bc69fc5acb7e7d51b133e237dcdcf118cf37 libraries/base/tests/dynamic002.hs | 5 +++++ libraries/base/tests/dynamic004.hs | 1 - 2 files changed, 5 insertions(+), 1 deletion(-) diff --git a/libraries/base/tests/dynamic002.hs b/libraries/base/tests/dynamic002.hs index 6d53d2e..fff14ec 100644 --- a/libraries/base/tests/dynamic002.hs +++ b/libraries/base/tests/dynamic002.hs @@ -1,7 +1,12 @@ +{-# LANGUAGE CPP #-} + -- !!! Testing Typeable instances module Main(main) where import Data.Dynamic +#if MIN_VERSION_base(4,9,0) +import Data.Typeable (TypeCon, TypeRep) +#endif import Data.Array import Data.Array.MArray import Data.Array.ST diff --git a/libraries/base/tests/dynamic004.hs b/libraries/base/tests/dynamic004.hs index e6b7a82..2091646 100644 --- a/libraries/base/tests/dynamic004.hs +++ b/libraries/base/tests/dynamic004.hs @@ -1,7 +1,6 @@ module Main where import Data.Typeable -import Data.Typeable.Internal import GHC.Fingerprint import Text.Printf From git at git.haskell.org Fri Jul 8 14:31:47 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 8 Jul 2016 14:31:47 +0000 (UTC) Subject: [commit: ghc] wip/ttypeable: Fix T8132 (ca5e33d) Message-ID: <20160708143147.BD36A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttypeable Link : http://ghc.haskell.org/trac/ghc/changeset/ca5e33d5f94bafd87c97a2ca9685879226bd2312/ghc >--------------------------------------------------------------- commit ca5e33d5f94bafd87c97a2ca9685879226bd2312 Author: Ben Gamari Date: Wed Mar 16 23:22:32 2016 +0100 Fix T8132 >--------------------------------------------------------------- ca5e33d5f94bafd87c97a2ca9685879226bd2312 testsuite/tests/polykinds/T8132.hs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/testsuite/tests/polykinds/T8132.hs b/testsuite/tests/polykinds/T8132.hs index 337e288..cdbfd7f 100644 --- a/testsuite/tests/polykinds/T8132.hs +++ b/testsuite/tests/polykinds/T8132.hs @@ -1,6 +1,7 @@ {-# LANGUAGE MagicHash #-} -import Data.Typeable.Internal +import Data.Typeable data K = K -instance Typeable K where typeRep# _ = undefined +-- This used to have a RHS but now we hide typeRep# +instance Typeable K -- where typeRep# _ = undefined From git at git.haskell.org Fri Jul 8 14:31:50 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 8 Jul 2016 14:31:50 +0000 (UTC) Subject: [commit: ghc] wip/ttypeable: Fix withTypeable (347c704) Message-ID: <20160708143150.7F72E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttypeable Link : http://ghc.haskell.org/trac/ghc/changeset/347c704d11f584b94e9d58f7c4c1016341580380/ghc >--------------------------------------------------------------- commit 347c704d11f584b94e9d58f7c4c1016341580380 Author: Ben Gamari Date: Fri May 20 18:07:01 2016 +0200 Fix withTypeable >--------------------------------------------------------------- 347c704d11f584b94e9d58f7c4c1016341580380 libraries/base/Data/Typeable/Internal.hs | 11 +++++++---- 1 file changed, 7 insertions(+), 4 deletions(-) diff --git a/libraries/base/Data/Typeable/Internal.hs b/libraries/base/Data/Typeable/Internal.hs index c72e41a..8c225a7 100644 --- a/libraries/base/Data/Typeable/Internal.hs +++ b/libraries/base/Data/Typeable/Internal.hs @@ -247,10 +247,13 @@ pattern TRApp :: forall k2 (t :: k2). () pattern TRApp f x <- TrApp _ f x -- | Use a 'TypeRep' as 'Typeable' evidence. -withTypeable :: TypeRep a -> (Typeable a => b) -> b -withTypeable rep f = f' rep - where f' :: TypeRep a -> b - f' = unsafeCoerce rep +withTypeable :: forall a r. TypeRep a -> (Typeable a => r) -> r +withTypeable rep k = unsafeCoerce k' rep + where k' :: Gift a r + k' = Gift k + +-- | A helper to satisfy the type checker in 'withTypeable'. +newtype Gift a r = Gift (Typeable a => r) -- | Pattern match on a type constructor -- TODO: do we want to expose kinds in these patterns? From git at git.haskell.org Fri Jul 8 14:31:53 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 8 Jul 2016 14:31:53 +0000 (UTC) Subject: [commit: ghc] wip/ttypeable: Inline space (9add749) Message-ID: <20160708143153.341A03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttypeable Link : http://ghc.haskell.org/trac/ghc/changeset/9add749f860264e12daf94e6bd08c6500d9268c8/ghc >--------------------------------------------------------------- commit 9add749f860264e12daf94e6bd08c6500d9268c8 Author: Ben Gamari Date: Wed Mar 16 22:10:16 2016 +0100 Inline space >--------------------------------------------------------------- 9add749f860264e12daf94e6bd08c6500d9268c8 libraries/base/Data/Typeable/Internal.hs | 4 +--- 1 file changed, 1 insertion(+), 3 deletions(-) diff --git a/libraries/base/Data/Typeable/Internal.hs b/libraries/base/Data/Typeable/Internal.hs index f671f0b..8e1c565 100644 --- a/libraries/base/Data/Typeable/Internal.hs +++ b/libraries/base/Data/Typeable/Internal.hs @@ -340,10 +340,8 @@ instance Show (TypeRep (a :: k)) where | otherwise = showParen (p > 9) $ showsPrec 8 f . - space . + showChar ' ' . showsPrec 9 x - where - space = showChar ' ' -- | @since 4.10.0.0 instance Show TypeRepX where From git at git.haskell.org Fri Jul 8 14:31:55 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 8 Jul 2016 14:31:55 +0000 (UTC) Subject: [commit: ghc] wip/ttypeable: Render TYPE 'PtrRepLifted as * (ff67285) Message-ID: <20160708143155.DA04A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttypeable Link : http://ghc.haskell.org/trac/ghc/changeset/ff67285500aad7ec2d081ea4e612c5ddf3e0dcbb/ghc >--------------------------------------------------------------- commit ff67285500aad7ec2d081ea4e612c5ddf3e0dcbb Author: Ben Gamari Date: Thu Mar 17 01:02:39 2016 +0100 Render TYPE 'PtrRepLifted as * >--------------------------------------------------------------- ff67285500aad7ec2d081ea4e612c5ddf3e0dcbb libraries/base/Data/Typeable/Internal.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/libraries/base/Data/Typeable/Internal.hs b/libraries/base/Data/Typeable/Internal.hs index 108aa71..8a58d4e 100644 --- a/libraries/base/Data/Typeable/Internal.hs +++ b/libraries/base/Data/Typeable/Internal.hs @@ -323,6 +323,8 @@ typeRepXFingerprint (TypeRepX t) = typeRepFingerprint t instance Show (TypeRep (a :: k)) where showsPrec _ rep + | Just HRefl <- rep `eqTypeRep` (typeRep :: TypeRep *) = + showChar '*' | isListTyCon tc, [ty] <- tys = showChar '[' . shows ty . showChar ']' | isTupleTyCon tc = From git at git.haskell.org Fri Jul 8 14:31:58 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 8 Jul 2016 14:31:58 +0000 (UTC) Subject: [commit: ghc] wip/ttypeable: testsuite: Bump base version (6c43926) Message-ID: <20160708143158.A52C43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttypeable Link : http://ghc.haskell.org/trac/ghc/changeset/6c43926959ea8dbaf6e9edb1b7fd80fdc206cad7/ghc >--------------------------------------------------------------- commit 6c43926959ea8dbaf6e9edb1b7fd80fdc206cad7 Author: Ben Gamari Date: Sat Jun 4 09:58:08 2016 +0200 testsuite: Bump base version >--------------------------------------------------------------- 6c43926959ea8dbaf6e9edb1b7fd80fdc206cad7 testsuite/tests/ado/ado004.stderr | 2 +- testsuite/tests/ghci/scripts/ghci008.stdout | 4 ++-- .../tests/indexed-types/should_compile/T3017.stderr | 2 +- .../tests/partial-sigs/should_compile/ADT.stderr | 2 +- .../partial-sigs/should_compile/AddAndOr1.stderr | 4 ++-- .../partial-sigs/should_compile/AddAndOr2.stderr | 4 ++-- .../partial-sigs/should_compile/AddAndOr3.stderr | 4 ++-- .../partial-sigs/should_compile/AddAndOr4.stderr | 4 ++-- .../partial-sigs/should_compile/AddAndOr5.stderr | 4 ++-- .../partial-sigs/should_compile/AddAndOr6.stderr | 4 ++-- .../partial-sigs/should_compile/BoolToBool.stderr | 4 ++-- .../should_compile/DataFamilyInstanceLHS.stderr | 2 +- .../should_compile/Defaulting1MROn.stderr | 4 ++-- .../should_compile/Defaulting2MROff.stderr | 2 +- .../should_compile/Defaulting2MROn.stderr | 2 +- .../tests/partial-sigs/should_compile/Either.stderr | 2 +- .../should_compile/EqualityConstraint.stderr | 2 +- .../tests/partial-sigs/should_compile/Every.stderr | 4 ++-- .../partial-sigs/should_compile/EveryNamed.stderr | 2 +- .../partial-sigs/should_compile/ExpressionSig.stderr | 4 ++-- .../should_compile/ExpressionSigNamed.stderr | 4 ++-- .../should_compile/ExtraConstraints1.stderr | 2 +- .../should_compile/ExtraConstraints2.stderr | 4 ++-- .../should_compile/ExtraConstraints3.stderr | 20 ++++++++++++++++++++ .../should_compile/ExtraNumAMROff.stderr | 4 ++-- .../partial-sigs/should_compile/ExtraNumAMROn.stderr | 2 +- .../tests/partial-sigs/should_compile/Forall1.stderr | 4 ++-- .../partial-sigs/should_compile/GenNamed.stderr | 4 ++-- .../partial-sigs/should_compile/HigherRank1.stderr | 4 ++-- .../partial-sigs/should_compile/HigherRank2.stderr | 4 ++-- .../should_compile/LocalDefinitionBug.stderr | 4 ++-- .../partial-sigs/should_compile/Meltdown.stderr | 2 +- .../should_compile/MonoLocalBinds.stderr | 4 ++-- .../partial-sigs/should_compile/NamedTyVar.stderr | 2 +- .../NamedWildcardInDataFamilyInstanceLHS.stderr | 2 +- .../NamedWildcardInTypeFamilyInstanceLHS.stderr | 2 +- .../should_compile/ParensAroundContext.stderr | 4 ++-- .../tests/partial-sigs/should_compile/PatBind.stderr | 4 ++-- .../partial-sigs/should_compile/PatBind2.stderr | 2 +- .../partial-sigs/should_compile/PatternSig.stderr | 4 ++-- .../partial-sigs/should_compile/Recursive.stderr | 4 ++-- .../should_compile/ScopedNamedWildcards.stderr | 4 ++-- .../should_compile/ScopedNamedWildcardsGood.stderr | 4 ++-- .../partial-sigs/should_compile/ShowNamed.stderr | 2 +- .../partial-sigs/should_compile/SimpleGen.stderr | 2 +- .../partial-sigs/should_compile/SkipMany.stderr | 2 +- .../should_compile/SomethingShowable.stderr | 2 +- .../should_compile/TypeFamilyInstanceLHS.stderr | 2 +- .../tests/partial-sigs/should_compile/Uncurry.stderr | 4 ++-- .../partial-sigs/should_compile/UncurryNamed.stderr | 2 +- .../WarningWildcardInstantiations.stderr | 2 +- testsuite/tests/polykinds/T8132.stderr | 2 +- testsuite/tests/rename/should_fail/rnfail040.stderr | 4 ++-- testsuite/tests/roles/should_compile/Roles1.stderr | 2 +- testsuite/tests/roles/should_compile/Roles14.stderr | 2 +- testsuite/tests/roles/should_compile/Roles2.stderr | 2 +- testsuite/tests/roles/should_compile/Roles3.stderr | 2 +- testsuite/tests/roles/should_compile/Roles4.stderr | 2 +- testsuite/tests/roles/should_compile/T8958.stderr | 2 +- testsuite/tests/safeHaskell/check/Check01.stderr | 4 ++-- testsuite/tests/safeHaskell/check/Check06.stderr | 4 ++-- testsuite/tests/safeHaskell/check/Check08.stderr | 4 ++-- testsuite/tests/safeHaskell/check/Check09.stderr | 8 ++++---- .../tests/safeHaskell/check/pkg01/ImpSafe01.stderr | 4 ++-- .../tests/safeHaskell/check/pkg01/ImpSafe04.stderr | 4 ++-- testsuite/tests/safeHaskell/flags/SafeFlags17.stderr | 4 ++-- .../tests/typecheck/should_compile/tc231.stderr | 2 +- .../should_fail/TcStaticPointersFail02.stderr | 4 ++-- .../tests/typecheck/should_fail/tcfail182.stderr | 4 ++-- 69 files changed, 127 insertions(+), 107 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 6c43926959ea8dbaf6e9edb1b7fd80fdc206cad7 From git at git.haskell.org Fri Jul 8 14:32:01 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 8 Jul 2016 14:32:01 +0000 (UTC) Subject: [commit: ghc] wip/ttypeable: Rework Show (0c91d29) Message-ID: <20160708143201.54E733A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttypeable Link : http://ghc.haskell.org/trac/ghc/changeset/0c91d29dd791c7cf54c4daedb38302d2bad87635/ghc >--------------------------------------------------------------- commit 0c91d29dd791c7cf54c4daedb38302d2bad87635 Author: Ben Gamari Date: Mon Jul 4 14:43:40 2016 +0200 Rework Show >--------------------------------------------------------------- 0c91d29dd791c7cf54c4daedb38302d2bad87635 libraries/base/Data/Typeable/Internal.hs | 48 +++++++++++++++++++------------- 1 file changed, 28 insertions(+), 20 deletions(-) diff --git a/libraries/base/Data/Typeable/Internal.hs b/libraries/base/Data/Typeable/Internal.hs index 8c225a7..e73fee6 100644 --- a/libraries/base/Data/Typeable/Internal.hs +++ b/libraries/base/Data/Typeable/Internal.hs @@ -329,29 +329,37 @@ typeRepXFingerprint (TypeRepX t) = typeRepFingerprint t ----------------- Showing TypeReps -------------------- instance Show (TypeRep (a :: k)) where - showsPrec _ rep - | Just HRefl <- rep `eqTypeRep` (typeRep :: TypeRep *) = - showChar '*' - | isListTyCon tc, [ty] <- tys = - showChar '[' . shows ty . showChar ']' - | isTupleTyCon tc = - showChar '(' . showArgs (showChar ',') tys . showChar ')' - where (tc, tys) = splitApps rep - showsPrec p (TrTyCon _ tycon _) = showsPrec p tycon + showsPrec = showTypeable + +showTypeable :: Int -> TypeRep (a :: k) -> ShowS +showTypeable p rep = + showParen (p > 9) $ + showTypeable' 8 rep . showString " :: " . showTypeable' 8 (typeRepKind rep) + +showTypeable' :: Int -> TypeRep (a :: k) -> ShowS +showTypeable' _ rep + | Just HRefl <- rep `eqTypeRep` (typeRep :: TypeRep *) = + showChar '*' + | isListTyCon tc, [ty] <- tys = + showChar '[' . shows ty . showChar ']' + | isTupleTyCon tc = + showChar '(' . showArgs (showChar ',') tys . showChar ')' + where (tc, tys) = splitApps rep +showTypeable' p (TrTyCon _ tycon _) = showsPrec p tycon --showsPrec p (TRFun x r) = -- showParen (p > 8) $ -- showsPrec 9 x . showString " -> " . showsPrec 8 r - showsPrec p (TrApp _ (TrApp _ (TrTyCon _ tycon _) x) r) - | isArrowTyCon tycon = - showParen (p > 8) $ - showsPrec 9 x . showString " -> " . showsPrec p r - - showsPrec p (TrApp _ f x) - | otherwise = - showParen (p > 9) $ - showsPrec 8 f . - showChar ' ' . - showsPrec 9 x +showTypeable' p (TrApp _ (TrApp _ (TrTyCon _ tycon _) x) r) + | isArrowTyCon tycon = + showParen (p > 8) $ + showsPrec 9 x . showString " -> " . showsPrec p r + +showTypeable' p (TrApp _ f x) + | otherwise = + showParen (p > 9) $ + showsPrec 8 f . + showChar ' ' . + showsPrec 9 x -- | @since 4.10.0.0 instance Show TypeRepX where From git at git.haskell.org Fri Jul 8 14:32:04 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 8 Jul 2016 14:32:04 +0000 (UTC) Subject: [commit: ghc] wip/ttypeable: Testsuite updates (c420dcf) Message-ID: <20160708143204.19A8B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttypeable Link : http://ghc.haskell.org/trac/ghc/changeset/c420dcfbb4ff689c0fb7935c04b1f3fdbe3ec246/ghc >--------------------------------------------------------------- commit c420dcfbb4ff689c0fb7935c04b1f3fdbe3ec246 Author: Ben Gamari Date: Mon Jul 4 14:43:50 2016 +0200 Testsuite updates >--------------------------------------------------------------- c420dcfbb4ff689c0fb7935c04b1f3fdbe3ec246 compiler/typecheck/TcInteract.hs | 4 +- libraries/base/tests/T11334a.stdout | 6 +- libraries/base/tests/dynamic002.hs | 2 +- testsuite/tests/cabal/cabal09/reexport.cabal | 2 +- .../tests/dependent/should_compile/RaeJobTalk.hs | 2 +- .../tests/determinism/determ021/determ021.stdout | 4 +- testsuite/tests/ghc-api/T10508_api.stdout | 6 +- .../ghc-api/dynCompileExpr/dynCompileExpr.stdout | 2 +- .../should_compile/ExtraConstraints3.stderr | 20 -- .../partial-sigs/should_compile/Uncurry.stderr | 2 +- .../tests/safeHaskell/unsafeLibs/GoodImport03.hs | 2 +- .../tests/stranal/should_compile/T10482a.stderr | 324 +++++++++++++++++++++ .../tests/typecheck/should_fail/tcfail182.stderr | 2 +- testsuite/tests/typecheck/should_run/TypeOf.stdout | 27 +- .../tests/typecheck/should_run/TypeRep.stdout | 22 +- utils/haddock | 2 +- 16 files changed, 366 insertions(+), 63 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc c420dcfbb4ff689c0fb7935c04b1f3fdbe3ec246 From git at git.haskell.org Fri Jul 8 14:32:06 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 8 Jul 2016 14:32:06 +0000 (UTC) Subject: [commit: ghc] wip/ttypeable: Clarify serialization errors (3cb0a1f) Message-ID: <20160708143206.BE15A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttypeable Link : http://ghc.haskell.org/trac/ghc/changeset/3cb0a1f1c0550faca70832ed78598d95d21e4873/ghc >--------------------------------------------------------------- commit 3cb0a1f1c0550faca70832ed78598d95d21e4873 Author: Ben Gamari Date: Fri Jul 8 14:56:38 2016 +0200 Clarify serialization errors >--------------------------------------------------------------- 3cb0a1f1c0550faca70832ed78598d95d21e4873 compiler/utils/Binary.hs | 33 ++++++++++++++++++++++++++------- libraries/ghci/GHCi/TH/Binary.hs | 33 ++++++++++++++++++++++++++------- 2 files changed, 52 insertions(+), 14 deletions(-) diff --git a/compiler/utils/Binary.hs b/compiler/utils/Binary.hs index 29d3049..2282230 100644 --- a/compiler/utils/Binary.hs +++ b/compiler/utils/Binary.hs @@ -598,7 +598,7 @@ putTypeRep bh (TRApp f x) = do put_ bh (4 :: Word8) putTypeRep bh f putTypeRep bh x -putTypeRep _ _ = fail "putTypeRep: Impossible" +putTypeRep _ _ = fail "Binary.putTypeRep: Impossible" getTypeRepX :: BinHandle -> IO TypeRepX getTypeRepX bh = do @@ -611,7 +611,10 @@ getTypeRepX bh = do TypeRepX rep_k <- getTypeRepX bh case rep_k `eqTypeRep` (typeRep :: TypeRep Type) of Just HRefl -> pure $ TypeRepX $ mkTrCon con rep_k - Nothing -> fail "getTypeRepX: Kind mismatch" + Nothing -> failure "Kind mismatch in constructor application" + [ " Type constructor: " ++ show con + , " Applied to type : " ++ show rep_k + ] 4 -> do TypeRepX f <- getTypeRepX bh TypeRepX x <- getTypeRepX bh @@ -620,17 +623,33 @@ getTypeRepX bh = do case arg `eqTypeRep` typeRepKind x of Just HRefl -> pure $ TypeRepX $ mkTrApp f x - _ -> fail "getTypeRepX: Kind mismatch" - _ -> fail "getTypeRepX: Applied non-arrow type" - _ -> fail "getTypeRepX: Invalid TypeRepX" + _ -> failure "Kind mismatch in type application" + [ " Found argument of kind: " ++ show (typeRepKind x) + , " Where the constructor: " ++ show f + , " Expects kind: " ++ show arg + ] + _ -> failure "Applied non-arrow" + [ " Applied type: " ++ show f + , " To argument: " ++ show x + ] + _ -> failure "Invalid TypeRepX" [] + where + failure description info = + fail $ unlines $ [ "Binary.getTypeRepX: "++description ] + ++ map (" "++) info instance Typeable a => Binary (TypeRep (a :: k)) where put_ = putTypeRep get bh = do TypeRepX rep <- getTypeRepX bh - case rep `eqTypeRep` (typeRep :: TypeRep a) of + case rep `eqTypeRep` expected of Just HRefl -> pure rep - Nothing -> fail "Binary: Type mismatch" + Nothing -> fail $ unlines + [ "Binary: Type mismatch" + , " Deserialized type: " ++ show rep + , " Expected type: " ++ show expected + ] + where expected = typeRep :: TypeRep a instance Binary TypeRepX where put_ bh (TypeRepX rep) = putTypeRep bh rep diff --git a/libraries/ghci/GHCi/TH/Binary.hs b/libraries/ghci/GHCi/TH/Binary.hs index c60b513..e8a7a77 100644 --- a/libraries/ghci/GHCi/TH/Binary.hs +++ b/libraries/ghci/GHCi/TH/Binary.hs @@ -101,7 +101,7 @@ putTypeRep (TRApp f x) = do put (4 :: Word8) putTypeRep f putTypeRep x -putTypeRep _ = fail "putTypeRep: Impossible" +putTypeRep _ = fail "GHCi.TH.Binary.putTypeRep: Impossible" getTypeRepX :: Get TypeRepX getTypeRepX = do @@ -114,7 +114,10 @@ getTypeRepX = do TypeRepX rep_k <- getTypeRepX case rep_k `eqTypeRep` (typeRep :: TypeRep Type) of Just HRefl -> pure $ TypeRepX $ mkTrCon con rep_k - Nothing -> fail "getTypeRepX: Kind mismatch" + Nothing -> failure "Kind mismatch" + [ "Type constructor: " ++ show con + , "Applied to type: " ++ show rep_k + ] 4 -> do TypeRepX f <- getTypeRepX TypeRepX x <- getTypeRepX @@ -123,17 +126,33 @@ getTypeRepX = do case arg `eqTypeRep` typeRepKind x of Just HRefl -> pure $ TypeRepX $ mkTrApp f x - _ -> fail "getTypeRepX: Kind mismatch" - _ -> fail "getTypeRepX: Applied non-arrow type" - _ -> fail "getTypeRepX: Invalid TypeRepX" + _ -> failure "Kind mismatch" + [ "Found argument of kind: " ++ show (typeRepKind x) + , "Where the constructor: " ++ show f + , "Expects an argument of kind: " ++ show arg + ] + _ -> failure "Applied non-arrow type" + [ "Applied type: " ++ show f + , "To argument: " ++ show x + ] + _ -> failure "Invalid TypeRepX" [] + where + failure description info = + fail $ unlines $ [ "GHCi.TH.Binary.getTypeRepX: "++description ] + ++ map (" "++) info instance Typeable a => Binary (TypeRep (a :: k)) where put = putTypeRep get = do TypeRepX rep <- getTypeRepX - case rep `eqTypeRep` (typeRep :: TypeRep a) of + case rep `eqTypeRep` expected of Just HRefl -> pure rep - Nothing -> fail "Binary: Type mismatch" + Nothing -> fail $ unlines + [ "GHCi.TH.Binary: Type mismatch" + , " Deserialized type: " ++ show rep + , " Expected type: " ++ show expected + ] + where expected = typeRep :: TypeRep a instance Binary TypeRepX where put (TypeRepX rep) = putTypeRep rep From git at git.haskell.org Fri Jul 8 14:32:10 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 8 Jul 2016 14:32:10 +0000 (UTC) Subject: [commit: ghc] wip/ttypeable's head updated: Clarify serialization errors (3cb0a1f) Message-ID: <20160708143210.88B1C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/ttypeable' now includes: 3910306 Add -XStaticPointers to the flag reference. 08e47ca FunDep printer: Fix unicode arrow 43589f5 testsuite: add CmmSwitchTest for 32-bit platforms ae7e9cb Fix Windows build after Ticky changes 8e92974 Testsuite: mark T8761 expect_broken #12077 a1f3bb8 Fix failing T12010 d9cb7a8 compiler/iface: compress .hi files e44a6f9 users-guide: Vector version of Thomson-Wheeler logo 6d6d6e4 rules/sphinx: Add missing dependency on conf.py for pdf rule cf1efc7 users-guide: Fix index in PDF output da3c1eb Enable checkProddableBlock on x86_64 527ed72 Fix deriving Ord when RebindableSyntax is enabled c81e7b2 Build system: temp solution for parallelisation bug (#11960) f669764 Use `setSession` instead of `modifySession` when setting `HscEnv` a70a6da rts/Linker.c: Fix compile error on Arm fa58710 Update format specifiers for Tickey.c 2230c88 Testsuite: fix T12010 for real 8c9b8a3 Allow unlifted types in pattern synonym result type d835ee6 Fix build by removing unused import. 785b38f testsuite: Update max_bytes_used for T4029 9bb2772 Revert "compiler/iface: compress .hi files" 4f5b335 Suppress the warning about __sync_fetch_and_nand (#9678) 03d8960 Don't split the arg types in a PatSyn signature eb8eb02 Spelling in comment 839b424 Remove unused Type.splitFunTysN 9c3e55b Comments only 35053eb Testsuite: delete check_files_written 1bf5c12 Spelling 8f7d016 Add support for unicode TH quotes (#11743) 4c6e69d Document some benign nondeterminism 9d06ef1 Make Arrow desugaring deterministic 95dfdce Remove 'deriving Typeable' statements fe8a4e5 Runtime linker: Break m32 allocator out into its own file 1956cbf Fix: #12084 deprecate old profiling flags 31f1804 Testsuite: delete drvfail015.stderr-7.0 [skip ci] 1319363 Always use native-Haskell de/encoders for ASCII and latin1 ac38c02 Update submodule vector [skip ci] 961ed26 Fix broken links to mdo papers eec88ee RTS: simplify read_heap_profiling_flag bdc5558 Testsuite: introduce TEST_HC_OPTS_INTERACTIVE (#11468) 8408d84 Spelling in comments 6a5bce1 Testsuite: also normalise platform-dependent .stdout/stderr f07bf19 Testsuite: fix enum01/02/03 on Windows (#9399) 5020bc8 Testsuite: add a test for #5522 (-fliberate-case -fspec-constr) 0f1e315 Fix bytecode gen to deal with rep-polymorphism e9e61f1 Reduce special-casing for nullary unboxed tuple 5b8bec2 StgCmmExpr: Fix a duplication 5b145c9 Coverage.hs: Fix a duplication cd50d23 StgCmmCon: Do not generate moves from unused fields to local variables b43a793 More fixes for unboxed tuples 72fd407 Comments and white space only 59250dc StgCmmExpr: Remove a redundant list 3a00ff9 Do not init record accessors as exported 3f20da1 Typos in comments d0dd572 Clarify users' guide section on GeneralizedNewtypeDeriving d40682e Testsuite: don't use --interactive in Makefiles 1e67010 RtsFlags.c: Const correct fixes 7e4f3dc StgCmmUtils.emitMultiAssign: Make assertion msg more helpful 0ffa23d Remove unused FAST_STRING_NOT_NEEDED macro defs 930e74f Update a Cmm note 0676e68 Fix detection and use of `USE_LIBDW` cb2c042 Use nameSetAny in findUses f2b3be0 Improve failed knot-tying error message. 99ace83 Kill nameSetElems in getInfo 36d254a Testsuite: run tests in /tmp/ghctest-xxx instead of /tmp/ghctest/xxx 940229c Travis: llvm's apt repository is offline cb9f635 Localize orphan-related nondeterminism d348acd Serialize vParallelTyCons in a stable order 3eac3a0 Add nameSetElemsStable and fix the build dad39ff Remove dead generics-related code from OccName d753ea2 Use UniqDSet for finding free names in the Linker e2446c0 Kill nameSetElems in findImportUsage be47085 Kill nameSetElems in rnCmdTop 060c176 Whitespace only 1d1987e HscMain: Minor simplification 9cc6fac Make FieldLabelEnv a deterministic set 2046297 Document putSymbolTable determinism 4842a80 Derive instances in Data.Data 1dadd9a testsuite: Mark broken tests on powerpc64le 3747372 Refactored SymbolInfo to lower memory usage in RTS 079c1b8 Use useful names for Symbol Addr and Names in Linker.c 02f893e integer-gmp: Make minusInteger more efficient 4aa299d PrelInfo: Ensure that tuple promoted datacon names are in knownKeyNames eda73a3 RTS SMP: Use compiler built-ins on all platforms. 4dbacbc Rename isPinnedByteArray# to isByteArrayPinned# b948a1d Refactor the SymbolName and SymbolAddr types to be pointers 5965117 Replace hand-written Bounded instances with derived ones 0d963ca Add relocation type R_X86_64_REX_GOTPCRELX 4848ab9 Testsuite: fixup comments for T9872d [skip ci] 886f4c1 Better comment for orIfNotFound. f91d87d Failing test-case for #12135. 3042a9d Use UniqDFM for HomePackageTable 48e9a1f Implement deterministic CallInfoSet a90085b Add @since annotations to base instances e684f54 Desugar ApplicativeDo and RecDo deterministically 31ba8d6 Kill nameSetElems 46d2da0 Document putDictionary determinism 3e7a876 Kill foldUniqSet 1937ef1 Make UnitIdMap a deterministic map a13cb27 Merge MatchFixity and HsMatchContext 77ccdf3 Kill occSetElts 7fea712 Use a deterministic map for imp_dep_mods d05dee3 CoreToStg: Remove hand-written Eq instances of HowBound and LetInfo 4426c5f Kill two instances of uniqSetToList 0d6f428 Fix build by removing unused import c148212 Kill varSetElems in checkValidInferredKinds ad8e203 Use DVarSet in Vectorise.Exp 3b698e8 Document determinism in pprintClosureCommand 5db93d2 Make vectInfoParallelVars a DVarSet 7008515 Kill varSetElems 7d58a97 Use pprUFM in pprStgLVs 00e3a5d Typofix. 4d5b2f6 Testsuite driver: always quote opts.testdir f5f5a8a Testsuite Windows: mark T8308 expect_broken (#8308) d4b548e Add some determinism tests dd33245 Desugar: Display resulting program stats with -v2 44a3c18 Revert "Desugar: Display resulting program stats with -v2" c2bbc8b Report term sizes with -v3 even when -ddump is enabled 80cf4cf Literal: Remove unused hashLiteral function d7933cb Show sources of cost centers in .prof 8f6d292 Fix #12064 by making IfaceClass typechecking more lazy. acb9e85 Minor performance note about IdInfo. 11ff1df Fix #12076 by inlining trivial expressions in CorePrep. 48385cb Remove special casing of Windows in generic files ceaf7f1 Implement Eq TyCon directly 68c1c29 Remove Ord (CoAxiom br) 9dbf354 Testsuite: delete dead code [skip ci] e703a23 Docs: fix links to ghc-flags 70e0a56 Remove Ord Class b2624ee Remove Ord PatSyn 77b8c29 Remove Ord AltCon c22ab1a Docs: delete PatternGuards documentation b020db2 Fix Ticky histogram on Windows e9dfb6e Improve the error messages for static forms. b0a7664 prettyPrintClosure(): Untag the closure before accessing fields 47d8173 Remove Printer.c:prettyPrintClosure() bcb419a Fix #12099: Remove bogus flags 6adff01 Comments only 6905ce2 Refine imports slightly 0f0b002 Comments only 3ae18df Minor refactoring b9fa72a Small refactor to mkRuntimErrorId 9e5ea67 NUMA support c88f31a Rts flags cleanup 5990016 ModuleSet: Use an actual set instead of map to units 6ace660 rts: Fix build when USE_LARGE_ADDRESS_SPACE is undefined 9130867 Skip retc001 on OSX b40e1b4 Fix incorrect calculated relocations on Windows x86_64 29e1464 Disable T12031 on linux 2bb6ba6 rts: Fix NUMA when cross compiling d25cb61 Kill off redundant SigTv check in occurCheckExpand 15b9bf4 Improve typechecking of let-bindings c28dde3 Tidy up zonkQuantifiedTyVar 7afb7ad Get in-scope set right in top_instantiate 35c9de7 Move the constraint-kind validity check 1f66128 Beef up mkNakedCastTy 15fc528 Fix the in-scope set for extendTvSubstWithClone 599d912 Beef up isPredTy 8104f7c Remove some traceTc calls e064f50 Add to .gitignore 921ebc9 Test Trac #12055 1dcb32d A second test for Trac #12055 5cee88d Add thin library support to Windows too 7de776c Kill unused foldModuleEnv 586d558 Use UniqFM for SigOf 0497ee5 Make the Ord Module independent of Unique order d55a9b4 Update Haddock to follow change in LHsSigWcType 4f35646 Adjust error message slightly 8dfd4ae Build system: mention ghc version in bindist's `configure --help` docdir a2deee0 Testsuite: enable ghci.prog010 (#2542) 23b73c9 Don't GC sparks for CAFs 9d22fbe Rename cmpType to nonDetCmpType 753c5b2 Simplify readProcessEnvWithExitCode + set LANGUAGE=C 70a4589 Revert "Make the Ord Module independent of Unique order" e33ca0e Fix testsuite wibble 77bb092 Re-add FunTy (big patch) e368f32 Major patch to introduce TyConBinder c56f8bd CoreMonad: Update error msg function docs 930a525 Abort the build when a Core plugin pass is specified in stage1 compiler a7f65b8 Remove dead code: countOnce, countMany 498ed26 NUMA cleanups 8d33af9 CoreLint: Slightly improve case type annotation error msgs 3e8c495 CmmNode: Make CmmTickScope's Unique strict 2396d9b llvmGen: Make metadata ids a newtype 85e09b1 llvmGen: Consolidate MetaExpr pretty-printing 9bb0578 Revert accidental submodule updates e02beb1 Driver: `ghc ../Test` (without file extension) should work f72f23f Testsuite: run tests in .run instead of /tmp 6f6f515 Testsuite: write "\n" instead of "\r\n" when using mingw Python d94c405 Testsuite: validate the tests/stage1 directory with the stage1 compiler a4c8532 Validate: use `rm -f` instead of `rm` 6354991 VarEnv: Comment only 270d545 Add Bifoldable and Bitraversable to base 9649fc0 Refactor derived Generic instances to reduce allocations 4d71cc8 Avoid find_tycon panic if datacon is not in scope f12fb8a Fix trac #10647: Notice about lack of SIMD support 2897be7 PPC NCG: Fix float parameter passing on 64-bit. f4b0488 PPC NCG: Fix and refactor TOC handling. 0be38a2 llvmGen: Add strictness to metadata fields 0e92af9 Remove use of KProxy in GHC.Generics 0ba34b6 ApplicativeDo: allow "return $ e" e7e42c8 Fix double-free in T5644 (#12208) cdc14b4 Testsuite: remove Windows CR again.. [skip ci] 9cdde38 Testsuite: remove Windows CR [skip ci] cf6e656 Testsuite: remove Windows CR [skip ci] 3dc1202 Testsuite: tabs -> spaces [skip ci] 7e7094f Testsuite: tabs -> spaces [skip ci] 46ff80f Testsuite: tabs -> spaces [skip ci] 915e07c Testsuite: tabs -> spaces [skip ci] 5b03dc6 Testsuite: tabs -> spaces [skip ci] a7160fa Testsuite: tabs -> spaces [skip ci] 4a4bdda Testsuite: recover from utf8 decoding errors 6d0a4fc Testsuite: fix WAY=ghci when LOCAL=0 1ddc10b Testsuite: *do* replace backslashes in config.libdir 1d938aa Testsuite: mark tests expect broken 3b49f8f Testsuite: remove `-fforce-recomp` from default flags (#11980) 82f7f18 Testsuite: delete TEST_HC_OPTS_NO_RECOMP 135fc86 Testsuite: remove `-Wno-warn-tabs` from default flags ebaf26b Testsuite: delete dead code + cleanup e170d19 Testsuite: assume timeout_prog always exists ee3bde7 Expand and clarify the docs for ApplicativeDo (#11835) 7301404 Typos in comments d09e982 Don't quantify over Refl in a RULE 97a50f8 Delete commented-out code 1230629 Make checkFamInstConsistency less expensive a47b62c Second attempt to fix sizeExpr c0583a9 Fix build breakage due to rebase 9d62d09 Hopefully fix all the rebase-induced breakage 4e7d835 Typos in comments [skip ci] 6199588 More typos in comments [skip ci] 93f40cb Don't error on GCC inlining warning in rts 348f2db Make the Ord Module independent of Unique order (2nd try) 15641b0 Accept new (lower) allocations for T7257 7e7aeab Comments only cc92a44 Improve error message in deriving( Functor ) a1b3359 Remove unused arg to tcSuperClasses ce97b72 Expand given superclasses more eagerly 210a2e1 Test Trac #12163 3e0af46 Give lookupGRE_Name a better API e556f76 Remove unused import 643706e Narrow the warning for simplifiable constraints 2f8cd14 Narrow the use of record wildcards slightly 7fc20b0 Have Core linter accept programs using StaticPointers and -fhpc. 35d1564 Provide Uniquable version of SCC bb74021 Remove Ord TyCon 7f5d560 Very confusing typo in error message. 9a34bf1 Fix #11974 by adding a more smarts to TcDefaults. 8035d1a Fix #10963 and #11975 by adding new cmds to GHCi. 4ae950f Release notes for #11975 and #10963 df9611e Testsuite: do not copy .hi/.o files to testdir (#12112) d2958bd Improve typechecking of instance defaults c871ce4 Comments around invisibility 393928d Fix renamer panic f86a337 Remove bogus comment on ForAllTy bb84ee4 Improve pretty-printing of Avail 12c4449 Implement ReifyConStrictness for -fexternal-interpreter (#12219) d2006d0 Run all TH tests with -fexternal-interpreter (#12219) bdb0d24 Remote GHCi: separate out message types eb73219 Remote GHCi: comments only 0bab375 Fix T8761 (#12219, #12077) dadd8b8 Test Trac #12229 9bc2233 Fix typo in Data.Bitraverse Haddocks 31b5806 Clean up outdated comments in template-haskell changelog a33b498 Add template-haskell changelog note for #8761 5fdb854 s/Invisible/Inferred/g s/Visible/Required/g 4cc5a39 Refactor tcInferArgs and add comments. 8c1cedd Allow building static libs. da60e3e rts/Linker.c: Improve ugly C pre-processor hack 7843c71 Make T8761 deterministic, I hope ff1cc26 Don't run the run_command tests with ext-interp 82282e8 Remove some `undefined`s 60c24b2 Typos in user manual and code: recurisve -> recursive afa6e83 rts/Linker.c: Rename ONLY_USED_x86_64_HOST_ARCH macro bbf0aa2 Testsuite: never pick up .T files in .run directories 7593c2f Testsuite: report duplicate testnames when `make TEST=` 1f45bce Testsuite: remove one level of indentation [skip ci] 206b4a1 Testsuite: simplify extra_file handling bafd615 Testsuite: do not print timeout message 58f0086 Testsuite: open/close stdin/stdout/stderr explicitly d8e9b87 Testsuite: cleanup printing of summary 782cacf Testsuite: framework failure improvements (#11165) 6b3b631 Testsuite: run all indexed-types ways on ./validate --slow 0eb0378 Testsuite: do not add -debug explicitly in .T file 3fb9837 Testsuite: mark tests expect_broken af21e38 Don't omit any evidence bindings 23b80ac Deal correctly with unused imports for 'coerce' dc62a22 Wibble error message for #11471 dd92c67 Stop the simplifier from removing StaticPtr binds. 2e9079f Test Trac #12185 848e3ce Testsuite: fixes for python2.6 support 9a645a1 Refactor match to not use Unique order 8f7194f Double the file descriptor limit for openFile008 1084d37 Testsuite: use ignore_stderr/stdout instead of ignore_output 24194a6 Fix pretty-printer for IfaceCo e8d6271 Testsuite: do not depend on sys.stdout.encoding fb6e2c7 Delete Ord Unique 9854f14 Add a new determinism test b6b20a5 Reorganize some determinism tests 480e066 Remove ufmToList b8b3e30 Axe RecFlag on TyCons. 0701db1 Updates to handle new Cabal 430f5c8 Trac #11554 fix loopy GADTs 6a5d13c nativeGen: Allow -fregs-graph to be used f68d40c ghc-pkg: Drop trailing slashes in computing db paths f1e16e9 CmmExpr: remove unused `vgcFlag` function b65363d Fix check_uniques in non-unicode locale 0afc41b Testsuite: be less strict about topHandler03's stderr c27ce26 users-guide: Fix markup in release notes 81b437b Add NamedThing (GenLocated l e) instance b412d82 Allow one type signature for multiple pattern synonyms 6ba4197 rules/sphinx.mk: stop xelatex on error ee8d1fa Remove unused oc->isImportLib (#12230) 6377757 Linker: some extra debugging / logging cbfeff4 Remove uniqSetToList 0d522b8 Document some benign nondeterminism 0ab63cf Kill varEnvElts in seqDmdEnv 01f449f Fix 32-bit build failures 89a68ea HACK: CoreLint: Kill unsaturated unlifted types check 9b6a125 TcSMonad: Introduce tcLookupId e6ab5e5 Outputable: Refactor handling of CallStacks b892440 CoreLint: Improve debug output 13cee20 Start implementing library side of TTypeable be43621 Fix rebase 7a0910a Add quick compatibility note 0b183c3 Fix warnings 5698aa3 Various fixes 18e1f45 Fix serialization 70501cd Implement Data.Typeable.funResultTy e1aefb4 Binary: More explicit pattern matching b7887c2 More serialization b7ff4de Message: Import Data.Typeable.TypeRep 3475bde TcInteract: Unused parameter 0176683 Fix a few TTypeRep references 42b3de3 Fix recursive fingerprints e762e12 Finally serialization is both general and correct 48eeb01 Break recursive loop in serialization abc44be Kill todo 3cb2c52 Fix up representation pretty-printer 4eed289 Another recursive serialization case 69dbfe0 TcTypeable: Don't generate bindings for special primitive tycons 5f3d10f Move special tycons a6bbaf2 Internal things 221620e Fix primitive types eaffd46 Fix pretty-printer 5849617 Kill debugShow 9add749 Inline space ddfe7e3 Accept easy test output 1c6abb5 Add mkFunTy 9159bc6 More test fixes ca5e33d Fix T8132 ff67285 Render TYPE 'PtrRepLifted as * 2c33fe8 Internal: Rename type variable 913ccde Implement withTypeable a9b5b00 Bump base to 4.10.0 347c704 Fix withTypeable 152c249 Bump base 6c43926 testsuite: Bump base version 0c91d29 Rework Show c420dcf Testsuite updates 3cb0a1f Clarify serialization errors From git at git.haskell.org Fri Jul 8 14:57:16 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 8 Jul 2016 14:57:16 +0000 (UTC) Subject: [commit: ghc] master: Kill eltsUFM in classifyTyCons (4f21a51) Message-ID: <20160708145716.50EEA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4f21a518d10abff786794cda086da0474971cdf9/ghc >--------------------------------------------------------------- commit 4f21a518d10abff786794cda086da0474971cdf9 Author: Bartosz Nitka Date: Fri Jul 8 07:40:48 2016 -0700 Kill eltsUFM in classifyTyCons GHC Trac: #4012 >--------------------------------------------------------------- 4f21a518d10abff786794cda086da0474971cdf9 compiler/vectorise/Vectorise/Type/Classify.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/vectorise/Vectorise/Type/Classify.hs b/compiler/vectorise/Vectorise/Type/Classify.hs index 7963ae7..98d9042 100644 --- a/compiler/vectorise/Vectorise/Type/Classify.hs +++ b/compiler/vectorise/Vectorise/Type/Classify.hs @@ -67,8 +67,8 @@ classifyTyCons convStatus parTyCons tcs = classify [] [] [] [] convStatus parTyC refs = ds `delListFromUniqSet` tcs -- the tycons that directly or indirectly depend on parallel arrays - tcs_par | any ((`elemNameSet` parTyCons) . tyConName) . eltsUFM $ refs = tcs - | otherwise = [] + tcs_par | anyUFM ((`elemNameSet` parTyCons) . tyConName) refs = tcs + | otherwise = [] pts' = pts `extendNameSetList` map tyConName tcs_par From git at git.haskell.org Fri Jul 8 20:38:25 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 8 Jul 2016 20:38:25 +0000 (UTC) Subject: [commit: ghc] master: DsExpr: Remove usage of concatFS in fingerprintName (6c7c193) Message-ID: <20160708203825.9DD833A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6c7c193f376fe3b48992724c12f6ff393dca6528/ghc >--------------------------------------------------------------- commit 6c7c193f376fe3b48992724c12f6ff393dca6528 Author: Ben Gamari Date: Fri Jul 8 22:41:55 2016 +0200 DsExpr: Remove usage of concatFS in fingerprintName This was the only user of concatFS and really just wants the `String` anyways. Stumbled upon while looking at #12357. Test Plan: Validate Reviewers: austin Reviewed By: austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2386 >--------------------------------------------------------------- 6c7c193f376fe3b48992724c12f6ff393dca6528 compiler/deSugar/DsExpr.hs | 12 +++++------- 1 file changed, 5 insertions(+), 7 deletions(-) diff --git a/compiler/deSugar/DsExpr.hs b/compiler/deSugar/DsExpr.hs index 85177ee..bf04f13 100644 --- a/compiler/deSugar/DsExpr.hs +++ b/compiler/deSugar/DsExpr.hs @@ -54,9 +54,9 @@ import SrcLoc import Util import Bag import Outputable -import FastString import PatSyn +import Data.List ( intercalate ) import Data.IORef ( atomicModifyIORef' ) import Control.Monad @@ -470,12 +470,10 @@ dsExpr (HsStatic _ expr@(L loc _)) = do mkStaticPtrFingerprint :: Module -> DsM Fingerprint mkStaticPtrFingerprint this_mod = do n <- mkGenPerModuleNum this_mod - return $ fingerprintString $ unpackFS $ concatFS - [ unitIdFS $ moduleUnitId this_mod - , fsLit ":" - , moduleNameFS $ moduleName this_mod - , fsLit ":" - , mkFastString $ show n + return $ fingerprintString $ intercalate ":" + [ unitIdString $ moduleUnitId this_mod + , moduleNameString $ moduleName this_mod + , show n ] mkGenPerModuleNum :: Module -> DsM Int From git at git.haskell.org Sat Jul 9 16:19:25 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 9 Jul 2016 16:19:25 +0000 (UTC) Subject: [commit: ghc] master: Testsuite: expose TEST_CC (path to gcc) (0177c85) Message-ID: <20160709161925.75A623A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0177c85b614618039578d6670453e030eaf49846/ghc >--------------------------------------------------------------- commit 0177c85b614618039578d6670453e030eaf49846 Author: Thomas Miedema Date: Sat Jul 9 14:03:51 2016 +0200 Testsuite: expose TEST_CC (path to gcc) Reviewed by: Phyx Differential Revision: https://phabricator.haskell.org/D2394 >--------------------------------------------------------------- 0177c85b614618039578d6670453e030eaf49846 testsuite/mk/ghc-config.hs | 1 + testsuite/tests/rts/T11223/Makefile | 2 +- 2 files changed, 2 insertions(+), 1 deletion(-) diff --git a/testsuite/mk/ghc-config.hs b/testsuite/mk/ghc-config.hs index 4ca3d30..84f1523 100644 --- a/testsuite/mk/ghc-config.hs +++ b/testsuite/mk/ghc-config.hs @@ -28,6 +28,7 @@ main = do getGhcFieldOrDefault fields "GhcProfiled" "GHC Profiled" "NO" getGhcFieldProgWithDefault fields "AR" "ar command" "ar" getGhcFieldProgWithDefault fields "LLC" "LLVM llc command" "llc" + getGhcFieldProgWithDefault fields "TEST_CC" "C compiler command" "gcc" let pkgdb_flag = case lookup "Project version" fields of Just v diff --git a/testsuite/tests/rts/T11223/Makefile b/testsuite/tests/rts/T11223/Makefile index 4920704..c0d8420 100644 --- a/testsuite/tests/rts/T11223/Makefile +++ b/testsuite/tests/rts/T11223/Makefile @@ -6,7 +6,7 @@ include $(TOP)/mk/test.mk # Testing RTS linker object resolution # -CC=gcc +CC=$(TEST_CC) .PHONY: t_11223_simple_link t_11223_simple_link: From git at git.haskell.org Sun Jul 10 08:42:56 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 10 Jul 2016 08:42:56 +0000 (UTC) Subject: [commit: ghc] master: TysWiredIn: Use UniqFM lookup for built-in OccNames (f53d761) Message-ID: <20160710084256.5F81F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f53d761df9762232b54ec57a950d301011cd21f8/ghc >--------------------------------------------------------------- commit f53d761df9762232b54ec57a950d301011cd21f8 Author: Ben Gamari Date: Sat Jul 9 21:03:46 2016 +0200 TysWiredIn: Use UniqFM lookup for built-in OccNames Previously we would unpack the OccName into a String, then pattern match against this string. Due to the implementation of `unpackFS`, this actually unpacks the entire contents, even though we often only need to look at the first few characters. Here we take another approach: build a UniqFM with the known built-in OccNames, allowing us to use `FastString`'s hash-based comparison instead. Reviewers: simonpj, austin, simonmar Reviewed By: simonmar Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2385 GHC Trac Issues: #12357 >--------------------------------------------------------------- f53d761df9762232b54ec57a950d301011cd21f8 compiler/prelude/TysWiredIn.hs | 52 ++++++++++++++++++++---------------------- 1 file changed, 25 insertions(+), 27 deletions(-) diff --git a/compiler/prelude/TysWiredIn.hs b/compiler/prelude/TysWiredIn.hs index 51f5555..8465cd9 100644 --- a/compiler/prelude/TysWiredIn.hs +++ b/compiler/prelude/TysWiredIn.hs @@ -134,6 +134,7 @@ import {-# SOURCE #-} ConLike import TyCon import Class ( Class, mkClass ) import RdrName +import UniqFM import Name import NameSet ( NameSet, mkNameSet, elemNameSet ) import BasicTypes ( Arity, Boxity(..), @@ -635,39 +636,36 @@ decl in GHC.Classes, so I think this part may not work properly. But it's unused I think. -} -isBuiltInOcc_maybe :: OccName -> Maybe Name --- Built in syntax isn't "in scope" so these OccNames --- map to wired-in Names with BuiltInSyntax -isBuiltInOcc_maybe occ - = case occNameString occ of - "[]" -> choose_ns listTyConName nilDataConName - ":" -> Just consDataConName - "[::]" -> Just parrTyConName - "()" -> tup_name Boxed 0 - "(##)" -> tup_name Unboxed 0 - '(':',':rest -> parse_tuple Boxed 2 rest - '(':'#':',':rest -> parse_tuple Unboxed 2 rest - _other -> Nothing +builtInOccNames :: UniqFM (OccName -> Name) +builtInOccNames = listToUFM $ + [ (fsLit "[]", choose_ns listTyConName nilDataConName) + , (fsLit ":" , const consDataConName) + , (fsLit "[::]", const parrTyConName) + , (fsLit "()", tup_name Boxed 0) + , (fsLit "(##)", tup_name Unboxed 0) + ] ++ + [ (fsLit $ "("++replicate n ','++")", tup_name Boxed (n+1)) | n <- [1..62] ] ++ + [ (fsLit $ "(#"++replicate n ','++"#)", tup_name Unboxed (n+1)) | n <- [1..62] ] where - ns = occNameSpace occ - - parse_tuple sort n rest - | (',' : rest2) <- rest = parse_tuple sort (n+1) rest2 - | tail_matches sort rest = tup_name sort n - | otherwise = Nothing - - tail_matches Boxed ")" = True - tail_matches Unboxed "#)" = True - tail_matches _ _ = False + choose_ns :: Name -> Name -> OccName -> Name + choose_ns tc dc occ + | isTcClsNameSpace ns = tc + | isDataConNameSpace ns = dc + | otherwise = pprPanic "tup_name" (ppr occ) + where ns = occNameSpace occ tup_name boxity arity = choose_ns (getName (tupleTyCon boxity arity)) (getName (tupleDataCon boxity arity)) - choose_ns tc dc - | isTcClsNameSpace ns = Just tc - | isDataConNameSpace ns = Just dc - | otherwise = pprPanic "tup_name" (ppr occ) + +isBuiltInOcc_maybe :: OccName -> Maybe Name +-- Built in syntax isn't "in scope" so these OccNames +-- map to wired-in Names with BuiltInSyntax +isBuiltInOcc_maybe occ + = case lookupUFM builtInOccNames (occNameFS occ) of + Just f -> Just (f occ) + Nothing -> Nothing mkTupleOcc :: NameSpace -> Boxity -> Arity -> OccName -- No need to cache these, the caching is done in mk_tuple From git at git.haskell.org Sun Jul 10 19:35:27 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 10 Jul 2016 19:35:27 +0000 (UTC) Subject: [commit: ghc] master: check-api-annotations utility loads by filename (9a3df1f) Message-ID: <20160710193527.8B6513A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9a3df1f892499f9e8bfaa2096da63f2058c20027/ghc >--------------------------------------------------------------- commit 9a3df1f892499f9e8bfaa2096da63f2058c20027 Author: Alan Zimmerman Date: Sun Jul 10 21:38:01 2016 +0200 check-api-annotations utility loads by filename Previously it loaded by modulename, which prevented loading files with a Main module. >--------------------------------------------------------------- 9a3df1f892499f9e8bfaa2096da63f2058c20027 testsuite/tests/ghc-api/annotations/.gitignore | 1 + testsuite/tests/ghc-api/annotations/Makefile | 44 ++++++++++++---------- testsuite/tests/ghc-api/annotations/all.T | 1 + testsuite/tests/ghc-api/annotations/load-main.hs | 4 ++ .../tests/ghc-api/annotations/load-main.stdout | 14 +++++++ utils/check-api-annotations/Main.hs | 14 +++++-- 6 files changed, 55 insertions(+), 23 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 9a3df1f892499f9e8bfaa2096da63f2058c20027 From git at git.haskell.org Mon Jul 11 07:46:47 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 11 Jul 2016 07:46:47 +0000 (UTC) Subject: [commit: ghc] master: Add -package-env to the flags reference (17d0b84) Message-ID: <20160711074647.797473A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/17d0b84efb6e9f0ee219266d31a1871126ba82c0/ghc >--------------------------------------------------------------- commit 17d0b84efb6e9f0ee219266d31a1871126ba82c0 Author: Simon Marlow Date: Sun Jul 10 11:00:06 2016 +0100 Add -package-env to the flags reference >--------------------------------------------------------------- 17d0b84efb6e9f0ee219266d31a1871126ba82c0 docs/users_guide/packages.rst | 7 ++++++- utils/mkUserGuidePart/Options/Packages.hs | 18 +++++++++++------- 2 files changed, 17 insertions(+), 8 deletions(-) diff --git a/docs/users_guide/packages.rst b/docs/users_guide/packages.rst index 77f23c5..0040afe 100644 --- a/docs/users_guide/packages.rst +++ b/docs/users_guide/packages.rst @@ -1323,10 +1323,15 @@ environment specifies precisely which packages should be visible. Note that for the ``package-db`` directive, if a relative path is given it must be relative to the location of the package environment file. +.. ghc-flag:: -package-env ⟨file⟩|⟨name⟩ + + Use the package environment in ⟨file⟩, or in + ``$HOME/.ghc/arch-os-version/environments/⟨name⟩`` + In order, ``ghc`` will look for the package environment in the following locations: -- File ⟨file⟩ if you pass the option ``-package-env file``. +- File ⟨file⟩ if you pass the option :ghc-flag:`-package-env file`. - File ``$HOME/.ghc/arch-os-version/environments/name`` if you pass the option ``-package-env name``. diff --git a/utils/mkUserGuidePart/Options/Packages.hs b/utils/mkUserGuidePart/Options/Packages.hs index 36a7b48..373773c 100644 --- a/utils/mkUserGuidePart/Options/Packages.hs +++ b/utils/mkUserGuidePart/Options/Packages.hs @@ -4,11 +4,11 @@ import Types packagesOptions :: [Flag] packagesOptions = - [ flag { flagName = "-this-unit-id⟨P⟩" + [ flag { flagName = "-this-unit-id ⟨P⟩" , flagDescription = "Compile to be part of unit (i.e. package) ⟨P⟩" , flagType = DynamicFlag } - , flag { flagName = "-package⟨P⟩" + , flag { flagName = "-package ⟨P⟩" , flagDescription = "Expose package ⟨P⟩" , flagType = DynamicSettableFlag } @@ -16,15 +16,15 @@ packagesOptions = , flagDescription = "Hide all packages by default" , flagType = DynamicFlag } - , flag { flagName = "-hide-package⟨name⟩" + , flag { flagName = "-hide-package ⟨name⟩" , flagDescription = "Hide package ⟨P⟩" , flagType = DynamicSettableFlag } - , flag { flagName = "-ignore-package⟨name⟩" + , flag { flagName = "-ignore-package ⟨name⟩" , flagDescription = "Ignore package ⟨P⟩" , flagType = DynamicSettableFlag } - , flag { flagName = "-package-db⟨file⟩" + , flag { flagName = "-package-db ⟨file⟩" , flagDescription = "Add ⟨file⟩ to the package db stack." , flagType = DynamicFlag } @@ -52,11 +52,11 @@ packagesOptions = , flagDescription = "Don't automatically link in the base and rts packages." , flagType = DynamicFlag } - , flag { flagName = "-trust⟨P⟩" + , flag { flagName = "-trust ⟨P⟩" , flagDescription = "Expose package ⟨P⟩ and set it to be trusted" , flagType = DynamicSettableFlag } - , flag { flagName = "-distrust⟨P⟩" + , flag { flagName = "-distrust ⟨P⟩" , flagDescription = "Expose package ⟨P⟩ and set it to be distrusted" , flagType = DynamicSettableFlag } @@ -64,4 +64,8 @@ packagesOptions = , flagDescription = "Distrust all packages by default" , flagType = DynamicSettableFlag } + , flag { flagName = "-package-env ⟨file⟩|⟨name⟩" + , flagDescription = "Use the specified package environment." + , flagType = DynamicFlag + } ] From git at git.haskell.org Mon Jul 11 08:36:53 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 11 Jul 2016 08:36:53 +0000 (UTC) Subject: [commit: ghc] wip/12368: DmdAnal: Add a final, safe iteration (0b3b3e9) Message-ID: <20160711083653.B3E593A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/12368 Link : http://ghc.haskell.org/trac/ghc/changeset/0b3b3e9b152ed3fdf4ae9be6a599e48325f17337/ghc >--------------------------------------------------------------- commit 0b3b3e9b152ed3fdf4ae9be6a599e48325f17337 Author: Joachim Breitner Date: Thu Jul 7 11:23:48 2016 +0200 DmdAnal: Add a final, safe iteration this fixes #12368. Differential Revision: https://phabricator.haskell.org/D2392 >--------------------------------------------------------------- 0b3b3e9b152ed3fdf4ae9be6a599e48325f17337 compiler/basicTypes/Demand.hs | 15 +++++++++++++-- compiler/stranal/DmdAnal.hs | 21 ++++++++++++--------- testsuite/tests/stranal/should_run/all.T | 2 +- 3 files changed, 26 insertions(+), 12 deletions(-) diff --git a/compiler/basicTypes/Demand.hs b/compiler/basicTypes/Demand.hs index 8dc7f3b..1849acc 100644 --- a/compiler/basicTypes/Demand.hs +++ b/compiler/basicTypes/Demand.hs @@ -35,7 +35,8 @@ module Demand ( vanillaCprProdRes, cprSumRes, appIsBottom, isBottomingSig, pprIfaceStrictSig, trimCPRInfo, returnsCPR_maybe, - StrictSig(..), mkStrictSig, mkClosedStrictSig, nopSig, botSig, cprProdSig, + StrictSig(..), mkStrictSig, mkClosedStrictSig, + nopSig, botSig, toTopSig, cprProdSig, isTopSig, hasDemandEnvSig, splitStrictSig, increaseStrictSigArity, seqDemand, seqDemandList, seqDmdType, seqStrictSig, @@ -1261,11 +1262,18 @@ emptyDmdEnv = emptyVarEnv -- nopDmdType is the demand of doing nothing -- (lazy, absent, no CPR information, no termination information). -- Note that it is ''not'' the top of the lattice (which would be "may use everything"), --- so it is (no longer) called topDmd +-- so it is (no longer) called topDmdType nopDmdType, botDmdType :: DmdType nopDmdType = DmdType emptyDmdEnv [] topRes botDmdType = DmdType emptyDmdEnv [] botRes +-- This converts a demand type to the least useful (most conservative) type +-- that mentions the same free variables. It takes the role of a top element, +-- which we do not have, since a top element would have to mention all variables +-- in the DmdEnv +toTopDmdType :: DmdType -> DmdType +toTopDmdType (DmdType env _ _) = DmdType (mapVarEnv (const topDmd) env) [] topRes + cprProdDmdType :: Arity -> DmdType cprProdDmdType arity = DmdType emptyDmdEnv [] (vanillaCprProdRes arity) @@ -1690,6 +1698,9 @@ nopSig, botSig :: StrictSig nopSig = StrictSig nopDmdType botSig = StrictSig botDmdType +toTopSig :: StrictSig -> StrictSig +toTopSig (StrictSig ty) = StrictSig (toTopDmdType ty) + cprProdSig :: Arity -> StrictSig cprProdSig arity = StrictSig (cprProdDmdType arity) diff --git a/compiler/stranal/DmdAnal.hs b/compiler/stranal/DmdAnal.hs index 53144ff..9928e17 100644 --- a/compiler/stranal/DmdAnal.hs +++ b/compiler/stranal/DmdAnal.hs @@ -475,26 +475,22 @@ dmdFix top_lvl env orig_pairs loop' n env pairs loop' n env pairs - | found_fixpoint + | found_fixpoint || n > 10 = (env', lazy_fv, pairs') -- Note: return pairs', not pairs. pairs' is the result of -- processing the RHSs with sigs (= sigs'), whereas pairs -- is the result of processing the RHSs with the *previous* -- iteration of sigs. - - | n >= 10 + | n == 10 = -- pprTrace "dmdFix loop" (ppr n <+> (vcat -- [ text "Sigs:" <+> ppr [ (id,lookupVarEnv (sigEnv env) id, -- lookupVarEnv (sigEnv env') id) -- | (id,_) <- pairs], -- text "env:" <+> ppr env, -- text "binds:" <+> pprCoreBinding (Rec pairs)])) - (env, lazy_fv, orig_pairs) -- Safe output - -- The lazy_fv part is really important! orig_pairs has no strictness - -- info, including nothing about free vars. But if we have - -- letrec f = ....y..... in ...f... - -- where 'y' is free in f, we must record that y is mentioned, - -- otherwise y will get recorded as absent altogether + loop (n+1) (addPessimisticSigs env bndrs) pairs' + -- We are not going to find a fix point any time soon. So do one final round + -- of analysis with safe assumptions about the strictness signatures | otherwise = loop (n+1) (nonVirgin env') pairs' @@ -1009,6 +1005,13 @@ addInitialSigs top_lvl env@(AE { ae_sigs = sigs, ae_virgin = virgin }) ids init_sig | virgin = \_ -> botSig | otherwise = idStrictness +addPessimisticSigs :: AnalEnv -> [Id] -> AnalEnv +addPessimisticSigs env@(AE { ae_sigs = sigs }) ids + = env { ae_sigs = extendVarEnvList sigs new_sigs } + where + new_sigs = [ (id, (toTopSig sig, top_lvl)) + | id <- ids, let Just (sig, top_lvl) = lookupSigEnv env id ] + nonVirgin :: AnalEnv -> AnalEnv nonVirgin env = env { ae_virgin = False } diff --git a/testsuite/tests/stranal/should_run/all.T b/testsuite/tests/stranal/should_run/all.T index 6846c82..5b976f1 100644 --- a/testsuite/tests/stranal/should_run/all.T +++ b/testsuite/tests/stranal/should_run/all.T @@ -12,4 +12,4 @@ test('T10148', normal, compile_and_run, ['']) test('T10218', normal, compile_and_run, ['']) test('T11076', normal, multimod_compile_and_run, ['T11076.hs', 'T11076_prim.cmm']) test('T11555a', normal, compile_and_run, ['']) -test('T12368', [ exit_code(1), expect_broken(12368) ], compile_and_run, ['']) +test('T12368', exit_code(1), compile_and_run, ['']) From git at git.haskell.org Mon Jul 11 09:10:50 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 11 Jul 2016 09:10:50 +0000 (UTC) Subject: [commit: ghc] wip/T12370: Demand analyser: Implement LetUp rule (#12370) (cc95b21) Message-ID: <20160711091050.6242B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T12370 Link : http://ghc.haskell.org/trac/ghc/changeset/cc95b211e7d08cda47d3e86632b5f514d5c8a876/ghc >--------------------------------------------------------------- commit cc95b211e7d08cda47d3e86632b5f514d5c8a876 Author: Joachim Breitner Date: Wed Jul 6 15:44:18 2016 +0200 Demand analyser: Implement LetUp rule (#12370) This makes the implementation match the description in the paper more closely: There, a let binding that is not a function has first its body analised, and then the binding’s RHS. This way, the demand on the bound variable by the body can be fed into the RHS, yielding more precise results. Performance measurements do unfortunately not show significant improvements or regessions. Differential Revision: https://phabricator.haskell.org/D2395 >--------------------------------------------------------------- cc95b211e7d08cda47d3e86632b5f514d5c8a876 compiler/coreSyn/CoreSyn.hs | 8 +++ compiler/stranal/DmdAnal.hs | 74 ++++++++++++++++------ .../simplCore/should_compile/spec-inline.stderr | 2 +- 3 files changed, 62 insertions(+), 22 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc cc95b211e7d08cda47d3e86632b5f514d5c8a876 From git at git.haskell.org Mon Jul 11 17:13:14 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 11 Jul 2016 17:13:14 +0000 (UTC) Subject: [commit: ghc] master: Pretty: delete really old changelog (372dbc4) Message-ID: <20160711171314.B28A53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/372dbc4e78abfb6b5d72c0fea27a1c858c5cd797/ghc >--------------------------------------------------------------- commit 372dbc4e78abfb6b5d72c0fea27a1c858c5cd797 Author: Thomas Miedema Date: Mon Jul 11 17:59:59 2016 +0200 Pretty: delete really old changelog This changelog is very incomplete, and basically useless. I'm removing it, because it made it harder to compare this copy of `Pretty.hs` with the copy in `libraries/pretty` (from which a similar changelog was deleted some time ago). >--------------------------------------------------------------- 372dbc4e78abfb6b5d72c0fea27a1c858c5cd797 compiler/utils/Pretty.hs | 174 ++++++----------------------------------------- 1 file changed, 20 insertions(+), 154 deletions(-) diff --git a/compiler/utils/Pretty.hs b/compiler/utils/Pretty.hs index 74d69f2..ab7db59 100644 --- a/compiler/utils/Pretty.hs +++ b/compiler/utils/Pretty.hs @@ -1,161 +1,27 @@ {-# LANGUAGE BangPatterns #-} -{- -********************************************************************************* -* * -* John Hughes's and Simon Peyton Jones's Pretty Printer Combinators * -* * -* based on "The Design of a Pretty-printing Library" * -* in Advanced Functional Programming, * -* Johan Jeuring and Erik Meijer (eds), LNCS 925 * -* http://www.cs.chalmers.se/~rjmh/Papers/pretty.ps * -* * -* Heavily modified by Simon Peyton Jones, Dec 96 * -* * -********************************************************************************* - -Version 3.0 28 May 1997 - * Cured massive performance bug. If you write - - foldl <> empty (map (text.show) [1..10000]) - - you get quadratic behaviour with V2.0. Why? For just the same reason as you get - quadratic behaviour with left-associated (++) chains. - - This is really bad news. One thing a pretty-printer abstraction should - certainly guarantee is insensivity to associativity. It matters: suddenly - GHC's compilation times went up by a factor of 100 when I switched to the - new pretty printer. - - I fixed it with a bit of a hack (because I wanted to get GHC back on the - road). I added two new constructors to the Doc type, Above and Beside: - - <> = Beside - $$ = Above - - Then, where I need to get to a "TextBeside" or "NilAbove" form I "force" - the Doc to squeeze out these suspended calls to Beside and Above; but in so - doing I re-associate. It's quite simple, but I'm not satisfied that I've done - the best possible job. I'll send you the code if you are interested. - - * Added new exports: - punctuate, hang - int, integer, float, double, rational, - lparen, rparen, lbrack, rbrack, lbrace, rbrace, - - * fullRender's type signature has changed. Rather than producing a string it - now takes an extra couple of arguments that tells it how to glue fragments - of output together: - - fullRender :: Mode - -> Int -- Line length - -> Float -- Ribbons per line - -> (TextDetails -> a -> a) -- What to do with text - -> a -- What to do at the end - -> Doc - -> a -- Result - - The "fragments" are encapsulated in the TextDetails data type: - data TextDetails = Chr Char - | Str String - | PStr FastString - - The Chr and Str constructors are obvious enough. The PStr constructor has a packed - string (FastString) inside it. It's generated by using the new "ptext" export. - - An advantage of this new setup is that you can get the renderer to do output - directly (by passing in a function of type (TextDetails -> IO () -> IO ()), - rather than producing a string that you then print. - - -Version 2.0 24 April 1997 - * Made empty into a left unit for <> as well as a right unit; - it is also now true that - nest k empty = empty - which wasn't true before. - - * Fixed an obscure bug in sep that occasionally gave very weird behaviour - - * Added $+$ - - * Corrected and tidied up the laws and invariants - -====================================================================== -Relative to John's original paper, there are the following new features: - -1. There's an empty document, "empty". It's a left and right unit for - both <> and $$, and anywhere in the argument list for - sep, hcat, hsep, vcat, fcat etc. - - It is Really Useful in practice. - -2. There is a paragraph-fill combinator, fsep, that's much like sep, - only it keeps fitting things on one line until it can't fit any more. - -3. Some random useful extra combinators are provided. - <+> puts its arguments beside each other with a space between them, - unless either argument is empty in which case it returns the other - +{-# LANGUAGE MagicHash #-} - hcat is a list version of <> - hsep is a list version of <+> - vcat is a list version of $$ - - sep (separate) is either like hsep or like vcat, depending on what fits - - cat is behaves like sep, but it uses <> for horizontal conposition - fcat is behaves like fsep, but it uses <> for horizontal conposition - - These new ones do the obvious things: - char, semi, comma, colon, space, - parens, brackets, braces, - quotes, quote, doubleQuotes - -4. The "above" combinator, $$, now overlaps its two arguments if the - last line of the top argument stops before the first line of the second begins. - For example: text "hi" $$ nest 5 "there" - lays out as - hi there - rather than - hi - there - - There are two places this is really useful - - a) When making labelled blocks, like this: - Left -> code for left - Right -> code for right - LongLongLongLabel -> - code for longlonglonglabel - The block is on the same line as the label if the label is - short, but on the next line otherwise. - - b) When laying out lists like this: - [ first - , second - , third - ] - which some people like. But if the list fits on one line - you want [first, second, third]. You can't do this with - John's original combinators, but it's quite easy with the - new $$. - - The combinator $+$ gives the original "never-overlap" behaviour. - -5. Several different renderers are provided: - * a standard one - * one that uses cut-marks to avoid deeply-nested documents - simply piling up in the right-hand margin - * one that ignores indentation (fewer chars output; good for machines) - * one that ignores indentation and newlines (ditto, only more so) - -6. Numerous implementation tidy-ups - Use of unboxed data types to speed up the implementation --} - - -{-# LANGUAGE BangPatterns, CPP, MagicHash #-} +----------------------------------------------------------------------------- +-- | +-- Module : Pretty +-- Copyright : (c) The University of Glasgow 2001 +-- License : BSD-style (see the file LICENSE) +-- +-- Maintainer : David Terei +-- Stability : stable +-- Portability : portable +-- +-- John Hughes's and Simon Peyton Jones's Pretty Printer Combinators +-- +-- Based on /The Design of a Pretty-printing Library/ +-- in Advanced Functional Programming, +-- Johan Jeuring and Erik Meijer (eds), LNCS 925 +-- +-- +----------------------------------------------------------------------------- module Pretty ( + -- * The document type Doc, TextDetails(..), From git at git.haskell.org Mon Jul 11 22:37:34 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 11 Jul 2016 22:37:34 +0000 (UTC) Subject: [commit: ghc] branch 'wip/binary-bytestring' created Message-ID: <20160711223734.F0F013A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/binary-bytestring Referencing: 913e1a397c79dc9249935bfb16a44e83c07452eb From git at git.haskell.org Mon Jul 11 22:37:37 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 11 Jul 2016 22:37:37 +0000 (UTC) Subject: [commit: ghc] wip/binary-bytestring: Binary: Use ByteString's copy in getBS (9245482) Message-ID: <20160711223737.C221F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/binary-bytestring Link : http://ghc.haskell.org/trac/ghc/changeset/9245482005cbcec5b7b1341066657a4f59804c1c/ghc >--------------------------------------------------------------- commit 9245482005cbcec5b7b1341066657a4f59804c1c Author: Ben Gamari Date: Sun Jul 10 16:19:04 2016 +0200 Binary: Use ByteString's copy in getBS It's unclear how much of an effect on runtime this will have, but if nothing else it's simpler. >--------------------------------------------------------------- 9245482005cbcec5b7b1341066657a4f59804c1c compiler/utils/Binary.hs | 29 +++++++++++------------------ 1 file changed, 11 insertions(+), 18 deletions(-) diff --git a/compiler/utils/Binary.hs b/compiler/utils/Binary.hs index 9f8d926..640c529 100644 --- a/compiler/utils/Binary.hs +++ b/compiler/utils/Binary.hs @@ -70,7 +70,7 @@ import SrcLoc import Foreign import Data.Array import Data.ByteString (ByteString) -import qualified Data.ByteString.Internal as BS +import qualified Data.ByteString as BS import qualified Data.ByteString.Unsafe as BS import Data.IORef import Data.Char ( ord, chr ) @@ -692,25 +692,18 @@ putBS bh bs = go (n+1) go 0 -{- -- possible faster version, not quite there yet: -getBS bh at BinMem{} = do - (I# l) <- get bh - arr <- readIORef (arr_r bh) - off <- readFastMutInt (off_r bh) - return $! (mkFastSubBytesBA# arr off l) --} getBS :: BinHandle -> IO ByteString getBS bh = do - l <- get bh - fp <- mallocForeignPtrBytes l - withForeignPtr fp $ \ptr -> do - let go n | n == l = return $ BS.fromForeignPtr fp 0 l - | otherwise = do - b <- getByte bh - pokeElemOff ptr n b - go (n+1) - -- - go 0 + l <- get bh :: IO Int + arr <- readIORef (_arr_r bh) + sz <- readFastMutInt (_sz_r bh) + off <- readFastMutInt (_off_r bh) + when (off + l > sz) $ + ioError (mkIOError eofErrorType "Data.Binary.getBS" Nothing Nothing) + writeFastMutInt (_off_r bh) (off+l) + withForeignPtr arr $ \ptr -> do + bs <- BS.unsafePackCStringLen (castPtr $ ptr `plusPtr` off, fromIntegral l) + return $! BS.copy bs instance Binary ByteString where put_ bh f = putBS bh f From git at git.haskell.org Mon Jul 11 22:37:40 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 11 Jul 2016 22:37:40 +0000 (UTC) Subject: [commit: ghc] wip/binary-bytestring: TysWiredIn: Notes (91a0420) Message-ID: <20160711223740.956C33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/binary-bytestring Link : http://ghc.haskell.org/trac/ghc/changeset/91a04202fb644f8e8afb8e0bd5e4c57a8ec220ce/ghc >--------------------------------------------------------------- commit 91a04202fb644f8e8afb8e0bd5e4c57a8ec220ce Author: Ben Gamari Date: Tue Jul 12 00:12:45 2016 +0200 TysWiredIn: Notes >--------------------------------------------------------------- 91a04202fb644f8e8afb8e0bd5e4c57a8ec220ce compiler/prelude/TysWiredIn.hs | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/compiler/prelude/TysWiredIn.hs b/compiler/prelude/TysWiredIn.hs index 65abdd8..609234f 100644 --- a/compiler/prelude/TysWiredIn.hs +++ b/compiler/prelude/TysWiredIn.hs @@ -637,9 +637,12 @@ decl in GHC.Classes, so I think this part may not work properly. But it's unused I think. -} +-- | Built in syntax isn't "in scope" so these OccNames map to wired-in Names +-- with BuiltInSyntax. However, this should only be necessary while resolving +-- names produced by Template Haskell splices since we take care to encode +-- built-in syntax names specially in interface files. See +-- Note [Symbol table representation of names]. isBuiltInOcc_maybe :: OccName -> Maybe Name --- Built in syntax isn't "in scope" so these OccNames --- map to wired-in Names with BuiltInSyntax isBuiltInOcc_maybe occ = case name of "[]" -> Just $ choose_ns listTyConName nilDataConName From git at git.haskell.org Mon Jul 11 22:37:43 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 11 Jul 2016 22:37:43 +0000 (UTC) Subject: [commit: ghc] wip/binary-bytestring: Binary: Fix incorrect name in comment (9e3f477) Message-ID: <20160711223743.5EF293A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/binary-bytestring Link : http://ghc.haskell.org/trac/ghc/changeset/9e3f477419996a54357aa38a908b7e1282e1bfc0/ghc >--------------------------------------------------------------- commit 9e3f477419996a54357aa38a908b7e1282e1bfc0 Author: Ben Gamari Date: Mon Jul 11 18:43:08 2016 +0200 Binary: Fix incorrect name in comment >--------------------------------------------------------------- 9e3f477419996a54357aa38a908b7e1282e1bfc0 compiler/utils/Binary.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/utils/Binary.hs b/compiler/utils/Binary.hs index 640c529..9f7c03d 100644 --- a/compiler/utils/Binary.hs +++ b/compiler/utils/Binary.hs @@ -664,7 +664,7 @@ getDictionary bh = do -- The Symbol Table --------------------------------------------------------- --- On disk, the symbol table is an array of IfaceExtName, when +-- On disk, the symbol table is an array of IfExtName, when -- reading it in we turn it into a SymbolTable. type SymbolTable = Array Int Name From git at git.haskell.org Mon Jul 11 22:37:46 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 11 Jul 2016 22:37:46 +0000 (UTC) Subject: [commit: ghc] wip/binary-bytestring: Wiring in tuples note (913e1a3) Message-ID: <20160711223746.37A743A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/binary-bytestring Link : http://ghc.haskell.org/trac/ghc/changeset/913e1a397c79dc9249935bfb16a44e83c07452eb/ghc >--------------------------------------------------------------- commit 913e1a397c79dc9249935bfb16a44e83c07452eb Author: Ben Gamari Date: Tue Jul 12 00:12:52 2016 +0200 Wiring in tuples note This should probably just be folded in to the note above >--------------------------------------------------------------- 913e1a397c79dc9249935bfb16a44e83c07452eb compiler/iface/IfaceEnv.hs | 10 ++++++++++ 1 file changed, 10 insertions(+) diff --git a/compiler/iface/IfaceEnv.hs b/compiler/iface/IfaceEnv.hs index b70c8e9..d4aa03b 100644 --- a/compiler/iface/IfaceEnv.hs +++ b/compiler/iface/IfaceEnv.hs @@ -202,6 +202,16 @@ However, there are two reasons why we might look up an Orig RdrName: go this route (Trac #8954). -} +{- +Note [Wiring in tuples] +~~~~~~~~~~~~~~~~~~~~~~~ + +The wiring-in of the tuple types is a bit tricky. The reason is that there are +very many of them and we consequently want to avoid cluttering the name cache +with them unnecessarily. For this reason we specially encode tuple Names in +interface files, +-} + lookupOrigNameCache :: OrigNameCache -> Module -> OccName -> Maybe Name lookupOrigNameCache nc mod occ | mod == gHC_TYPES From git at git.haskell.org Mon Jul 11 22:37:49 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 11 Jul 2016 22:37:49 +0000 (UTC) Subject: [commit: ghc] wip/binary-bytestring: TysWiredIn: Switch back to parsing tuple names (0848a2b) Message-ID: <20160711223749.1D4303A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/binary-bytestring Link : http://ghc.haskell.org/trac/ghc/changeset/0848a2b1044e541f0ccf1fe6eb73885570e8f14b/ghc >--------------------------------------------------------------- commit 0848a2b1044e541f0ccf1fe6eb73885570e8f14b Author: Ben Gamari Date: Mon Jul 11 21:20:59 2016 +0200 TysWiredIn: Switch back to parsing tuple names >--------------------------------------------------------------- 0848a2b1044e541f0ccf1fe6eb73885570e8f14b compiler/prelude/TysWiredIn.hs | 51 ++++++++++++++++++++++-------------------- 1 file changed, 27 insertions(+), 24 deletions(-) diff --git a/compiler/prelude/TysWiredIn.hs b/compiler/prelude/TysWiredIn.hs index 8465cd9..65abdd8 100644 --- a/compiler/prelude/TysWiredIn.hs +++ b/compiler/prelude/TysWiredIn.hs @@ -5,6 +5,7 @@ -} {-# LANGUAGE CPP #-} +{-# LANGUAGE OverloadedStrings #-} -- | This module is about types that can be defined in Haskell, but which -- must be wired into the compiler nonetheless. C.f module TysPrim @@ -134,7 +135,6 @@ import {-# SOURCE #-} ConLike import TyCon import Class ( Class, mkClass ) import RdrName -import UniqFM import Name import NameSet ( NameSet, mkNameSet, elemNameSet ) import BasicTypes ( Arity, Boxity(..), @@ -148,6 +148,8 @@ import Outputable import Util import BooleanFormula ( mkAnd ) +import qualified Data.ByteString.Char8 as BS + alpha_tyvar :: [TyVar] alpha_tyvar = [alphaTyVar] @@ -181,8 +183,7 @@ names in PrelNames, so they use wTcQual, wDataQual, etc -- define here. -- -- Because of their infinite nature, this list excludes tuples, Any and implicit --- parameter TyCons. Instead, we have a hack in lookupOrigNameCache to deal with --- these names. +-- parameter TyCons (see Note [Built-in syntax and the OrigNameCache]). -- -- See also Note [Known-key names] wiredInTyCons :: [TyCon] @@ -636,19 +637,30 @@ decl in GHC.Classes, so I think this part may not work properly. But it's unused I think. -} -builtInOccNames :: UniqFM (OccName -> Name) -builtInOccNames = listToUFM $ - [ (fsLit "[]", choose_ns listTyConName nilDataConName) - , (fsLit ":" , const consDataConName) - , (fsLit "[::]", const parrTyConName) - , (fsLit "()", tup_name Boxed 0) - , (fsLit "(##)", tup_name Unboxed 0) - ] ++ - [ (fsLit $ "("++replicate n ','++")", tup_name Boxed (n+1)) | n <- [1..62] ] ++ - [ (fsLit $ "(#"++replicate n ','++"#)", tup_name Unboxed (n+1)) | n <- [1..62] ] +isBuiltInOcc_maybe :: OccName -> Maybe Name +-- Built in syntax isn't "in scope" so these OccNames +-- map to wired-in Names with BuiltInSyntax +isBuiltInOcc_maybe occ = + case name of + "[]" -> Just $ choose_ns listTyConName nilDataConName + ":" -> Just consDataConName + "[::]" -> Just parrTyConName + "()" -> Just $ tup_name Boxed 0 + "(##)" -> Just $ tup_name Unboxed 0 + _ | Just rest <- name `BS.stripPrefix` "(" + , (commas, rest') <- BS.span (==',') rest + , ")" <- rest' + -> Just $ tup_name Boxed (1+BS.length commas) + _ | Just rest <- name `BS.stripPrefix` "(#" + , (commas, rest') <- BS.span (==',') rest + , "#)" <- rest' + -> Just $ tup_name Unboxed (1+BS.length commas) + _ -> Nothing where - choose_ns :: Name -> Name -> OccName -> Name - choose_ns tc dc occ + name = fastStringToByteString $ occNameFS occ + + choose_ns :: Name -> Name -> Name + choose_ns tc dc | isTcClsNameSpace ns = tc | isDataConNameSpace ns = dc | otherwise = pprPanic "tup_name" (ppr occ) @@ -658,15 +670,6 @@ builtInOccNames = listToUFM $ = choose_ns (getName (tupleTyCon boxity arity)) (getName (tupleDataCon boxity arity)) - -isBuiltInOcc_maybe :: OccName -> Maybe Name --- Built in syntax isn't "in scope" so these OccNames --- map to wired-in Names with BuiltInSyntax -isBuiltInOcc_maybe occ - = case lookupUFM builtInOccNames (occNameFS occ) of - Just f -> Just (f occ) - Nothing -> Nothing - mkTupleOcc :: NameSpace -> Boxity -> Arity -> OccName -- No need to cache these, the caching is done in mk_tuple mkTupleOcc ns Boxed ar = mkOccName ns (mkBoxedTupleStr ar) From git at git.haskell.org Mon Jul 11 22:37:51 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 11 Jul 2016 22:37:51 +0000 (UTC) Subject: [commit: ghc] wip/binary-bytestring: IfaceEnv: Only check for built-in OccNames if mod is GHC.Types (524ff05) Message-ID: <20160711223751.CFDD13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/binary-bytestring Link : http://ghc.haskell.org/trac/ghc/changeset/524ff05a7f36a0cc92be0afb9cac35ec9181e177/ghc >--------------------------------------------------------------- commit 524ff05a7f36a0cc92be0afb9cac35ec9181e177 Author: Ben Gamari Date: Mon Jul 11 18:41:40 2016 +0200 IfaceEnv: Only check for built-in OccNames if mod is GHC.Types This check is not entirely cheap and will not succeed unless we are looking for something in the module where built-in syntax lives, GHC.Types. >--------------------------------------------------------------- 524ff05a7f36a0cc92be0afb9cac35ec9181e177 compiler/iface/IfaceEnv.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/compiler/iface/IfaceEnv.hs b/compiler/iface/IfaceEnv.hs index 0c8d8e9..b70c8e9 100644 --- a/compiler/iface/IfaceEnv.hs +++ b/compiler/iface/IfaceEnv.hs @@ -33,6 +33,7 @@ import Module import FastString import FastStringEnv import IfaceType +import PrelNames ( gHC_TYPES ) import UniqSupply import SrcLoc import Util @@ -203,7 +204,8 @@ However, there are two reasons why we might look up an Orig RdrName: lookupOrigNameCache :: OrigNameCache -> Module -> OccName -> Maybe Name lookupOrigNameCache nc mod occ - | Just name <- isBuiltInOcc_maybe occ + | mod == gHC_TYPES + , Just name <- isBuiltInOcc_maybe occ = -- See Note [Known-key names], 3(c) in PrelNames -- Special case for tuples; there are too many -- of them to pre-populate the original-name cache From git at git.haskell.org Tue Jul 12 10:33:34 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 12 Jul 2016 10:33:34 +0000 (UTC) Subject: [commit: ghc] wip/T12370: Demand analyser: Implement LetUp rule (#12370) (4428f61) Message-ID: <20160712103334.C5B8F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T12370 Link : http://ghc.haskell.org/trac/ghc/changeset/4428f614d3dea136cee40f00e39878126d02b079/ghc >--------------------------------------------------------------- commit 4428f614d3dea136cee40f00e39878126d02b079 Author: Joachim Breitner Date: Wed Jul 6 15:44:18 2016 +0200 Demand analyser: Implement LetUp rule (#12370) This makes the implementation match the description in the paper more closely: There, a let binding that is not a function has first its body analised, and then the binding’s RHS. This way, the demand on the bound variable by the body can be fed into the RHS, yielding more precise results. Performance measurements do unfortunately not show significant improvements or regessions. Differential Revision: https://phabricator.haskell.org/D2395 >--------------------------------------------------------------- 4428f614d3dea136cee40f00e39878126d02b079 compiler/stranal/DmdAnal.hs | 100 ++++++++++++++++----- .../simplCore/should_compile/spec-inline.stderr | 2 +- testsuite/tests/stranal/sigs/T12370.hs | 12 +++ testsuite/tests/stranal/sigs/T12370.stderr | 14 +++ testsuite/tests/stranal/sigs/all.T | 1 + 5 files changed, 107 insertions(+), 22 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 4428f614d3dea136cee40f00e39878126d02b079 From git at git.haskell.org Tue Jul 12 11:23:58 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 12 Jul 2016 11:23:58 +0000 (UTC) Subject: [commit: ghc] branch 'wip/T12370' deleted Message-ID: <20160712112358.438C63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Deleted branch: wip/T12370 From git at git.haskell.org Tue Jul 12 11:24:01 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 12 Jul 2016 11:24:01 +0000 (UTC) Subject: [commit: ghc] master: Demand analyser: Implement LetUp rule (#12370) (45d8f4e) Message-ID: <20160712112401.B797F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/45d8f4eb2bf2fcb103517d064e7ba1e491a66f4c/ghc >--------------------------------------------------------------- commit 45d8f4eb2bf2fcb103517d064e7ba1e491a66f4c Author: Joachim Breitner Date: Wed Jul 6 15:44:18 2016 +0200 Demand analyser: Implement LetUp rule (#12370) This makes the implementation match the description in the paper more closely: There, a let binding that is not a function has first its body analised, and then the binding’s RHS. This way, the demand on the bound variable by the body can be fed into the RHS, yielding more precise results. Performance measurements do unfortunately not show significant improvements or regessions. Differential Revision: https://phabricator.haskell.org/D2395 >--------------------------------------------------------------- 45d8f4eb2bf2fcb103517d064e7ba1e491a66f4c compiler/stranal/DmdAnal.hs | 100 ++++++++++++++++----- .../simplCore/should_compile/spec-inline.stderr | 2 +- testsuite/tests/stranal/sigs/T12370.hs | 12 +++ testsuite/tests/stranal/sigs/T12370.stderr | 14 +++ testsuite/tests/stranal/sigs/all.T | 1 + 5 files changed, 107 insertions(+), 22 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 45d8f4eb2bf2fcb103517d064e7ba1e491a66f4c From git at git.haskell.org Tue Jul 12 14:50:42 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 12 Jul 2016 14:50:42 +0000 (UTC) Subject: [commit: ghc] branch 'wip/T12382' created Message-ID: <20160712145042.BDED33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/T12382 Referencing: 1162fc4dd3e8f1845cf2beb1bcf2e01c6e5ebfdc From git at git.haskell.org Tue Jul 12 14:50:45 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 12 Jul 2016 14:50:45 +0000 (UTC) Subject: [commit: ghc] wip/T12382: tidyType: Rename variables of nested forall at once (1162fc4) Message-ID: <20160712145045.7475B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T12382 Link : http://ghc.haskell.org/trac/ghc/changeset/1162fc4dd3e8f1845cf2beb1bcf2e01c6e5ebfdc/ghc >--------------------------------------------------------------- commit 1162fc4dd3e8f1845cf2beb1bcf2e01c6e5ebfdc Author: Joachim Breitner Date: Tue Jul 12 16:52:42 2016 +0200 tidyType: Rename variables of nested forall at once this refactoring commit prepares for fixing #12382, which can now be implemented soley in `tidyOccNames`. >--------------------------------------------------------------- 1162fc4dd3e8f1845cf2beb1bcf2e01c6e5ebfdc compiler/basicTypes/OccName.hs | 6 +++++- compiler/types/TyCoRep.hs | 46 +++++++++++++++++++++++++++++++++--------- 2 files changed, 42 insertions(+), 10 deletions(-) diff --git a/compiler/basicTypes/OccName.hs b/compiler/basicTypes/OccName.hs index 65195ab..c17bd06 100644 --- a/compiler/basicTypes/OccName.hs +++ b/compiler/basicTypes/OccName.hs @@ -98,7 +98,7 @@ module OccName ( filterOccSet, -- * Tidying up - TidyOccEnv, emptyTidyOccEnv, tidyOccName, initTidyOccEnv, + TidyOccEnv, emptyTidyOccEnv, tidyOccNames, tidyOccName, initTidyOccEnv, -- FsEnv FastStringEnv, emptyFsEnv, lookupFsEnv, extendFsEnv, mkFsEnv @@ -114,6 +114,7 @@ import FastStringEnv import Outputable import Lexeme import Binary +import Data.List (mapAccumL) import Data.Char import Data.Data @@ -822,6 +823,9 @@ initTidyOccEnv = foldl add emptyUFM where add env (OccName _ fs) = addToUFM env fs 1 +tidyOccNames :: TidyOccEnv -> [OccName] -> (TidyOccEnv, [OccName]) +tidyOccNames env occs = mapAccumL tidyOccName env occs + tidyOccName :: TidyOccEnv -> OccName -> (TidyOccEnv, OccName) tidyOccName env occ@(OccName occ_sp fs) = case lookupUFM env fs of diff --git a/compiler/types/TyCoRep.hs b/compiler/types/TyCoRep.hs index 08ac9c9..08d1744 100644 --- a/compiler/types/TyCoRep.hs +++ b/compiler/types/TyCoRep.hs @@ -3104,17 +3104,31 @@ ppSuggestExplicitKinds -- -- It doesn't change the uniques at all, just the print names. tidyTyCoVarBndrs :: TidyEnv -> [TyCoVar] -> (TidyEnv, [TyCoVar]) -tidyTyCoVarBndrs env tvs = mapAccumL tidyTyCoVarBndr env tvs +tidyTyCoVarBndrs tidy_env@(occ_env, subst) tvs + = case tidyOccNames occ_env (map getHelpfulOccName tvs) of + (occ_env', occs') -> ((occ_env', subst'), tvs') + where + subst' = extendVarEnvList subst (zip tvs tvs') + tvs' = zipWith (updateOccName tidy_env) occs' tvs tidyTyCoVarBndr :: TidyEnv -> TyCoVar -> (TidyEnv, TyCoVar) tidyTyCoVarBndr tidy_env@(occ_env, subst) tyvar - = case tidyOccName occ_env occ1 of - (tidy', occ') -> ((tidy', subst'), tyvar') + = case tidyOccName occ_env (getHelpfulOccName tyvar) of + (occ_env', occ') -> ((occ_env', subst'), tyvar') where subst' = extendVarEnv subst tyvar tyvar' - tyvar' = setTyVarKind (setTyVarName tyvar name') kind' - name' = tidyNameOcc name occ' - kind' = tidyKind tidy_env (tyVarKind tyvar) + tyvar' = updateOccName tidy_env occ' tyvar + +updateOccName :: TidyEnv -> OccName -> TyCoVar -> TyCoVar +updateOccName tidy_env occ tyvar = tyvar' + where + name = tyVarName tyvar + tyvar' = setTyVarKind (setTyVarName tyvar name') kind' + name' = tidyNameOcc name occ + kind' = tidyKind tidy_env (tyVarKind tyvar) + +getHelpfulOccName :: TyCoVar -> OccName +getHelpfulOccName tyvar = occ1 where name = tyVarName tyvar occ = getOccName name @@ -3182,13 +3196,27 @@ tidyType env (TyConApp tycon tys) = let args = tidyTypes env tys in args `seqList` TyConApp tycon args tidyType env (AppTy fun arg) = (AppTy $! (tidyType env fun)) $! (tidyType env arg) tidyType env (FunTy fun arg) = (FunTy $! (tidyType env fun)) $! (tidyType env arg) -tidyType env (ForAllTy (TvBndr tv vis) ty) - = (ForAllTy $! ((TvBndr $! tvp) $! vis)) $! (tidyType envp ty) +tidyType env (ty@(ForAllTy{})) = mkForAllTys' (zip tvs' vis) $! tidyType env' body_ty where - (envp, tvp) = tidyTyCoVarBndr env tv + (tvs, vis, body_ty) = splitForAllTys' ty + (env', tvs') = tidyTyCoVarBndrs env tvs tidyType env (CastTy ty co) = (CastTy $! tidyType env ty) $! (tidyCo env co) tidyType env (CoercionTy co) = CoercionTy $! (tidyCo env co) + +-- The following two functions differ from mkForAllTys and splitForAllTys in that +-- they expect/preserve the ArgFlag argument. Thes belong to types/Type.hs, but +-- how should they be named? +mkForAllTys' :: [(TyVar, ArgFlag)] -> Type -> Type +mkForAllTys' tvvs ty = foldr (\(tv, vis) -> ForAllTy (TvBndr tv vis)) ty tvvs + +splitForAllTys' :: Type -> ([TyVar], [ArgFlag], Type) +splitForAllTys' ty = go ty [] [] + where + go (ForAllTy (TvBndr tv vis) ty) tvs viss = go ty (tv:tvs) (vis:viss) + go ty tvs viss = (reverse tvs, reverse viss, ty) + + --------------- -- | Grabs the free type variables, tidies them -- and then uses 'tidyType' to work over the type itself From git at git.haskell.org Tue Jul 12 15:02:46 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 12 Jul 2016 15:02:46 +0000 (UTC) Subject: [commit: ghc] wip/binary-bytestring: Binary: Fix incorrect name in comment (48af747) Message-ID: <20160712150246.C5BE43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/binary-bytestring Link : http://ghc.haskell.org/trac/ghc/changeset/48af7474fb2bbea46404cd64e84e172f593dc33c/ghc >--------------------------------------------------------------- commit 48af7474fb2bbea46404cd64e84e172f593dc33c Author: Ben Gamari Date: Mon Jul 11 18:43:08 2016 +0200 Binary: Fix incorrect name in comment >--------------------------------------------------------------- 48af7474fb2bbea46404cd64e84e172f593dc33c compiler/utils/Binary.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/utils/Binary.hs b/compiler/utils/Binary.hs index 640c529..9f7c03d 100644 --- a/compiler/utils/Binary.hs +++ b/compiler/utils/Binary.hs @@ -664,7 +664,7 @@ getDictionary bh = do -- The Symbol Table --------------------------------------------------------- --- On disk, the symbol table is an array of IfaceExtName, when +-- On disk, the symbol table is an array of IfExtName, when -- reading it in we turn it into a SymbolTable. type SymbolTable = Array Int Name From git at git.haskell.org Tue Jul 12 15:02:49 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 12 Jul 2016 15:02:49 +0000 (UTC) Subject: [commit: ghc] wip/binary-bytestring: Binary: Use ByteString's copy in getBS (f6c257b) Message-ID: <20160712150249.8AF1E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/binary-bytestring Link : http://ghc.haskell.org/trac/ghc/changeset/f6c257bf7c0f6aeef77db5e27d533f6175b05dab/ghc >--------------------------------------------------------------- commit f6c257bf7c0f6aeef77db5e27d533f6175b05dab Author: Ben Gamari Date: Sun Jul 10 16:19:04 2016 +0200 Binary: Use ByteString's copy in getBS It's unclear how much of an effect on runtime this will have, but if nothing else it's simpler. >--------------------------------------------------------------- f6c257bf7c0f6aeef77db5e27d533f6175b05dab compiler/utils/Binary.hs | 29 +++++++++++------------------ 1 file changed, 11 insertions(+), 18 deletions(-) diff --git a/compiler/utils/Binary.hs b/compiler/utils/Binary.hs index 9f8d926..640c529 100644 --- a/compiler/utils/Binary.hs +++ b/compiler/utils/Binary.hs @@ -70,7 +70,7 @@ import SrcLoc import Foreign import Data.Array import Data.ByteString (ByteString) -import qualified Data.ByteString.Internal as BS +import qualified Data.ByteString as BS import qualified Data.ByteString.Unsafe as BS import Data.IORef import Data.Char ( ord, chr ) @@ -692,25 +692,18 @@ putBS bh bs = go (n+1) go 0 -{- -- possible faster version, not quite there yet: -getBS bh at BinMem{} = do - (I# l) <- get bh - arr <- readIORef (arr_r bh) - off <- readFastMutInt (off_r bh) - return $! (mkFastSubBytesBA# arr off l) --} getBS :: BinHandle -> IO ByteString getBS bh = do - l <- get bh - fp <- mallocForeignPtrBytes l - withForeignPtr fp $ \ptr -> do - let go n | n == l = return $ BS.fromForeignPtr fp 0 l - | otherwise = do - b <- getByte bh - pokeElemOff ptr n b - go (n+1) - -- - go 0 + l <- get bh :: IO Int + arr <- readIORef (_arr_r bh) + sz <- readFastMutInt (_sz_r bh) + off <- readFastMutInt (_off_r bh) + when (off + l > sz) $ + ioError (mkIOError eofErrorType "Data.Binary.getBS" Nothing Nothing) + writeFastMutInt (_off_r bh) (off+l) + withForeignPtr arr $ \ptr -> do + bs <- BS.unsafePackCStringLen (castPtr $ ptr `plusPtr` off, fromIntegral l) + return $! BS.copy bs instance Binary ByteString where put_ bh f = putBS bh f From git at git.haskell.org Tue Jul 12 15:02:52 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 12 Jul 2016 15:02:52 +0000 (UTC) Subject: [commit: ghc] wip/binary-bytestring's head updated: Binary: Fix incorrect name in comment (48af747) Message-ID: <20160712150252.201FC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/binary-bytestring' now includes: 9a3df1f check-api-annotations utility loads by filename 17d0b84 Add -package-env to the flags reference 372dbc4 Pretty: delete really old changelog f6c257b Binary: Use ByteString's copy in getBS 48af747 Binary: Fix incorrect name in comment From git at git.haskell.org Tue Jul 12 15:18:34 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 12 Jul 2016 15:18:34 +0000 (UTC) Subject: [commit: ghc] wip/T12382: tidyOccNames: Rename variables fairly (86ad1d6) Message-ID: <20160712151834.897873A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T12382 Link : http://ghc.haskell.org/trac/ghc/changeset/86ad1d649e57da4aa2447164395de813ee39816c/ghc >--------------------------------------------------------------- commit 86ad1d649e57da4aa2447164395de813ee39816c Author: Joachim Breitner Date: Tue Jul 12 17:21:07 2016 +0200 tidyOccNames: Rename variables fairly So that > :t (id,id,id) produces (id,id,id) :: (a3 -> a3, a2 -> a2, a1 -> a1) instead of (id,id,id) :: (a2 -> a2, a1 -> a1, a -> a) >--------------------------------------------------------------- 86ad1d649e57da4aa2447164395de813ee39816c compiler/basicTypes/OccName.hs | 46 ++++++++++++++++++++++++++++++++++++------ 1 file changed, 40 insertions(+), 6 deletions(-) diff --git a/compiler/basicTypes/OccName.hs b/compiler/basicTypes/OccName.hs index c17bd06..f41355e 100644 --- a/compiler/basicTypes/OccName.hs +++ b/compiler/basicTypes/OccName.hs @@ -810,6 +810,29 @@ So we use the TidyOccEnv mapping for "a" (not "a7" or "a8") as our base for starting the search; and we make sure to update the starting point for "a" after we allocate a new one. + +Node [Tidying multiple names at once] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + +Consider + + > :t (id,id,id) + +Every id contributes a type variable to the type signature, and all of them are +"a". If we tidy them one by one, we get + + (id,id,id) :: (a2 -> a2, a1 -> a1, a -> a) + +which is a bit unfortunate, as it unfairly renames only one of them. What we +would like to see is + + (id,id,id) :: (a3 -> a3, a2 -> a2, a1 -> a1) + +This is achieved in tidyOccNames. It still uses tidyOccName to rename each name +on its own, but it prepares the TidyEnv (using addDups), by “blocking” every +name that occurs twice in the map. This way, none of the "a"s will get the priviledge of keeping this name, and all of them will get a suitable numbery by tidyOccName. +This is #12382. + -} type TidyOccEnv = UniqFM Int -- The in-scope OccNames @@ -823,16 +846,27 @@ initTidyOccEnv = foldl add emptyUFM where add env (OccName _ fs) = addToUFM env fs 1 +-- see Note [Tidying multiple names at once] tidyOccNames :: TidyOccEnv -> [OccName] -> (TidyOccEnv, [OccName]) -tidyOccNames env occs = mapAccumL tidyOccName env occs +tidyOccNames env occs = mapAccumL tidyOccName env' occs + where + env' = addDups env emptyUFM occs + +addDups :: TidyOccEnv -> UniqFM () -> [OccName] -> TidyOccEnv +addDups env _ [] = env +addDups env seenOnce ((OccName _ fs):occs) + | fs `elemUFM` env = addDups env seenOnce occs + | fs `elemUFM` seenOnce = addDups (addToUFM env fs 1) seenOnce occs + | otherwise = addDups env (addToUFM seenOnce fs ()) occs tidyOccName :: TidyOccEnv -> OccName -> (TidyOccEnv, OccName) tidyOccName env occ@(OccName occ_sp fs) - = case lookupUFM env fs of - Nothing -> (addToUFM env fs 1, occ) -- Desired OccName is free - Just {} -> case lookupUFM env base1 of - Nothing -> (addToUFM env base1 2, OccName occ_sp base1) - Just n -> find 1 n + | not (fs `elemUFM` env) + = (addToUFM env fs 1, occ) -- Desired OccName is free + | otherwise + = case lookupUFM env base1 of + Nothing -> (addToUFM env base1 2, OccName occ_sp base1) + Just n -> find 1 n where base :: String -- Drop trailing digits (see Note [TidyOccEnv]) base = dropWhileEndLE isDigit (unpackFS fs) From git at git.haskell.org Tue Jul 12 15:23:35 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 12 Jul 2016 15:23:35 +0000 (UTC) Subject: [commit: ghc] branch 'wip/occname' created Message-ID: <20160712152335.EE26F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/occname Referencing: e13f37aef116eca7cb0548abbf7b8fdce7650c79 From git at git.haskell.org Tue Jul 12 15:23:38 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 12 Jul 2016 15:23:38 +0000 (UTC) Subject: [commit: ghc] wip/occname: TysWiredIn: Switch back to parsing tuple names (23649dd) Message-ID: <20160712152338.CC15F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/occname Link : http://ghc.haskell.org/trac/ghc/changeset/23649dd8a68f8ead0688f794d5d1d82219adad95/ghc >--------------------------------------------------------------- commit 23649dd8a68f8ead0688f794d5d1d82219adad95 Author: Ben Gamari Date: Mon Jul 11 21:20:59 2016 +0200 TysWiredIn: Switch back to parsing tuple names >--------------------------------------------------------------- 23649dd8a68f8ead0688f794d5d1d82219adad95 compiler/prelude/TysWiredIn.hs | 51 ++++++++++++++++++++++-------------------- 1 file changed, 27 insertions(+), 24 deletions(-) diff --git a/compiler/prelude/TysWiredIn.hs b/compiler/prelude/TysWiredIn.hs index 8465cd9..65abdd8 100644 --- a/compiler/prelude/TysWiredIn.hs +++ b/compiler/prelude/TysWiredIn.hs @@ -5,6 +5,7 @@ -} {-# LANGUAGE CPP #-} +{-# LANGUAGE OverloadedStrings #-} -- | This module is about types that can be defined in Haskell, but which -- must be wired into the compiler nonetheless. C.f module TysPrim @@ -134,7 +135,6 @@ import {-# SOURCE #-} ConLike import TyCon import Class ( Class, mkClass ) import RdrName -import UniqFM import Name import NameSet ( NameSet, mkNameSet, elemNameSet ) import BasicTypes ( Arity, Boxity(..), @@ -148,6 +148,8 @@ import Outputable import Util import BooleanFormula ( mkAnd ) +import qualified Data.ByteString.Char8 as BS + alpha_tyvar :: [TyVar] alpha_tyvar = [alphaTyVar] @@ -181,8 +183,7 @@ names in PrelNames, so they use wTcQual, wDataQual, etc -- define here. -- -- Because of their infinite nature, this list excludes tuples, Any and implicit --- parameter TyCons. Instead, we have a hack in lookupOrigNameCache to deal with --- these names. +-- parameter TyCons (see Note [Built-in syntax and the OrigNameCache]). -- -- See also Note [Known-key names] wiredInTyCons :: [TyCon] @@ -636,19 +637,30 @@ decl in GHC.Classes, so I think this part may not work properly. But it's unused I think. -} -builtInOccNames :: UniqFM (OccName -> Name) -builtInOccNames = listToUFM $ - [ (fsLit "[]", choose_ns listTyConName nilDataConName) - , (fsLit ":" , const consDataConName) - , (fsLit "[::]", const parrTyConName) - , (fsLit "()", tup_name Boxed 0) - , (fsLit "(##)", tup_name Unboxed 0) - ] ++ - [ (fsLit $ "("++replicate n ','++")", tup_name Boxed (n+1)) | n <- [1..62] ] ++ - [ (fsLit $ "(#"++replicate n ','++"#)", tup_name Unboxed (n+1)) | n <- [1..62] ] +isBuiltInOcc_maybe :: OccName -> Maybe Name +-- Built in syntax isn't "in scope" so these OccNames +-- map to wired-in Names with BuiltInSyntax +isBuiltInOcc_maybe occ = + case name of + "[]" -> Just $ choose_ns listTyConName nilDataConName + ":" -> Just consDataConName + "[::]" -> Just parrTyConName + "()" -> Just $ tup_name Boxed 0 + "(##)" -> Just $ tup_name Unboxed 0 + _ | Just rest <- name `BS.stripPrefix` "(" + , (commas, rest') <- BS.span (==',') rest + , ")" <- rest' + -> Just $ tup_name Boxed (1+BS.length commas) + _ | Just rest <- name `BS.stripPrefix` "(#" + , (commas, rest') <- BS.span (==',') rest + , "#)" <- rest' + -> Just $ tup_name Unboxed (1+BS.length commas) + _ -> Nothing where - choose_ns :: Name -> Name -> OccName -> Name - choose_ns tc dc occ + name = fastStringToByteString $ occNameFS occ + + choose_ns :: Name -> Name -> Name + choose_ns tc dc | isTcClsNameSpace ns = tc | isDataConNameSpace ns = dc | otherwise = pprPanic "tup_name" (ppr occ) @@ -658,15 +670,6 @@ builtInOccNames = listToUFM $ = choose_ns (getName (tupleTyCon boxity arity)) (getName (tupleDataCon boxity arity)) - -isBuiltInOcc_maybe :: OccName -> Maybe Name --- Built in syntax isn't "in scope" so these OccNames --- map to wired-in Names with BuiltInSyntax -isBuiltInOcc_maybe occ - = case lookupUFM builtInOccNames (occNameFS occ) of - Just f -> Just (f occ) - Nothing -> Nothing - mkTupleOcc :: NameSpace -> Boxity -> Arity -> OccName -- No need to cache these, the caching is done in mk_tuple mkTupleOcc ns Boxed ar = mkOccName ns (mkBoxedTupleStr ar) From git at git.haskell.org Tue Jul 12 15:23:41 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 12 Jul 2016 15:23:41 +0000 (UTC) Subject: [commit: ghc] wip/occname: IfaceEnv: Only check for built-in OccNames if mod is GHC.Types (f4de155) Message-ID: <20160712152341.904203A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/occname Link : http://ghc.haskell.org/trac/ghc/changeset/f4de1552d6455d53fba89cde3b67e2307ecc82cc/ghc >--------------------------------------------------------------- commit f4de1552d6455d53fba89cde3b67e2307ecc82cc Author: Ben Gamari Date: Mon Jul 11 18:41:40 2016 +0200 IfaceEnv: Only check for built-in OccNames if mod is GHC.Types This check is not entirely cheap and will not succeed unless we are looking for something in the module where built-in syntax lives, GHC.Types. >--------------------------------------------------------------- f4de1552d6455d53fba89cde3b67e2307ecc82cc compiler/iface/IfaceEnv.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/compiler/iface/IfaceEnv.hs b/compiler/iface/IfaceEnv.hs index 0c8d8e9..b70c8e9 100644 --- a/compiler/iface/IfaceEnv.hs +++ b/compiler/iface/IfaceEnv.hs @@ -33,6 +33,7 @@ import Module import FastString import FastStringEnv import IfaceType +import PrelNames ( gHC_TYPES ) import UniqSupply import SrcLoc import Util @@ -203,7 +204,8 @@ However, there are two reasons why we might look up an Orig RdrName: lookupOrigNameCache :: OrigNameCache -> Module -> OccName -> Maybe Name lookupOrigNameCache nc mod occ - | Just name <- isBuiltInOcc_maybe occ + | mod == gHC_TYPES + , Just name <- isBuiltInOcc_maybe occ = -- See Note [Known-key names], 3(c) in PrelNames -- Special case for tuples; there are too many -- of them to pre-populate the original-name cache From git at git.haskell.org Tue Jul 12 15:23:44 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 12 Jul 2016 15:23:44 +0000 (UTC) Subject: [commit: ghc] wip/occname: Wiring in tuples note (e13f37a) Message-ID: <20160712152344.467853A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/occname Link : http://ghc.haskell.org/trac/ghc/changeset/e13f37aef116eca7cb0548abbf7b8fdce7650c79/ghc >--------------------------------------------------------------- commit e13f37aef116eca7cb0548abbf7b8fdce7650c79 Author: Ben Gamari Date: Tue Jul 12 00:12:52 2016 +0200 Wiring in tuples note This should probably just be folded in to the note above >--------------------------------------------------------------- e13f37aef116eca7cb0548abbf7b8fdce7650c79 compiler/iface/IfaceEnv.hs | 10 ++++++++++ 1 file changed, 10 insertions(+) diff --git a/compiler/iface/IfaceEnv.hs b/compiler/iface/IfaceEnv.hs index b70c8e9..d4aa03b 100644 --- a/compiler/iface/IfaceEnv.hs +++ b/compiler/iface/IfaceEnv.hs @@ -202,6 +202,16 @@ However, there are two reasons why we might look up an Orig RdrName: go this route (Trac #8954). -} +{- +Note [Wiring in tuples] +~~~~~~~~~~~~~~~~~~~~~~~ + +The wiring-in of the tuple types is a bit tricky. The reason is that there are +very many of them and we consequently want to avoid cluttering the name cache +with them unnecessarily. For this reason we specially encode tuple Names in +interface files, +-} + lookupOrigNameCache :: OrigNameCache -> Module -> OccName -> Maybe Name lookupOrigNameCache nc mod occ | mod == gHC_TYPES From git at git.haskell.org Tue Jul 12 15:23:47 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 12 Jul 2016 15:23:47 +0000 (UTC) Subject: [commit: ghc] wip/occname: TysWiredIn: Notes (45a2505) Message-ID: <20160712152347.0FB6E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/occname Link : http://ghc.haskell.org/trac/ghc/changeset/45a25050ecfa44d6784d449ebdce532d9a39d63e/ghc >--------------------------------------------------------------- commit 45a25050ecfa44d6784d449ebdce532d9a39d63e Author: Ben Gamari Date: Tue Jul 12 00:12:45 2016 +0200 TysWiredIn: Notes >--------------------------------------------------------------- 45a25050ecfa44d6784d449ebdce532d9a39d63e compiler/prelude/TysWiredIn.hs | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/compiler/prelude/TysWiredIn.hs b/compiler/prelude/TysWiredIn.hs index 65abdd8..609234f 100644 --- a/compiler/prelude/TysWiredIn.hs +++ b/compiler/prelude/TysWiredIn.hs @@ -637,9 +637,12 @@ decl in GHC.Classes, so I think this part may not work properly. But it's unused I think. -} +-- | Built in syntax isn't "in scope" so these OccNames map to wired-in Names +-- with BuiltInSyntax. However, this should only be necessary while resolving +-- names produced by Template Haskell splices since we take care to encode +-- built-in syntax names specially in interface files. See +-- Note [Symbol table representation of names]. isBuiltInOcc_maybe :: OccName -> Maybe Name --- Built in syntax isn't "in scope" so these OccNames --- map to wired-in Names with BuiltInSyntax isBuiltInOcc_maybe occ = case name of "[]" -> Just $ choose_ns listTyConName nilDataConName From git at git.haskell.org Wed Jul 13 08:54:58 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 13 Jul 2016 08:54:58 +0000 (UTC) Subject: [commit: ghc] wip/T12382: tidyType: Rename variables of nested forall at once (99f69e5) Message-ID: <20160713085458.396B83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T12382 Link : http://ghc.haskell.org/trac/ghc/changeset/99f69e5e228febbad67c0fe6bcb84e17afe758c5/ghc >--------------------------------------------------------------- commit 99f69e5e228febbad67c0fe6bcb84e17afe758c5 Author: Joachim Breitner Date: Tue Jul 12 16:52:42 2016 +0200 tidyType: Rename variables of nested forall at once this refactoring commit prepares for fixing #12382, which can now be implemented soley in tidyTyCoVarBndrs. >--------------------------------------------------------------- 99f69e5e228febbad67c0fe6bcb84e17afe758c5 compiler/basicTypes/OccName.hs | 6 +++++- compiler/types/TyCoRep.hs | 34 +++++++++++++++++++++++++++------- 2 files changed, 32 insertions(+), 8 deletions(-) diff --git a/compiler/basicTypes/OccName.hs b/compiler/basicTypes/OccName.hs index 65195ab..c17bd06 100644 --- a/compiler/basicTypes/OccName.hs +++ b/compiler/basicTypes/OccName.hs @@ -98,7 +98,7 @@ module OccName ( filterOccSet, -- * Tidying up - TidyOccEnv, emptyTidyOccEnv, tidyOccName, initTidyOccEnv, + TidyOccEnv, emptyTidyOccEnv, tidyOccNames, tidyOccName, initTidyOccEnv, -- FsEnv FastStringEnv, emptyFsEnv, lookupFsEnv, extendFsEnv, mkFsEnv @@ -114,6 +114,7 @@ import FastStringEnv import Outputable import Lexeme import Binary +import Data.List (mapAccumL) import Data.Char import Data.Data @@ -822,6 +823,9 @@ initTidyOccEnv = foldl add emptyUFM where add env (OccName _ fs) = addToUFM env fs 1 +tidyOccNames :: TidyOccEnv -> [OccName] -> (TidyOccEnv, [OccName]) +tidyOccNames env occs = mapAccumL tidyOccName env occs + tidyOccName :: TidyOccEnv -> OccName -> (TidyOccEnv, OccName) tidyOccName env occ@(OccName occ_sp fs) = case lookupUFM env fs of diff --git a/compiler/types/TyCoRep.hs b/compiler/types/TyCoRep.hs index 08ac9c9..ab07f33 100644 --- a/compiler/types/TyCoRep.hs +++ b/compiler/types/TyCoRep.hs @@ -3104,17 +3104,21 @@ ppSuggestExplicitKinds -- -- It doesn't change the uniques at all, just the print names. tidyTyCoVarBndrs :: TidyEnv -> [TyCoVar] -> (TidyEnv, [TyCoVar]) -tidyTyCoVarBndrs env tvs = mapAccumL tidyTyCoVarBndr env tvs +tidyTyCoVarBndrs tidy_env tvs = mapAccumL tidyTyCoVarBndr tidy_env tvs tidyTyCoVarBndr :: TidyEnv -> TyCoVar -> (TidyEnv, TyCoVar) tidyTyCoVarBndr tidy_env@(occ_env, subst) tyvar - = case tidyOccName occ_env occ1 of - (tidy', occ') -> ((tidy', subst'), tyvar') + = case tidyOccName occ_env (getHelpfulOccName tyvar) of + (occ_env', occ') -> ((occ_env', subst'), tyvar') where subst' = extendVarEnv subst tyvar tyvar' tyvar' = setTyVarKind (setTyVarName tyvar name') kind' - name' = tidyNameOcc name occ' kind' = tidyKind tidy_env (tyVarKind tyvar) + name' = tidyNameOcc name occ' + name = tyVarName tyvar + +getHelpfulOccName :: TyCoVar -> OccName +getHelpfulOccName tyvar = occ1 where name = tyVarName tyvar occ = getOccName name @@ -3182,13 +3186,29 @@ tidyType env (TyConApp tycon tys) = let args = tidyTypes env tys in args `seqList` TyConApp tycon args tidyType env (AppTy fun arg) = (AppTy $! (tidyType env fun)) $! (tidyType env arg) tidyType env (FunTy fun arg) = (FunTy $! (tidyType env fun)) $! (tidyType env arg) -tidyType env (ForAllTy (TvBndr tv vis) ty) - = (ForAllTy $! ((TvBndr $! tvp) $! vis)) $! (tidyType envp ty) +tidyType env (ty@(ForAllTy{})) = mkForAllTys' (zip tvs' vis) $! tidyType env' body_ty where - (envp, tvp) = tidyTyCoVarBndr env tv + (tvs, vis, body_ty) = splitForAllTys' ty + (env', tvs') = tidyTyCoVarBndrs env tvs tidyType env (CastTy ty co) = (CastTy $! tidyType env ty) $! (tidyCo env co) tidyType env (CoercionTy co) = CoercionTy $! (tidyCo env co) + +-- The following two functions differ from mkForAllTys and splitForAllTys in that +-- they expect/preserve the ArgFlag argument. Thes belong to types/Type.hs, but +-- how should they be named? +mkForAllTys' :: [(TyVar, ArgFlag)] -> Type -> Type +mkForAllTys' tvvs ty = foldr strictMkForAllTy ty tvvs + where + strictMkForAllTy (tv,vis) ty = (ForAllTy $! ((TvBndr $! tv) $! vis)) $! ty + +splitForAllTys' :: Type -> ([TyVar], [ArgFlag], Type) +splitForAllTys' ty = go ty [] [] + where + go (ForAllTy (TvBndr tv vis) ty) tvs viss = go ty (tv:tvs) (vis:viss) + go ty tvs viss = (reverse tvs, reverse viss, ty) + + --------------- -- | Grabs the free type variables, tidies them -- and then uses 'tidyType' to work over the type itself From git at git.haskell.org Wed Jul 13 08:55:00 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 13 Jul 2016 08:55:00 +0000 (UTC) Subject: [commit: ghc] wip/T12382: tidyOccNames: Rename variables fairly (a078901) Message-ID: <20160713085500.E984E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T12382 Link : http://ghc.haskell.org/trac/ghc/changeset/a0789017484dccc534908c60355fd681f7674fac/ghc >--------------------------------------------------------------- commit a0789017484dccc534908c60355fd681f7674fac Author: Joachim Breitner Date: Tue Jul 12 17:21:07 2016 +0200 tidyOccNames: Rename variables fairly So that > :t (id,id,id) produces (id,id,id) :: (a3 -> a3, a2 -> a2, a1 -> a1) instead of (id,id,id) :: (a2 -> a2, a1 -> a1, a -> a) >--------------------------------------------------------------- a0789017484dccc534908c60355fd681f7674fac compiler/basicTypes/OccName.hs | 59 +++++++++++++++++++--- compiler/types/TyCoRep.hs | 10 +++- testsuite/tests/ado/ado004.stderr | 14 ++--- testsuite/tests/driver/werror.stderr | 2 +- testsuite/tests/ghci/scripts/T6018ghcifail.stderr | 2 +- testsuite/tests/ghci/scripts/T7587.stdout | 2 +- testsuite/tests/ghci/scripts/T7730.stdout | 2 +- testsuite/tests/ghci/scripts/ghci013.stdout | 2 +- .../partial-sigs/should_compile/Uncurry.stderr | 2 +- .../tests/typecheck/should_compile/tc168.stderr | 2 +- .../tests/typecheck/should_fail/T6018fail.stderr | 2 +- .../typecheck/should_fail/T6018failclosed.stderr | 4 +- 12 files changed, 78 insertions(+), 25 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc a0789017484dccc534908c60355fd681f7674fac From git at git.haskell.org Wed Jul 13 09:38:19 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 13 Jul 2016 09:38:19 +0000 (UTC) Subject: [commit: ghc] wip/T12382: tidyOccNames: Rename variables fairly (ea8023e) Message-ID: <20160713093819.487103A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T12382 Link : http://ghc.haskell.org/trac/ghc/changeset/ea8023e7dd1982e7359e8e1c4d9af34e54e2ee7e/ghc >--------------------------------------------------------------- commit ea8023e7dd1982e7359e8e1c4d9af34e54e2ee7e Author: Joachim Breitner Date: Tue Jul 12 17:21:07 2016 +0200 tidyOccNames: Rename variables fairly So that > :t (id,id,id) produces (id,id,id) :: (a3 -> a3, a2 -> a2, a1 -> a1) instead of (id,id,id) :: (a2 -> a2, a1 -> a1, a -> a) >--------------------------------------------------------------- ea8023e7dd1982e7359e8e1c4d9af34e54e2ee7e compiler/basicTypes/OccName.hs | 59 +++++++++++++++++++--- compiler/types/TyCoRep.hs | 10 +++- testsuite/tests/ado/ado004.stderr | 14 ++--- testsuite/tests/driver/werror.stderr | 2 +- testsuite/tests/ghci/scripts/T6018ghcifail.stderr | 2 +- testsuite/tests/ghci/scripts/T7587.stdout | 2 +- testsuite/tests/ghci/scripts/T7730.stdout | 2 +- testsuite/tests/ghci/scripts/ghci013.stdout | 2 +- .../partial-sigs/should_compile/Uncurry.stderr | 2 +- .../tests/typecheck/should_compile/tc168.stderr | 2 +- .../tests/typecheck/should_fail/T6018fail.stderr | 2 +- .../typecheck/should_fail/T6018failclosed.stderr | 4 +- 12 files changed, 78 insertions(+), 25 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc ea8023e7dd1982e7359e8e1c4d9af34e54e2ee7e From git at git.haskell.org Wed Jul 13 09:41:30 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 13 Jul 2016 09:41:30 +0000 (UTC) Subject: [commit: ghc] wip/T12382: tidyOccNames: Rename variables fairly (ef48eed) Message-ID: <20160713094130.4BB953A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T12382 Link : http://ghc.haskell.org/trac/ghc/changeset/ef48eedb9b366afd3a40e42e5a9e9112b881d5b0/ghc >--------------------------------------------------------------- commit ef48eedb9b366afd3a40e42e5a9e9112b881d5b0 Author: Joachim Breitner Date: Tue Jul 12 17:21:07 2016 +0200 tidyOccNames: Rename variables fairly So that > :t (id,id,id) produces (id,id,id) :: (a3 -> a3, a2 -> a2, a1 -> a1) instead of (id,id,id) :: (a2 -> a2, a1 -> a1, a -> a) >--------------------------------------------------------------- ef48eedb9b366afd3a40e42e5a9e9112b881d5b0 compiler/basicTypes/OccName.hs | 59 +++++++++++++++++++--- compiler/types/TyCoRep.hs | 10 +++- testsuite/tests/ado/ado004.stderr | 14 ++--- testsuite/tests/driver/werror.stderr | 2 +- testsuite/tests/ghci/scripts/T6018ghcifail.stderr | 2 +- testsuite/tests/ghci/scripts/T7587.stdout | 2 +- testsuite/tests/ghci/scripts/T7730.stdout | 2 +- testsuite/tests/ghci/scripts/ghci013.stdout | 2 +- .../partial-sigs/should_compile/Uncurry.stderr | 2 +- .../tests/typecheck/should_compile/tc168.stderr | 2 +- .../tests/typecheck/should_fail/T6018fail.stderr | 2 +- .../typecheck/should_fail/T6018failclosed.stderr | 4 +- 12 files changed, 78 insertions(+), 25 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc ef48eedb9b366afd3a40e42e5a9e9112b881d5b0 From git at git.haskell.org Wed Jul 13 09:41:32 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 13 Jul 2016 09:41:32 +0000 (UTC) Subject: [commit: ghc] wip/T12382: tidyType: Rename variables of nested forall at once (18ac80f) Message-ID: <20160713094132.E93483A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T12382 Link : http://ghc.haskell.org/trac/ghc/changeset/18ac80ff729eb19ec370ead9f9275b3bc32c1f81/ghc >--------------------------------------------------------------- commit 18ac80ff729eb19ec370ead9f9275b3bc32c1f81 Author: Joachim Breitner Date: Tue Jul 12 16:52:42 2016 +0200 tidyType: Rename variables of nested forall at once this refactoring commit prepares for fixing #12382, which can now be implemented soley in tidyTyCoVarBndrs. >--------------------------------------------------------------- 18ac80ff729eb19ec370ead9f9275b3bc32c1f81 compiler/basicTypes/OccName.hs | 6 +++++- compiler/types/TyCoRep.hs | 34 +++++++++++++++++++++++++++------- testsuite/tests/perf/space_leaks/all.T | 2 ++ 3 files changed, 34 insertions(+), 8 deletions(-) diff --git a/compiler/basicTypes/OccName.hs b/compiler/basicTypes/OccName.hs index 65195ab..c17bd06 100644 --- a/compiler/basicTypes/OccName.hs +++ b/compiler/basicTypes/OccName.hs @@ -98,7 +98,7 @@ module OccName ( filterOccSet, -- * Tidying up - TidyOccEnv, emptyTidyOccEnv, tidyOccName, initTidyOccEnv, + TidyOccEnv, emptyTidyOccEnv, tidyOccNames, tidyOccName, initTidyOccEnv, -- FsEnv FastStringEnv, emptyFsEnv, lookupFsEnv, extendFsEnv, mkFsEnv @@ -114,6 +114,7 @@ import FastStringEnv import Outputable import Lexeme import Binary +import Data.List (mapAccumL) import Data.Char import Data.Data @@ -822,6 +823,9 @@ initTidyOccEnv = foldl add emptyUFM where add env (OccName _ fs) = addToUFM env fs 1 +tidyOccNames :: TidyOccEnv -> [OccName] -> (TidyOccEnv, [OccName]) +tidyOccNames env occs = mapAccumL tidyOccName env occs + tidyOccName :: TidyOccEnv -> OccName -> (TidyOccEnv, OccName) tidyOccName env occ@(OccName occ_sp fs) = case lookupUFM env fs of diff --git a/compiler/types/TyCoRep.hs b/compiler/types/TyCoRep.hs index 08ac9c9..ab07f33 100644 --- a/compiler/types/TyCoRep.hs +++ b/compiler/types/TyCoRep.hs @@ -3104,17 +3104,21 @@ ppSuggestExplicitKinds -- -- It doesn't change the uniques at all, just the print names. tidyTyCoVarBndrs :: TidyEnv -> [TyCoVar] -> (TidyEnv, [TyCoVar]) -tidyTyCoVarBndrs env tvs = mapAccumL tidyTyCoVarBndr env tvs +tidyTyCoVarBndrs tidy_env tvs = mapAccumL tidyTyCoVarBndr tidy_env tvs tidyTyCoVarBndr :: TidyEnv -> TyCoVar -> (TidyEnv, TyCoVar) tidyTyCoVarBndr tidy_env@(occ_env, subst) tyvar - = case tidyOccName occ_env occ1 of - (tidy', occ') -> ((tidy', subst'), tyvar') + = case tidyOccName occ_env (getHelpfulOccName tyvar) of + (occ_env', occ') -> ((occ_env', subst'), tyvar') where subst' = extendVarEnv subst tyvar tyvar' tyvar' = setTyVarKind (setTyVarName tyvar name') kind' - name' = tidyNameOcc name occ' kind' = tidyKind tidy_env (tyVarKind tyvar) + name' = tidyNameOcc name occ' + name = tyVarName tyvar + +getHelpfulOccName :: TyCoVar -> OccName +getHelpfulOccName tyvar = occ1 where name = tyVarName tyvar occ = getOccName name @@ -3182,13 +3186,29 @@ tidyType env (TyConApp tycon tys) = let args = tidyTypes env tys in args `seqList` TyConApp tycon args tidyType env (AppTy fun arg) = (AppTy $! (tidyType env fun)) $! (tidyType env arg) tidyType env (FunTy fun arg) = (FunTy $! (tidyType env fun)) $! (tidyType env arg) -tidyType env (ForAllTy (TvBndr tv vis) ty) - = (ForAllTy $! ((TvBndr $! tvp) $! vis)) $! (tidyType envp ty) +tidyType env (ty@(ForAllTy{})) = mkForAllTys' (zip tvs' vis) $! tidyType env' body_ty where - (envp, tvp) = tidyTyCoVarBndr env tv + (tvs, vis, body_ty) = splitForAllTys' ty + (env', tvs') = tidyTyCoVarBndrs env tvs tidyType env (CastTy ty co) = (CastTy $! tidyType env ty) $! (tidyCo env co) tidyType env (CoercionTy co) = CoercionTy $! (tidyCo env co) + +-- The following two functions differ from mkForAllTys and splitForAllTys in that +-- they expect/preserve the ArgFlag argument. Thes belong to types/Type.hs, but +-- how should they be named? +mkForAllTys' :: [(TyVar, ArgFlag)] -> Type -> Type +mkForAllTys' tvvs ty = foldr strictMkForAllTy ty tvvs + where + strictMkForAllTy (tv,vis) ty = (ForAllTy $! ((TvBndr $! tv) $! vis)) $! ty + +splitForAllTys' :: Type -> ([TyVar], [ArgFlag], Type) +splitForAllTys' ty = go ty [] [] + where + go (ForAllTy (TvBndr tv vis) ty) tvs viss = go ty (tv:tvs) (vis:viss) + go ty tvs viss = (reverse tvs, reverse viss, ty) + + --------------- -- | Grabs the free type variables, tidies them -- and then uses 'tidyType' to work over the type itself diff --git a/testsuite/tests/perf/space_leaks/all.T b/testsuite/tests/perf/space_leaks/all.T index e3597df..0bb21b1 100644 --- a/testsuite/tests/perf/space_leaks/all.T +++ b/testsuite/tests/perf/space_leaks/all.T @@ -60,11 +60,13 @@ test('T4029', [(wordsize(64), 82, 10)]), # 2016-02-26: 66 (amd64/Linux) INITIAL # 2016-05-23: 82 (amd64/Linux) Use -G1 + # 2016-07-13: 92 (amd64/Linux) Changes to tidyType stats_num_field('max_bytes_used', [(wordsize(64), 25247216, 5)]), # 2016-02-26: 24071720 (amd64/Linux) INITIAL # 2016-04-21: 25542832 (amd64/Linux) # 2016-05-23: 25247216 (amd64/Linux) Use -G1 + # 2016-07-13: 27575416 (amd64/Linux) Changes to tidyType extra_hc_opts('+RTS -G1 -RTS' ), ], ghci_script, From git at git.haskell.org Thu Jul 14 08:02:41 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 14 Jul 2016 08:02:41 +0000 (UTC) Subject: [commit: ghc] branch 'wip/T12382' deleted Message-ID: <20160714080241.CCDB23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Deleted branch: wip/T12382 From git at git.haskell.org Thu Jul 14 08:02:44 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 14 Jul 2016 08:02:44 +0000 (UTC) Subject: [commit: ghc] master: tidyOccNames: Rename variables fairly (cd0750e) Message-ID: <20160714080244.897883A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/cd0750ec96fba9b1683b25954092439c0f267fd7/ghc >--------------------------------------------------------------- commit cd0750ec96fba9b1683b25954092439c0f267fd7 Author: Joachim Breitner Date: Tue Jul 12 17:21:07 2016 +0200 tidyOccNames: Rename variables fairly So that > :t (id,id,id) produces (id,id,id) :: (a3 -> a3, a2 -> a2, a1 -> a1) instead of (id,id,id) :: (a2 -> a2, a1 -> a1, a -> a) Differential Revision: https://phabricator.haskell.org/D2402 >--------------------------------------------------------------- cd0750ec96fba9b1683b25954092439c0f267fd7 compiler/basicTypes/OccName.hs | 59 +++++++++++++++++++--- compiler/types/TyCoRep.hs | 10 +++- testsuite/tests/ado/ado004.stderr | 14 ++--- testsuite/tests/driver/werror.stderr | 2 +- testsuite/tests/ghci/scripts/T6018ghcifail.stderr | 2 +- testsuite/tests/ghci/scripts/T7587.stdout | 2 +- testsuite/tests/ghci/scripts/T7730.stdout | 2 +- testsuite/tests/ghci/scripts/ghci013.stdout | 2 +- .../partial-sigs/should_compile/Uncurry.stderr | 2 +- .../tests/typecheck/should_compile/tc168.stderr | 2 +- .../tests/typecheck/should_fail/T6018fail.stderr | 2 +- .../typecheck/should_fail/T6018failclosed.stderr | 4 +- 12 files changed, 78 insertions(+), 25 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc cd0750ec96fba9b1683b25954092439c0f267fd7 From git at git.haskell.org Thu Jul 14 08:02:46 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 14 Jul 2016 08:02:46 +0000 (UTC) Subject: [commit: ghc] master's head updated: tidyOccNames: Rename variables fairly (cd0750e) Message-ID: <20160714080246.D22E13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'master' now includes: 18ac80f tidyType: Rename variables of nested forall at once cd0750e tidyOccNames: Rename variables fairly From git at git.haskell.org Thu Jul 14 13:52:45 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 14 Jul 2016 13:52:45 +0000 (UTC) Subject: [commit: ghc] branch 'wip/ghc-8.0-det' created Message-ID: <20160714135245.09A103A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/ghc-8.0-det Referencing: 8ed4318af25820aca86b6a96c33ab3aedce8f32c From git at git.haskell.org Thu Jul 14 13:52:47 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 14 Jul 2016 13:52:47 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Fix two buglets in 17eb241 noticed by Richard (a027e1c) Message-ID: <20160714135247.B10BB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/a027e1c1ca5a0b4d5f27fe592c2cd22564fcf0bf/ghc >--------------------------------------------------------------- commit a027e1c1ca5a0b4d5f27fe592c2cd22564fcf0bf Author: Simon Peyton Jones Date: Wed Apr 20 15:56:44 2016 +0100 Fix two buglets in 17eb241 noticed by Richard These are corner cases in 17eb241 Refactor computing dependent type vars and I couldn't even come up with a test case * In TcSimplify.simplifyInfer, in the promotion step, be sure to promote kind variables as well as type variables. * In TcType.spiltDepVarsOfTypes, the CoercionTy case, be sure to get the free coercion variables too. >--------------------------------------------------------------- a027e1c1ca5a0b4d5f27fe592c2cd22564fcf0bf compiler/typecheck/TcSimplify.hs | 29 +++++++++++++++-------------- compiler/typecheck/TcType.hs | 7 +------ 2 files changed, 16 insertions(+), 20 deletions(-) diff --git a/compiler/typecheck/TcSimplify.hs b/compiler/typecheck/TcSimplify.hs index 70de14c..853976c 100644 --- a/compiler/typecheck/TcSimplify.hs +++ b/compiler/typecheck/TcSimplify.hs @@ -604,10 +604,10 @@ simplifyInfer rhs_tclvl apply_mr sigs name_taus wanteds -- Decide what type variables and constraints to quantify ; zonked_taus <- mapM (TcM.zonkTcType . snd) name_taus - ; let zonked_tau_tkvs = splitDepVarsOfTypes zonked_taus + ; let zonked_tau_dvs = splitDepVarsOfTypes zonked_taus ; (qtvs, bound_theta) <- decideQuantification apply_mr sigs name_taus - quant_pred_candidates zonked_tau_tkvs + quant_pred_candidates zonked_tau_dvs -- Promote any type variables that are free in the inferred type -- of the function: @@ -621,24 +621,25 @@ simplifyInfer rhs_tclvl apply_mr sigs name_taus wanteds -- we don't quantify over beta (since it is fixed by envt) -- so we must promote it! The inferred type is just -- f :: beta -> beta - ; zonked_tau_tvs <- TcM.zonkTyCoVarsAndFV (dv_tvs zonked_tau_tkvs) + ; zonked_tau_tkvs <- TcM.zonkTyCoVarsAndFV $ + dv_kvs zonked_tau_dvs `unionVarSet` dv_tvs zonked_tau_dvs -- decideQuantification turned some meta tyvars into -- quantified skolems, so we have to zonk again - ; let phi_tvs = tyCoVarsOfTypes bound_theta - `unionVarSet` zonked_tau_tvs + ; let phi_tkvs = tyCoVarsOfTypes bound_theta -- Already zonked + `unionVarSet` zonked_tau_tkvs + promote_tkvs = closeOverKinds phi_tkvs `delVarSetList` qtvs - promote_tvs = closeOverKinds phi_tvs `delVarSetList` qtvs - ; MASSERT2( closeOverKinds promote_tvs `subVarSet` promote_tvs - , ppr phi_tvs $$ - ppr (closeOverKinds phi_tvs) $$ - ppr promote_tvs $$ - ppr (closeOverKinds promote_tvs) ) + ; MASSERT2( closeOverKinds promote_tkvs `subVarSet` promote_tkvs + , ppr phi_tkvs $$ + ppr (closeOverKinds phi_tkvs) $$ + ppr promote_tkvs $$ + ppr (closeOverKinds promote_tkvs) ) -- we really don't want a type to be promoted when its kind isn't! -- promoteTyVar ignores coercion variables ; outer_tclvl <- TcM.getTcLevel - ; mapM_ (promoteTyVar outer_tclvl) (varSetElems promote_tvs) + ; mapM_ (promoteTyVar outer_tclvl) (varSetElems promote_tkvs) -- Emit an implication constraint for the -- remaining constraints from the RHS @@ -664,8 +665,8 @@ simplifyInfer rhs_tclvl apply_mr sigs name_taus wanteds ; traceTc "} simplifyInfer/produced residual implication for quantification" $ vcat [ text "quant_pred_candidates =" <+> ppr quant_pred_candidates , text "zonked_taus" <+> ppr zonked_taus - , text "zonked_tau_tvs=" <+> ppr zonked_tau_tvs - , text "promote_tvs=" <+> ppr promote_tvs + , text "zonked_tau_dvs=" <+> ppr zonked_tau_dvs + , text "promote_tvs=" <+> ppr promote_tkvs , text "bound_theta =" <+> ppr bound_theta , text "qtvs =" <+> ppr qtvs , text "implic =" <+> ppr implic ] diff --git a/compiler/typecheck/TcType.hs b/compiler/typecheck/TcType.hs index c833a9b..6ff1b85 100644 --- a/compiler/typecheck/TcType.hs +++ b/compiler/typecheck/TcType.hs @@ -929,12 +929,7 @@ split_dep_vars = go go (LitTy {}) = mempty go (CastTy ty co) = go ty `mappend` Pair (tyCoVarsOfCo co) emptyVarSet - go (CoercionTy co) = go_co co - - go_co co = let Pair ty1 ty2 = coercionKind co in - -- co :: ty1 ~ ty2 - go ty1 `mappend` go ty2 - + go (CoercionTy co) = Pair (tyCoVarsOfCo co) emptyVarSet isTouchableOrFmv ctxt_tclvl tv = ASSERT2( isTcTyVar tv, ppr tv ) From git at git.haskell.org Thu Jul 14 13:52:50 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 14 Jul 2016 13:52:50 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Refactor free tyvars on LHS of rules (8289ba7) Message-ID: <20160714135250.6E9723A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/8289ba79d95fca70113bc3343122f7b84a934d9d/ghc >--------------------------------------------------------------- commit 8289ba79d95fca70113bc3343122f7b84a934d9d Author: Simon Peyton Jones Date: Fri Apr 22 10:47:14 2016 +0100 Refactor free tyvars on LHS of rules A RULE can have unbound meta-tyvars on the LHS. Consider data T a = C foo :: T a -> Int foo C = 1 {-# RULES "myrule" foo C = 1 #-} After type checking the LHS becomes (foo alpha (C alpah)) and we do not want to zap the unbound meta-tyvar 'alpha' to Any, because that limits the applicability of the rule. Instead, we want to quantify over it! Previously there was a rather clunky implementation of this quantification, buried in the zonker in TcHsSyn (zonkTvCollecting). This patch refactors it so that the zonker just turns the meta-tyvar into a skolem, and the desugarer adds the quantification. See DsBinds Note [Free tyvars on rule LHS]. As it happened, the desugarer was already doing something similar for dictionaries. See DsBinds Note [Free dictionaries on rule LHS] No change in functionality, but less cruft. >--------------------------------------------------------------- 8289ba79d95fca70113bc3343122f7b84a934d9d compiler/deSugar/DsBinds.hs | 99 +++++++++++++++++++------------ compiler/typecheck/TcHsSyn.hs | 134 ++++++++++++++++++------------------------ 2 files changed, 121 insertions(+), 112 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 8289ba79d95fca70113bc3343122f7b84a934d9d From git at git.haskell.org Thu Jul 14 13:52:53 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 14 Jul 2016 13:52:53 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Kill unnecessary varSetElemsWellScoped in deriveTyData (1e7f7a8) Message-ID: <20160714135253.28CEE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/1e7f7a82695449e0f11b0d7142e368ea51eb6e46/ghc >--------------------------------------------------------------- commit 1e7f7a82695449e0f11b0d7142e368ea51eb6e46 Author: Bartosz Nitka Date: Wed Apr 20 08:54:10 2016 -0700 Kill unnecessary varSetElemsWellScoped in deriveTyData varSetElemsWellScoped introduces unnecessary non-determinism and it's possible to do the same thing deterministically for the same price. Test Plan: ./validate Reviewers: austin, simonmar, bgamari, simonpj Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2124 GHC Trac Issues: #4012 >--------------------------------------------------------------- 1e7f7a82695449e0f11b0d7142e368ea51eb6e46 compiler/typecheck/TcDeriv.hs | 9 ++++++--- 1 file changed, 6 insertions(+), 3 deletions(-) diff --git a/compiler/typecheck/TcDeriv.hs b/compiler/typecheck/TcDeriv.hs index 03f593c..39c9bfc 100644 --- a/compiler/typecheck/TcDeriv.hs +++ b/compiler/typecheck/TcDeriv.hs @@ -63,6 +63,7 @@ import Outputable import FastString import Bag import Pair +import FV (runFVList, unionFV, someVars) import qualified GHC.LanguageExtensions as LangExt import Control.Monad @@ -651,9 +652,11 @@ deriveTyData tvs tc tc_args deriv_pred mb_match = tcUnifyTy inst_ty_kind cls_arg_kind Just kind_subst = mb_match - all_tkvs = varSetElemsWellScoped $ - mkVarSet deriv_tvs `unionVarSet` - tyCoVarsOfTypes tc_args_to_keep + all_tkvs = toposortTyVars $ + runFVList $ unionFV + (tyCoVarsOfTypesAcc tc_args_to_keep) + (someVars deriv_tvs) + unmapped_tkvs = filter (`notElemTCvSubst` kind_subst) all_tkvs (subst, tkvs) = mapAccumL substTyVarBndr kind_subst unmapped_tkvs From git at git.haskell.org Thu Jul 14 13:52:55 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 14 Jul 2016 13:52:55 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Remove mysterious varSetElemsWellScoped in tidyFreeTyCoVars (9560075) Message-ID: <20160714135255.D6BA33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/9560075b1c40538428bf8f30f6134bf90d57f657/ghc >--------------------------------------------------------------- commit 9560075b1c40538428bf8f30f6134bf90d57f657 Author: Bartosz Nitka Date: Thu Apr 21 03:49:30 2016 -0700 Remove mysterious varSetElemsWellScoped in tidyFreeTyCoVars Richard isn't sure why it's there and removing it didn't change anything. >--------------------------------------------------------------- 9560075b1c40538428bf8f30f6134bf90d57f657 compiler/types/TyCoRep.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/types/TyCoRep.hs b/compiler/types/TyCoRep.hs index fe9a746..2295cac 100644 --- a/compiler/types/TyCoRep.hs +++ b/compiler/types/TyCoRep.hs @@ -128,7 +128,7 @@ import {-# SOURCE #-} DataCon( dataConTyCon, dataConFullSig , dataConUnivTyBinders, dataConExTyBinders , DataCon, filterEqSpec ) import {-# SOURCE #-} Type( isPredTy, isCoercionTy, mkAppTy - , tyCoVarsOfTypesWellScoped, varSetElemsWellScoped + , tyCoVarsOfTypesWellScoped , partitionInvisibles, coreView, typeKind , eqType ) -- Transitively pulls in a LOT of stuff, better to break the loop @@ -3046,7 +3046,7 @@ tidyFreeTyCoVars :: TidyEnv -> TyCoVarSet -> TidyEnv -- ^ Add the free 'TyVar's to the env in tidy form, -- so that we can tidy the type they are free in tidyFreeTyCoVars (full_occ_env, var_env) tyvars - = fst (tidyOpenTyCoVars (full_occ_env, var_env) (varSetElemsWellScoped tyvars)) + = fst (tidyOpenTyCoVars (full_occ_env, var_env) (varSetElems tyvars)) --------------- tidyOpenTyCoVars :: TidyEnv -> [TyCoVar] -> (TidyEnv, [TyCoVar]) From git at git.haskell.org Thu Jul 14 13:52:58 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 14 Jul 2016 13:52:58 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Kill varSetElems in injImproveEqns (a547b06) Message-ID: <20160714135258.956B93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/a547b0652c7142b6c192ea0572d4784cd4c21b1d/ghc >--------------------------------------------------------------- commit a547b0652c7142b6c192ea0572d4784cd4c21b1d Author: Bartosz Nitka Date: Thu Apr 28 05:40:39 2016 -0700 Kill varSetElems in injImproveEqns We want to remove varSetElems at the source level because it might be a source of nondeterminism. I don't think it introduces nondeterminism here, but it's easy to do the same thing deterministically for the same price. instFlexiTcS :: [TKVar] -> TcS (TCvSubst, [TcType]) instFlexiTcS currently gives the range of the produced substitution as the second element of the tuple, but it's not used anywhere right now. If it started to be used in the code I'm modifying it would cause nondeterminism problems. Test Plan: ./validate Reviewers: austin, goldfire, bgamari, simonmar, simonpj Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2149 GHC Trac Issues: #4012 >--------------------------------------------------------------- a547b0652c7142b6c192ea0572d4784cd4c21b1d compiler/typecheck/TcInteract.hs | 15 ++++++++++----- 1 file changed, 10 insertions(+), 5 deletions(-) diff --git a/compiler/typecheck/TcInteract.hs b/compiler/typecheck/TcInteract.hs index 39ad787..ca5d912 100644 --- a/compiler/typecheck/TcInteract.hs +++ b/compiler/typecheck/TcInteract.hs @@ -1491,7 +1491,7 @@ improve_top_fun_eqs fam_envs fam_tc args rhs_ty -> (a -> [Type]) -- get LHS of an axiom -> (a -> Type) -- get RHS of an axiom -> (a -> Maybe CoAxBranch) -- Just => apartness check required - -> [( [Type], TCvSubst, TyVarSet, Maybe CoAxBranch )] + -> [( [Type], TCvSubst, [TyVar], Maybe CoAxBranch )] -- Result: -- ( [arguments of a matching axiom] -- , RHS-unifying substitution @@ -1503,15 +1503,20 @@ improve_top_fun_eqs fam_envs fam_tc args rhs_ty , let ax_args = axiomLHS axiom , let ax_rhs = axiomRHS axiom , Just subst <- [tcUnifyTyWithTFs False ax_rhs rhs_ty] - , let tvs = tyCoVarsOfTypes ax_args + , let tvs = tyCoVarsOfTypesList ax_args notInSubst tv = not (tv `elemVarEnv` getTvSubstEnv subst) - unsubstTvs = filterVarSet (notInSubst <&&> isTyVar) tvs ] + unsubstTvs = filter (notInSubst <&&> isTyVar) tvs ] injImproveEqns :: [Bool] - -> ([Type], TCvSubst, TyCoVarSet, Maybe CoAxBranch) + -> ([Type], TCvSubst, [TyCoVar], Maybe CoAxBranch) -> TcS [Eqn] injImproveEqns inj_args (ax_args, theta, unsubstTvs, cabr) = do - (theta', _) <- instFlexiTcS (varSetElems unsubstTvs) + (theta', _) <- instFlexiTcS unsubstTvs + -- The use of deterministically ordered list for `unsubstTvs` + -- is not strictly necessary here, we only use the substitution + -- part of the result of instFlexiTcS. If we used the second + -- part of the tuple, which is the range of the substitution then + -- the order could be important. let subst = theta `unionTCvSubst` theta' return [ Pair arg (substTyUnchecked subst ax_arg) | case cabr of From git at git.haskell.org Thu Jul 14 13:53:01 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 14 Jul 2016 13:53:01 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Get rid of varSetElemsWellScoped in abstractFloats (9aa2419) Message-ID: <20160714135301.40B8C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/9aa241903556c616e7d2ca9584891b2441e6d559/ghc >--------------------------------------------------------------- commit 9aa241903556c616e7d2ca9584891b2441e6d559 Author: Bartosz Nitka Date: Fri Apr 22 09:47:30 2016 -0700 Get rid of varSetElemsWellScoped in abstractFloats It's possible to get rid of this use site in a local way and it introduces unneccessary nondeterminism. Test Plan: ./validate Reviewers: simonmar, goldfire, austin, bgamari, simonpj Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2122 GHC Trac Issues: #4012 >--------------------------------------------------------------- 9aa241903556c616e7d2ca9584891b2441e6d559 compiler/coreSyn/CoreFVs.hs | 9 ++++++++- compiler/simplCore/SimplUtils.hs | 8 ++++---- compiler/types/TyCoRep.hs | 7 ++++++- compiler/types/Type.hs | 2 +- 4 files changed, 19 insertions(+), 7 deletions(-) diff --git a/compiler/coreSyn/CoreFVs.hs b/compiler/coreSyn/CoreFVs.hs index 660538c..084ed65 100644 --- a/compiler/coreSyn/CoreFVs.hs +++ b/compiler/coreSyn/CoreFVs.hs @@ -22,7 +22,7 @@ module CoreFVs ( -- * Selective free variables of expressions InterestingVarFun, exprSomeFreeVars, exprsSomeFreeVars, - exprsSomeFreeVarsList, + exprSomeFreeVarsList, exprsSomeFreeVarsList, -- * Free variables of Rules, Vars and Ids varTypeTyCoVars, @@ -155,6 +155,13 @@ exprSomeFreeVars :: InterestingVarFun -- ^ Says which 'Var's are interesting -> VarSet exprSomeFreeVars fv_cand e = fvVarSet $ filterFV fv_cand $ expr_fvs e +-- | Finds free variables in an expression selected by a predicate +-- returning a deterministically ordered list. +exprSomeFreeVarsList :: InterestingVarFun -- ^ Says which 'Var's are interesting + -> CoreExpr + -> [Var] +exprSomeFreeVarsList fv_cand e = fvVarList $ filterFV fv_cand $ expr_fvs e + -- | Finds free variables in several expressions selected by a predicate exprsSomeFreeVars :: InterestingVarFun -- Says which 'Var's are interesting -> [CoreExpr] diff --git a/compiler/simplCore/SimplUtils.hs b/compiler/simplCore/SimplUtils.hs index 266a051..a3eb357 100644 --- a/compiler/simplCore/SimplUtils.hs +++ b/compiler/simplCore/SimplUtils.hs @@ -1573,10 +1573,10 @@ abstractFloats main_tvs body_env body rhs' = CoreSubst.substExpr (text "abstract_floats2") subst rhs -- tvs_here: see Note [Which type variables to abstract over] - tvs_here = varSetElemsWellScoped $ - intersectVarSet main_tv_set $ - closeOverKinds $ - exprSomeFreeVars isTyVar rhs' + tvs_here = toposortTyVars $ + filter (`elemVarSet` main_tv_set) $ + closeOverKindsList $ + exprSomeFreeVarsList isTyVar rhs' abstract subst (Rec prs) = do { (poly_ids, poly_apps) <- mapAndUnzipM (mk_poly tvs_here) ids diff --git a/compiler/types/TyCoRep.hs b/compiler/types/TyCoRep.hs index 2295cac..7054ed5 100644 --- a/compiler/types/TyCoRep.hs +++ b/compiler/types/TyCoRep.hs @@ -64,7 +64,7 @@ module TyCoRep ( tyCoVarsOfType, tyCoVarsOfTypeDSet, tyCoVarsOfTypes, tyCoVarsOfTypesDSet, tyCoFVsBndr, tyCoFVsOfType, tyCoVarsOfTypeList, tyCoFVsOfTypes, tyCoVarsOfTypesList, - closeOverKindsDSet, closeOverKindsFV, + closeOverKindsDSet, closeOverKindsFV, closeOverKindsList, coVarsOfType, coVarsOfTypes, coVarsOfCo, coVarsOfCos, tyCoVarsOfCo, tyCoVarsOfCos, @@ -1405,6 +1405,11 @@ closeOverKindsFV tvs = mapUnionFV (tyCoFVsOfType . tyVarKind) tvs `unionFV` mkFVs tvs -- | Add the kind variables free in the kinds of the tyvars in the given set. +-- Returns a deterministically ordered list. +closeOverKindsList :: [TyVar] -> [TyVar] +closeOverKindsList tvs = fvVarList $ closeOverKindsFV tvs + +-- | Add the kind variables free in the kinds of the tyvars in the given set. -- Returns a deterministic set. closeOverKindsDSet :: DTyVarSet -> DTyVarSet closeOverKindsDSet = fvDVarSet . closeOverKindsFV . dVarSetElems diff --git a/compiler/types/Type.hs b/compiler/types/Type.hs index 774db35..36cdf06 100644 --- a/compiler/types/Type.hs +++ b/compiler/types/Type.hs @@ -120,7 +120,7 @@ module Type ( tyCoVarsOfType, tyCoVarsOfTypes, tyCoFVsOfType, tyCoVarsOfTypeDSet, coVarsOfType, - coVarsOfTypes, closeOverKinds, + coVarsOfTypes, closeOverKinds, closeOverKindsList, splitDepVarsOfType, splitDepVarsOfTypes, splitVisVarsOfType, splitVisVarsOfTypes, expandTypeSynonyms, From git at git.haskell.org Thu Jul 14 13:53:03 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 14 Jul 2016 13:53:03 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Kill some unnecessary varSetElems (af1fe61) Message-ID: <20160714135303.EE93A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/af1fe61fb452f784a565efe267a8fa23a70034cb/ghc >--------------------------------------------------------------- commit af1fe61fb452f784a565efe267a8fa23a70034cb Author: Bartosz Nitka Date: Fri Apr 15 04:46:21 2016 -0700 Kill some unnecessary varSetElems When you do `varSetElems (tyCoVarsOfType x)` it's equivalent to `tyCoVarsOfTypeList x`. Why? If you look at the implementation: ``` tyCoVarsOfTypeList ty = runFVList $ tyCoVarsOfTypeAcc ty tyCoVarsOfType ty = runFVSet $ tyCoVarsOfTypeAcc ty ``` they use the same helper function. The helper function returns a deterministically ordered list and a set. The only difference between the two is which part of the result they take. It is redundant to take the set and then immediately convert it to a list. This helps with determinism and we eventually want to replace the uses of `varSetElems` with functions that don't leak the values of uniques. This change gets rid of some instances that are easy to kill. I chose not to annotate every place where I got rid of `varSetElems` with a comment about non-determinism, because once we get rid of `varSetElems` it will not be possible to do the wrong thing. Test Plan: ./validate Reviewers: goldfire, austin, simonmar, bgamari, simonpj Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2115 GHC Trac Issues: #4012 >--------------------------------------------------------------- af1fe61fb452f784a565efe267a8fa23a70034cb compiler/coreSyn/CoreFVs.hs | 40 ++++++++++++++++++++++++++++++++++++---- compiler/coreSyn/CoreLint.hs | 4 ++-- compiler/deSugar/Desugar.hs | 6 ++++-- compiler/deSugar/DsArrows.hs | 2 +- compiler/deSugar/DsBinds.hs | 4 +++- compiler/main/InteractiveEval.hs | 7 +++---- compiler/main/TidyPgm.hs | 2 +- compiler/specialise/Rules.hs | 4 ++-- compiler/typecheck/TcErrors.hs | 2 +- compiler/typecheck/TcInteract.hs | 2 +- compiler/typecheck/TcSimplify.hs | 5 +++-- compiler/typecheck/TcTyDecls.hs | 4 ++-- compiler/typecheck/TcValidity.hs | 5 +++-- 13 files changed, 62 insertions(+), 25 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc af1fe61fb452f784a565efe267a8fa23a70034cb From git at git.haskell.org Thu Jul 14 13:53:06 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 14 Jul 2016 13:53:06 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Kill non-deterministic foldUFM in TrieMap and TcAppMap (8064574) Message-ID: <20160714135306.A10203A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/806457482330a1bf660c92e71a6aff0fb62b16c2/ghc >--------------------------------------------------------------- commit 806457482330a1bf660c92e71a6aff0fb62b16c2 Author: Bartosz Nitka Date: Wed May 4 09:22:37 2016 -0700 Kill non-deterministic foldUFM in TrieMap and TcAppMap Summary: foldUFM introduces unnecessary non-determinism that actually leads to different generated code as explained in Note [TrieMap determinism]. As we're switching from UniqFM to UniqDFM here you might be concerned about performance. There's nothing that ./validate detects. nofib reports no change in Compile Allocations, but Compile Time got better on some tests and worse on some, yielding this summary: -1 s.d. ----- -3.8% +1 s.d. ----- +5.4% Average ----- +0.7% This is not a fair comparison as the order of Uniques changes what GHC is actually doing. One benefit from making this deterministic is also that it will make the performance results more stable. Full nofib results: P108 Test Plan: ./validate, nofib Reviewers: goldfire, simonpj, simonmar, austin, bgamari Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2169 GHC Trac Issues: #4012 >--------------------------------------------------------------- 806457482330a1bf660c92e71a6aff0fb62b16c2 compiler/basicTypes/NameEnv.hs | 24 ++++ compiler/basicTypes/VarEnv.hs | 8 ++ compiler/coreSyn/TrieMap.hs | 132 ++++++++++++++++----- compiler/typecheck/TcSMonad.hs | 28 +++-- .../tests/ghc-api/apirecomp001/apirecomp001.stderr | 16 +-- .../indexed-types/should_compile/T3017.stderr | 2 +- testsuite/tests/parser/should_compile/T2245.stderr | 8 +- .../should_compile/ExtraConstraints1.stderr | 6 +- .../should_compile/ExtraConstraints3.stderr | 32 ++--- .../WarningWildcardInstantiations.stderr | 2 +- .../InstantiatedNamedWildcardsInConstraints.stderr | 2 +- .../should_fail/WildcardInstantiations.stderr | 2 +- testsuite/tests/rebindable/rebindable6.stderr | 17 +-- .../tests/typecheck/should_compile/T10971a.stderr | 6 +- testsuite/tests/typecheck/should_fail/T5300.stderr | 4 +- testsuite/tests/typecheck/should_fail/T5853.stderr | 29 +++-- .../tests/typecheck/should_fail/tcfail171.stderr | 4 +- .../tests/typecheck/should_fail/tcfail204.stderr | 9 +- .../tests/warnings/should_compile/PluralS.stderr | 7 +- 19 files changed, 220 insertions(+), 118 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 806457482330a1bf660c92e71a6aff0fb62b16c2 From git at git.haskell.org Thu Jul 14 13:53:09 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 14 Jul 2016 13:53:09 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Remove some gratitious varSetElemsWellScoped (429b97c) Message-ID: <20160714135309.56C5F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/429b97c66fd8291178d76f43ecba7878dcef5c9c/ghc >--------------------------------------------------------------- commit 429b97c66fd8291178d76f43ecba7878dcef5c9c Author: Bartosz Nitka Date: Fri Apr 15 04:48:45 2016 -0700 Remove some gratitious varSetElemsWellScoped Summary: `varSetElemsWellScoped` uses `varSetElems` under the hood which introduces unnecessary nondeterminism. This does the same thing, possibly cheaper, while preserving determinism. Test Plan: ./validate Reviewers: simonmar, goldfire, austin, bgamari, simonpj Reviewed By: simonpj Subscribers: thomie, RyanGlScott Differential Revision: https://phabricator.haskell.org/D2116 GHC Trac Issues: #4012 >--------------------------------------------------------------- 429b97c66fd8291178d76f43ecba7878dcef5c9c compiler/typecheck/TcClassDcl.hs | 13 ++++++------- compiler/typecheck/TcDeriv.hs | 8 ++++---- compiler/typecheck/TcGenGenerics.hs | 12 ++++++------ 3 files changed, 16 insertions(+), 17 deletions(-) diff --git a/compiler/typecheck/TcClassDcl.hs b/compiler/typecheck/TcClassDcl.hs index 602ef64..48b0e56 100644 --- a/compiler/typecheck/TcClassDcl.hs +++ b/compiler/typecheck/TcClassDcl.hs @@ -26,7 +26,7 @@ import TcBinds import TcUnify import TcHsType import TcMType -import Type ( getClassPredTys_maybe, varSetElemsWellScoped, piResultTys ) +import Type ( getClassPredTys_maybe, piResultTys ) import TcType import TcRnMonad import BuildTyCl( TcMethInfo ) @@ -41,7 +41,6 @@ import NameEnv import NameSet import Var import VarEnv -import VarSet import Outputable import SrcLoc import TyCon @@ -53,7 +52,7 @@ import BooleanFormula import Util import Control.Monad -import Data.List ( mapAccumL ) +import Data.List ( mapAccumL, partition ) {- Dictionary handling @@ -454,10 +453,10 @@ tcATDefault emit_warn loc inst_subst defined_ats (ATI fam_tc defs) = do { let (subst', pat_tys') = mapAccumL subst_tv inst_subst (tyConTyVars fam_tc) rhs' = substTyUnchecked subst' rhs_ty - tcv_set' = tyCoVarsOfTypes pat_tys' - (tv_set', cv_set') = partitionVarSet isTyVar tcv_set' - tvs' = varSetElemsWellScoped tv_set' - cvs' = varSetElemsWellScoped cv_set' + tcv' = tyCoVarsOfTypesList pat_tys' + (tv', cv') = partition isTyVar tcv' + tvs' = toposortTyVars tv' + cvs' = toposortTyVars cv' ; rep_tc_name <- newFamInstTyConName (L loc (tyConName fam_tc)) pat_tys' ; let axiom = mkSingleCoAxiom Nominal rep_tc_name tvs' cvs' fam_tc pat_tys' rhs' diff --git a/compiler/typecheck/TcDeriv.hs b/compiler/typecheck/TcDeriv.hs index 9b9a22b..03f593c 100644 --- a/compiler/typecheck/TcDeriv.hs +++ b/compiler/typecheck/TcDeriv.hs @@ -1586,7 +1586,7 @@ mkNewTypeEqn dflags overlap_mode tvs case mtheta of Just theta -> return $ GivenTheta $ DS { ds_loc = loc - , ds_name = dfun_name, ds_tvs = varSetElemsWellScoped dfun_tvs + , ds_name = dfun_name, ds_tvs = dfun_tvs , ds_cls = cls, ds_tys = inst_tys , ds_tc = rep_tycon , ds_theta = theta @@ -1594,7 +1594,7 @@ mkNewTypeEqn dflags overlap_mode tvs , ds_newtype = Just rep_inst_ty } Nothing -> return $ InferTheta $ DS { ds_loc = loc - , ds_name = dfun_name, ds_tvs = varSetElemsWellScoped dfun_tvs + , ds_name = dfun_name, ds_tvs = dfun_tvs , ds_cls = cls, ds_tys = inst_tys , ds_tc = rep_tycon , ds_theta = all_preds @@ -1689,7 +1689,7 @@ mkNewTypeEqn dflags overlap_mode tvs -- Next we figure out what superclass dictionaries to use -- See Note [Newtype deriving superclasses] above cls_tyvars = classTyVars cls - dfun_tvs = tyCoVarsOfTypes inst_tys + dfun_tvs = tyCoVarsOfTypesWellScoped inst_tys inst_ty = mkTyConApp tycon tc_args inst_tys = cls_tys ++ [inst_ty] sc_theta = mkThetaOrigin DerivOrigin TypeLevel $ @@ -1701,7 +1701,7 @@ mkNewTypeEqn dflags overlap_mode tvs -- newtype type; precisely the constraints required for the -- calls to coercible that we are going to generate. coercible_constraints = - [ let (Pair t1 t2) = mkCoerceClassMethEqn cls (varSetElemsWellScoped dfun_tvs) inst_tys rep_inst_ty meth + [ let (Pair t1 t2) = mkCoerceClassMethEqn cls dfun_tvs inst_tys rep_inst_ty meth in mkPredOrigin (DerivOriginCoerce meth t1 t2) TypeLevel (mkReprPrimEqPred t1 t2) | meth <- classMethods cls ] diff --git a/compiler/typecheck/TcGenGenerics.hs b/compiler/typecheck/TcGenGenerics.hs index 03b4d65..ebe9303 100644 --- a/compiler/typecheck/TcGenGenerics.hs +++ b/compiler/typecheck/TcGenGenerics.hs @@ -37,13 +37,13 @@ import ErrUtils( Validity(..), andValid ) import SrcLoc import Bag import VarEnv -import VarSet (elemVarSet, partitionVarSet) +import VarSet (elemVarSet) import Outputable import FastString import Util import Control.Monad (mplus) -import Data.List (zip4) +import Data.List (zip4, partition) import Data.Maybe (isJust) #include "HsVersions.h" @@ -395,10 +395,10 @@ tc_mkRepFamInsts gk tycon inst_ty mod = in_scope = mkInScopeSet (tyCoVarsOfType inst_ty) subst = mkTvSubst in_scope env repTy' = substTy subst repTy - tcv_set' = tyCoVarsOfType inst_ty - (tv_set', cv_set') = partitionVarSet isTyVar tcv_set' - tvs' = varSetElemsWellScoped tv_set' - cvs' = varSetElemsWellScoped cv_set' + tcv' = tyCoVarsOfTypeList inst_ty + (tv', cv') = partition isTyVar tcv' + tvs' = toposortTyVars tv' + cvs' = toposortTyVars cv' axiom = mkSingleCoAxiom Nominal rep_name tvs' cvs' fam_tc [inst_ty] repTy' From git at git.haskell.org Thu Jul 14 13:53:11 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 14 Jul 2016 13:53:11 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Make benign non-determinism in pretty-printing more obvious (3c1c80b) Message-ID: <20160714135312.003973A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/3c1c80b88a82c0aff3662c6747f8528902e4dc1e/ghc >--------------------------------------------------------------- commit 3c1c80b88a82c0aff3662c6747f8528902e4dc1e Author: Bartosz Nitka Date: Mon Apr 18 07:32:03 2016 -0700 Make benign non-determinism in pretty-printing more obvious This change takes us one step closer to being able to remove `varSetElemsWellScoped`. The end goal is to make every source of non-determinism obvious at the source level, so that when we achieve determinism it doesn't get broken accidentally. Test Plan: compile GHC Reviewers: simonmar, goldfire, simonpj, austin, bgamari Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2123 GHC Trac Issues: #4012 >--------------------------------------------------------------- 3c1c80b88a82c0aff3662c6747f8528902e4dc1e compiler/basicTypes/VarSet.hs | 21 ++++++++++++++++++++- compiler/typecheck/FamInst.hs | 4 ++-- compiler/typecheck/FunDeps.hs | 6 +++--- compiler/utils/UniqFM.hs | 20 +++++++++++++++++++- 4 files changed, 44 insertions(+), 7 deletions(-) diff --git a/compiler/basicTypes/VarSet.hs b/compiler/basicTypes/VarSet.hs index 1cd9e21..8ece555 100644 --- a/compiler/basicTypes/VarSet.hs +++ b/compiler/basicTypes/VarSet.hs @@ -21,6 +21,7 @@ module VarSet ( lookupVarSet, lookupVarSetByName, mapVarSet, sizeVarSet, seqVarSet, elemVarSetByKey, partitionVarSet, + pluralVarSet, pprVarSet, -- * Deterministic Var set types DVarSet, DIdSet, DTyVarSet, DTyCoVarSet, @@ -45,8 +46,9 @@ import Unique import Name ( Name ) import UniqSet import UniqDSet -import UniqFM( disjointUFM ) +import UniqFM( disjointUFM, pluralUFM, pprUFM ) import UniqDFM( disjointUDFM ) +import Outputable (SDoc) -- | A non-deterministic set of variables. -- See Note [Deterministic UniqFM] in UniqDFM for explanation why it's not @@ -169,6 +171,23 @@ transCloVarSet fn seeds seqVarSet :: VarSet -> () seqVarSet s = sizeVarSet s `seq` () +-- | Determines the pluralisation suffix appropriate for the length of a set +-- in the same way that plural from Outputable does for lists. +pluralVarSet :: VarSet -> SDoc +pluralVarSet = pluralUFM + +-- | Pretty-print a non-deterministic set. +-- The order of variables is non-deterministic and for pretty-printing that +-- shouldn't be a problem. +-- Having this function helps contain the non-determinism created with +-- varSetElems. +pprVarSet :: ([Var] -> SDoc) -- ^ The pretty printing function to use on the + -- elements + -> VarSet -- ^ The things to be pretty printed + -> SDoc -- ^ 'SDoc' where the things have been pretty + -- printed +pprVarSet = pprUFM + -- Deterministic VarSet -- See Note [Deterministic UniqFM] in UniqDFM for explanation why we need -- DVarSet. diff --git a/compiler/typecheck/FamInst.hs b/compiler/typecheck/FamInst.hs index 2ff256d..1d9e1ce 100644 --- a/compiler/typecheck/FamInst.hs +++ b/compiler/typecheck/FamInst.hs @@ -562,12 +562,12 @@ unusedInjectiveVarsErr (Pair invis_vars vis_vars) errorBuilder tyfamEqn = errorBuilder (injectivityErrorHerald True $$ msg) [tyfamEqn] where - tvs = varSetElemsWellScoped (invis_vars `unionVarSet` vis_vars) + tvs = invis_vars `unionVarSet` vis_vars has_types = not $ isEmptyVarSet vis_vars has_kinds = not $ isEmptyVarSet invis_vars doc = sep [ what <+> text "variable" <> - plural tvs <+> pprQuotedList tvs + pluralVarSet tvs <+> pprVarSet (pprQuotedList . toposortTyVars) tvs , text "cannot be inferred from the right-hand side." ] what = case (has_types, has_kinds) of (True, True) -> text "Type and kind" diff --git a/compiler/typecheck/FunDeps.hs b/compiler/typecheck/FunDeps.hs index 87fb4ff..776a9f1 100644 --- a/compiler/typecheck/FunDeps.hs +++ b/compiler/typecheck/FunDeps.hs @@ -387,7 +387,7 @@ checkInstCoverage be_liberal clas theta inst_taus liberal_undet_tvs = (`minusVarSet` closed_ls_tvs) <$> rs_tvs conserv_undet_tvs = (`minusVarSet` ls_tvs) <$> rs_tvs - undet_list = varSetElemsWellScoped (fold undetermined_tvs) + undet_set = fold undetermined_tvs msg = vcat [ -- text "ls_tvs" <+> ppr ls_tvs -- , text "closed ls_tvs" <+> ppr (closeOverKinds ls_tvs) @@ -407,8 +407,8 @@ checkInstCoverage be_liberal clas theta inst_taus else text "do not jointly") <+> text "determine rhs type"<>plural rs <+> pprQuotedList rs ] - , text "Un-determined variable" <> plural undet_list <> colon - <+> pprWithCommas ppr undet_list + , text "Un-determined variable" <> pluralVarSet undet_set <> colon + <+> pprVarSet (pprWithCommas ppr) undet_set , ppWhen (isEmptyVarSet $ pSnd undetermined_tvs) $ text "(Use -fprint-explicit-kinds to see the kind variables in the types)" , ppWhen (not be_liberal && diff --git a/compiler/utils/UniqFM.hs b/compiler/utils/UniqFM.hs index e261df7..4a5f14f 100644 --- a/compiler/utils/UniqFM.hs +++ b/compiler/utils/UniqFM.hs @@ -67,7 +67,7 @@ module UniqFM ( eltsUFM, keysUFM, splitUFM, ufmToSet_Directly, ufmToList, - joinUFM, pprUniqFM + joinUFM, pprUniqFM, pprUFM, pluralUFM ) where import Unique ( Uniquable(..), Unique, getKey ) @@ -327,3 +327,21 @@ pprUniqFM ppr_elt ufm = brackets $ fsep $ punctuate comma $ [ ppr uq <+> text ":->" <+> ppr_elt elt | (uq, elt) <- ufmToList ufm ] + +-- | Pretty-print a non-deterministic set. +-- The order of variables is non-deterministic and for pretty-printing that +-- shouldn't be a problem. +-- Having this function helps contain the non-determinism created with +-- eltsUFM. +pprUFM :: ([a] -> SDoc) -- ^ The pretty printing function to use on the elements + -> UniqFM a -- ^ The things to be pretty printed + -> SDoc -- ^ 'SDoc' where the things have been pretty + -- printed +pprUFM pp ufm = pp (eltsUFM ufm) + +-- | Determines the pluralisation suffix appropriate for the length of a set +-- in the same way that plural from Outputable does for lists. +pluralUFM :: UniqFM a -> SDoc +pluralUFM ufm + | sizeUFM ufm == 1 = empty + | otherwise = char 's' From git at git.haskell.org Thu Jul 14 13:53:14 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 14 Jul 2016 13:53:14 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Refactor computing dependent type vars (f57263b) Message-ID: <20160714135314.C838B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/f57263b9092eedfd21f05a3dbe5cd61baca3fb57/ghc >--------------------------------------------------------------- commit f57263b9092eedfd21f05a3dbe5cd61baca3fb57 Author: Simon Peyton Jones Date: Mon Apr 18 15:01:13 2016 +0100 Refactor computing dependent type vars There should be no change in behaviour here * Move splitDepVarsOfType(s) from Type to TcType * Define data type TcType.TcDepVars, document what it means, and use it where appropriate, notably in splitDepVarsOfType(s) * Use it in TcMType.quantifyTyVars and friends >--------------------------------------------------------------- f57263b9092eedfd21f05a3dbe5cd61baca3fb57 compiler/typecheck/TcHsType.hs | 29 +++++++------ compiler/typecheck/TcMType.hs | 56 +++++++++++++----------- compiler/typecheck/TcPatSyn.hs | 22 ++++------ compiler/typecheck/TcSimplify.hs | 33 +++++++------- compiler/typecheck/TcType.hs | 94 ++++++++++++++++++++++++++++++++++++++++ compiler/types/Type.hs | 42 ------------------ 6 files changed, 163 insertions(+), 113 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc f57263b9092eedfd21f05a3dbe5cd61baca3fb57 From git at git.haskell.org Thu Jul 14 13:53:17 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 14 Jul 2016 13:53:17 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Kill varSetElems in TcErrors (8066564) Message-ID: <20160714135317.7861D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/80665640c51d5f6db1a7705d21c5386bcc6c234b/ghc >--------------------------------------------------------------- commit 80665640c51d5f6db1a7705d21c5386bcc6c234b Author: Bartosz Nitka Date: Tue Apr 26 08:47:21 2016 -0700 Kill varSetElems in TcErrors The uses of varSetElems in these places are unnecessary and while it doesn't intruduce non-determinism in the ABI the plan is to get rid of all varSetElems to get some compile time guarantees. Test Plan: ./validate Reviewers: austin, simonmar, bgamari, goldfire, simonpj Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2141 GHC Trac Issues: #4012 >--------------------------------------------------------------- 80665640c51d5f6db1a7705d21c5386bcc6c234b compiler/typecheck/TcErrors.hs | 14 ++++----- .../tests/dependent/should_fail/T11407.stderr | 2 +- .../tests/indexed-types/should_fail/T2693.stderr | 8 ++--- testsuite/tests/typecheck/should_fail/T4921.stderr | 34 +++++++++++----------- 4 files changed, 29 insertions(+), 29 deletions(-) diff --git a/compiler/typecheck/TcErrors.hs b/compiler/typecheck/TcErrors.hs index 1418a2b..96c5530 100644 --- a/compiler/typecheck/TcErrors.hs +++ b/compiler/typecheck/TcErrors.hs @@ -52,6 +52,7 @@ import StaticFlags ( opt_PprStyle_Debug ) import ListSetOps ( equivClasses ) import Maybes import qualified GHC.LanguageExtensions as LangExt +import FV ( fvVarList, unionFV ) import Control.Monad ( when ) import Data.List ( partition, mapAccumL, nub, sortBy ) @@ -175,7 +176,7 @@ report_unsolved mb_binds_var err_as_warn type_errors expr_holes type_holes wante free_tvs = tyCoVarsOfWC wanted ; traceTc "reportUnsolved (after zonking and tidying):" $ - vcat [ pprTvBndrs (varSetElems free_tvs) + vcat [ pprVarSet pprTvBndrs free_tvs , ppr wanted ] ; warn_redundant <- woptM Opt_WarnRedundantConstraints @@ -1333,8 +1334,8 @@ mkTyVarEqErr dflags ctxt report ct oriented tv1 ty2 interesting_tyvars = filter (not . isEmptyVarSet . tyCoVarsOfType . tyVarKind) $ filter isTyVar $ - varSetElems $ - tyCoVarsOfType ty1 `unionVarSet` tyCoVarsOfType ty2 + fvVarList $ + tyCoFVsOfType ty1 `unionFV` tyCoFVsOfType ty2 extra3 = relevant_bindings $ ppWhen (not (null interesting_tyvars)) $ hang (text "Type variable kinds:") 2 $ @@ -2419,10 +2420,9 @@ getAmbigTkvs :: Ct -> ([Var],[Var]) getAmbigTkvs ct = partition (`elemVarSet` dep_tkv_set) ambig_tkvs where - tkv_set = tyCoVarsOfCt ct - ambig_tkv_set = filterVarSet isAmbiguousTyVar tkv_set - dep_tkv_set = tyCoVarsOfTypes (map tyVarKind (varSetElems tkv_set)) - ambig_tkvs = varSetElems ambig_tkv_set + tkvs = tyCoVarsOfCtList ct + ambig_tkvs = filter isAmbiguousTyVar tkvs + dep_tkv_set = tyCoVarsOfTypes (map tyVarKind tkvs) getSkolemInfo :: [Implication] -> TcTyVar -> ([TcTyVar], SkolemInfo) -- Get the skolem info for a type variable diff --git a/testsuite/tests/dependent/should_fail/T11407.stderr b/testsuite/tests/dependent/should_fail/T11407.stderr index b5d95bf..b07aa2b 100644 --- a/testsuite/tests/dependent/should_fail/T11407.stderr +++ b/testsuite/tests/dependent/should_fail/T11407.stderr @@ -4,5 +4,5 @@ T11407.hs:10:40: error: • In the second argument of ‘UhOh’, namely ‘(a :: x a)’ In the data instance declaration for ‘UhOh’ • Type variable kinds: - a :: k0 x :: k0 -> * + a :: k0 diff --git a/testsuite/tests/indexed-types/should_fail/T2693.stderr b/testsuite/tests/indexed-types/should_fail/T2693.stderr index 0c00711..a0ac4ea 100644 --- a/testsuite/tests/indexed-types/should_fail/T2693.stderr +++ b/testsuite/tests/indexed-types/should_fail/T2693.stderr @@ -1,7 +1,7 @@ T2693.hs:12:15: error: • Couldn't match expected type ‘(a8, b1)’ with actual type ‘TFn a6’ - The type variables ‘b1’, ‘a6’, ‘a8’ are ambiguous + The type variables ‘a6’, ‘a8’, ‘b1’ are ambiguous • In the first argument of ‘fst’, namely ‘x’ In the first argument of ‘(+)’, namely ‘fst x’ In the expression: fst x + fst x @@ -9,7 +9,7 @@ T2693.hs:12:15: error: T2693.hs:12:23: error: • Couldn't match expected type ‘(a8, b2)’ with actual type ‘TFn a7’ - The type variables ‘b2’, ‘a7’, ‘a8’ are ambiguous + The type variables ‘a7’, ‘a8’, ‘b2’ are ambiguous • In the first argument of ‘fst’, namely ‘x’ In the second argument of ‘(+)’, namely ‘fst x’ In the expression: fst x + fst x @@ -17,7 +17,7 @@ T2693.hs:12:23: error: T2693.hs:19:15: error: • Couldn't match expected type ‘(a5, b0)’ with actual type ‘TFn a2’ - The type variables ‘b0’, ‘a2’, ‘a5’ are ambiguous + The type variables ‘a2’, ‘a5’, ‘b0’ are ambiguous • In the first argument of ‘fst’, namely ‘x’ In the first argument of ‘(+)’, namely ‘fst x’ In the expression: fst x + snd x @@ -25,7 +25,7 @@ T2693.hs:19:15: error: T2693.hs:19:23: error: • Couldn't match expected type ‘(a3, a5)’ with actual type ‘TFn a4’ - The type variables ‘a3’, ‘a4’, ‘a5’ are ambiguous + The type variables ‘a4’, ‘a3’, ‘a5’ are ambiguous • In the first argument of ‘snd’, namely ‘x’ In the second argument of ‘(+)’, namely ‘snd x’ In the expression: fst x + snd x diff --git a/testsuite/tests/typecheck/should_fail/T4921.stderr b/testsuite/tests/typecheck/should_fail/T4921.stderr index 42d5a8a..8eff919 100644 --- a/testsuite/tests/typecheck/should_fail/T4921.stderr +++ b/testsuite/tests/typecheck/should_fail/T4921.stderr @@ -1,21 +1,21 @@ T4921.hs:10:9: error: - Ambiguous type variables ‘b1’, ‘a0’ arising from a use of ‘f’ - prevents the constraint ‘(C a0 b1)’ from being solved. - Relevant bindings include x :: a0 (bound at T4921.hs:10:1) - Probable fix: use a type annotation to specify what ‘b1’, ‘a0’ should be. - These potential instance exist: - instance C Int Char -- Defined at T4921.hs:7:10 - In the first argument of ‘fst’, namely ‘f’ - In the expression: fst f - In an equation for ‘x’: x = fst f + • Ambiguous type variables ‘a0’, ‘b1’ arising from a use of ‘f’ + prevents the constraint ‘(C a0 b1)’ from being solved. + Relevant bindings include x :: a0 (bound at T4921.hs:10:1) + Probable fix: use a type annotation to specify what ‘a0’, ‘b1’ should be. + These potential instance exist: + instance C Int Char -- Defined at T4921.hs:7:10 + • In the first argument of ‘fst’, namely ‘f’ + In the expression: fst f + In an equation for ‘x’: x = fst f T4921.hs:12:9: error: - Ambiguous type variable ‘b0’ arising from a use of ‘f’ - prevents the constraint ‘(C Int b0)’ from being solved. - Probable fix: use a type annotation to specify what ‘b0’ should be. - These potential instance exist: - instance C Int Char -- Defined at T4921.hs:7:10 - In the first argument of ‘fst’, namely ‘f’ - In the expression: fst f :: Int - In an equation for ‘y’: y = fst f :: Int + • Ambiguous type variable ‘b0’ arising from a use of ‘f’ + prevents the constraint ‘(C Int b0)’ from being solved. + Probable fix: use a type annotation to specify what ‘b0’ should be. + These potential instance exist: + instance C Int Char -- Defined at T4921.hs:7:10 + • In the first argument of ‘fst’, namely ‘f’ + In the expression: fst f :: Int + In an equation for ‘y’: y = fst f :: Int From git at git.haskell.org Thu Jul 14 13:53:20 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 14 Jul 2016 13:53:20 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Make absentError not depend on uniques (982eff5) Message-ID: <20160714135320.26B823A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/982eff5e1a16f2620e1ec1c568a27277509df790/ghc >--------------------------------------------------------------- commit 982eff5e1a16f2620e1ec1c568a27277509df790 Author: Bartosz Nitka Date: Thu May 12 05:42:21 2016 -0700 Make absentError not depend on uniques As explained in the comment it will cause changes in inlining if we don't suppress them. Test Plan: ./validate Reviewers: bgamari, austin, simonpj, goldfire, simonmar Reviewed By: simonmar Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2203 GHC Trac Issues: #4012 >--------------------------------------------------------------- 982eff5e1a16f2620e1ec1c568a27277509df790 compiler/stranal/WwLib.hs | 9 ++++++++- 1 file changed, 8 insertions(+), 1 deletion(-) diff --git a/compiler/stranal/WwLib.hs b/compiler/stranal/WwLib.hs index 1472ead..09bc204 100644 --- a/compiler/stranal/WwLib.hs +++ b/compiler/stranal/WwLib.hs @@ -757,7 +757,14 @@ mk_absent_let dflags arg where arg_ty = idType arg abs_rhs = mkRuntimeErrorApp aBSENT_ERROR_ID arg_ty msg - msg = showSDoc dflags (ppr arg <+> ppr (idType arg)) + msg = showSDoc (gopt_set dflags Opt_SuppressUniques) + (ppr arg <+> ppr (idType arg)) + -- We need to suppress uniques here because otherwise they'd + -- end up in the generated code as strings. This is bad for + -- determinism, because with different uniques the strings + -- will have different lengths and hence different costs for + -- the inliner leading to different inlining. + -- See also Note [Unique Determinism] in Unique mk_seq_case :: Id -> CoreExpr -> CoreExpr mk_seq_case arg body = Case (Var arg) (sanitiseCaseBndr arg) (exprType body) [(DEFAULT, [], body)] From git at git.haskell.org Thu Jul 14 13:53:22 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 14 Jul 2016 13:53:22 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Kill varEnvElts in specImports (24da27c) Message-ID: <20160714135322.D2E693A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/24da27c59d90b2a7e73f4458a2717c619dd91158/ghc >--------------------------------------------------------------- commit 24da27c59d90b2a7e73f4458a2717c619dd91158 Author: Bartosz Nitka Date: Thu May 12 06:55:00 2016 -0700 Kill varEnvElts in specImports We need the order of specialized binds and rules to be deterministic, so we use a deterministic set here. Test Plan: ./validate Reviewers: simonmar, bgamari, austin, simonpj Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2197 GHC Trac Issues: #4012 >--------------------------------------------------------------- 24da27c59d90b2a7e73f4458a2717c619dd91158 compiler/basicTypes/VarEnv.hs | 25 +++++++++++++++++++++++-- compiler/specialise/Specialise.hs | 28 ++++++++++++++++++---------- compiler/utils/UniqDFM.hs | 32 ++++++++++++++++++++++++++++++++ 3 files changed, 73 insertions(+), 12 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 24da27c59d90b2a7e73f4458a2717c619dd91158 From git at git.haskell.org Thu Jul 14 13:53:25 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 14 Jul 2016 13:53:25 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Rename FV related functions (8f007d6) Message-ID: <20160714135325.916CB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/8f007d6383273e2d1614469464dc712a12b225ed/ghc >--------------------------------------------------------------- commit 8f007d6383273e2d1614469464dc712a12b225ed Author: Bartosz Nitka Date: Wed Apr 20 09:51:05 2016 -0700 Rename FV related functions This is from Simon's suggestion: * `tyCoVarsOfTypesAcc` is a terrible name for a function with a perfectly decent type `[Type] -> FV`. Maybe `tyCoFVsOfTypes`? Similarly others * `runFVList` is also terrible, but also has a decent type. Maybe just `fvVarList` (and `fvVarSet` for `runFVSet`). * `someVars` could be `mkFVs :: [Var] -> FV`. >--------------------------------------------------------------- 8f007d6383273e2d1614469464dc712a12b225ed compiler/coreSyn/CoreFVs.hs | 150 ++++++++++++++++++++-------------------- compiler/coreSyn/CoreSubst.hs | 2 +- compiler/simplCore/SetLevels.hs | 4 +- compiler/typecheck/TcDeriv.hs | 10 +-- compiler/typecheck/TcRnTypes.hs | 32 +++++---- compiler/typecheck/TcType.hs | 10 +-- compiler/types/Coercion.hs | 2 +- compiler/types/TyCoRep.hs | 144 ++++++++++++++++++++------------------ compiler/types/Type.hs | 2 +- compiler/utils/FV.hs | 69 +++++++++--------- 10 files changed, 220 insertions(+), 205 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 8f007d6383273e2d1614469464dc712a12b225ed From git at git.haskell.org Thu Jul 14 13:53:28 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 14 Jul 2016 13:53:28 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Kill varSetElems try_tyvar_defaulting (788aa81) Message-ID: <20160714135328.451453A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/788aa81331522b8e558afa46f2b84a8c8cd1efc4/ghc >--------------------------------------------------------------- commit 788aa81331522b8e558afa46f2b84a8c8cd1efc4 Author: Bartosz Nitka Date: Tue Apr 26 09:51:26 2016 -0700 Kill varSetElems try_tyvar_defaulting `varSetElems` introduces unnecessary nondeterminism and we can do the same thing deterministically for the same price. Test Plan: ./validate Reviewers: goldfire, austin, simonmar, bgamari, simonpj Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2143 GHC Trac Issues: #4012 >--------------------------------------------------------------- 788aa81331522b8e558afa46f2b84a8c8cd1efc4 compiler/typecheck/TcMType.hs | 7 +++++++ compiler/typecheck/TcRnTypes.hs | 37 +++++++++++++++++++++++++++---------- compiler/typecheck/TcSMonad.hs | 4 ++++ compiler/typecheck/TcSimplify.hs | 5 ++--- 4 files changed, 40 insertions(+), 13 deletions(-) diff --git a/compiler/typecheck/TcMType.hs b/compiler/typecheck/TcMType.hs index 5fefa2b..5fa0bc9 100644 --- a/compiler/typecheck/TcMType.hs +++ b/compiler/typecheck/TcMType.hs @@ -68,6 +68,7 @@ module TcMType ( tidyEvVar, tidyCt, tidySkolemInfo, skolemiseUnboundMetaTyVar, zonkTcTyVar, zonkTcTyVars, zonkTyCoVarsAndFV, zonkTcTypeAndFV, + zonkTyCoVarsAndFVList, zonkTcTypeAndSplitDepVars, zonkTcTypesAndSplitDepVars, zonkQuantifiedTyVar, zonkQuantifiedTyVarOrType, quantifyTyVars, quantifyZonkedTyVars, @@ -1202,6 +1203,12 @@ zonkTyCoVar tv | isTcTyVar tv = zonkTcTyVar tv zonkTyCoVarsAndFV :: TyCoVarSet -> TcM TyCoVarSet zonkTyCoVarsAndFV tycovars = tyCoVarsOfTypes <$> mapM zonkTyCoVar (varSetElems tycovars) +-- Takes a list of TyCoVars, zonks them and returns a +-- deterministically ordered list of their free variables. +zonkTyCoVarsAndFVList :: [TyCoVar] -> TcM [TyCoVar] +zonkTyCoVarsAndFVList tycovars = + tyCoVarsOfTypesList <$> mapM zonkTyCoVar tycovars + -- Takes a deterministic set of TyCoVars, zonks them and returns a -- deterministic set of their free variables. -- See Note [quantifyTyVars determinism]. diff --git a/compiler/typecheck/TcRnTypes.hs b/compiler/typecheck/TcRnTypes.hs index dccfd40..4755f8d 100644 --- a/compiler/typecheck/TcRnTypes.hs +++ b/compiler/typecheck/TcRnTypes.hs @@ -85,6 +85,7 @@ module TcRnTypes( andWC, unionsWC, mkSimpleWC, mkImplicWC, addInsols, addSimples, addImplics, tyCoVarsOfWC, dropDerivedWC, dropDerivedSimples, dropDerivedInsols, + tyCoVarsOfWCList, isDroppableDerivedLoc, insolubleImplic, arisesFromGivens, @@ -1608,22 +1609,38 @@ tyCoVarsOfCtsList = fvVarList . tyCoFVsOfCts tyCoFVsOfCts :: Cts -> FV tyCoFVsOfCts = foldrBag (unionFV . tyCoFVsOfCt) emptyFV +-- | Returns free variables of WantedConstraints as a non-deterministic +-- set. See Note [Deterministic FV] in FV. tyCoVarsOfWC :: WantedConstraints -> TyCoVarSet -- Only called on *zonked* things, hence no need to worry about flatten-skolems -tyCoVarsOfWC (WC { wc_simple = simple, wc_impl = implic, wc_insol = insol }) - = tyCoVarsOfCts simple `unionVarSet` - tyCoVarsOfBag tyCoVarsOfImplic implic `unionVarSet` - tyCoVarsOfCts insol +tyCoVarsOfWC = fvVarSet . tyCoFVsOfWC + +-- | Returns free variables of WantedConstraints as a deterministically +-- ordered list. See Note [Deterministic FV] in FV. +tyCoVarsOfWCList :: WantedConstraints -> [TyCoVar] +-- Only called on *zonked* things, hence no need to worry about flatten-skolems +tyCoVarsOfWCList = fvVarList . tyCoFVsOfWC -tyCoVarsOfImplic :: Implication -> TyCoVarSet +-- | Returns free variables of WantedConstraints as a composable FV +-- computation. See Note [Deterministic FV] in FV. +tyCoFVsOfWC :: WantedConstraints -> FV +-- Only called on *zonked* things, hence no need to worry about flatten-skolems +tyCoFVsOfWC (WC { wc_simple = simple, wc_impl = implic, wc_insol = insol }) + = tyCoFVsOfCts simple `unionFV` + tyCoFVsOfBag tyCoFVsOfImplic implic `unionFV` + tyCoFVsOfCts insol + +-- | Returns free variables of Implication as a composable FV computation. +-- See Note [Deterministic FV] in FV. +tyCoFVsOfImplic :: Implication -> FV -- Only called on *zonked* things, hence no need to worry about flatten-skolems -tyCoVarsOfImplic (Implic { ic_skols = skols +tyCoFVsOfImplic (Implic { ic_skols = skols , ic_given = givens, ic_wanted = wanted }) - = (tyCoVarsOfWC wanted `unionVarSet` tyCoVarsOfTypes (map evVarPred givens)) - `delVarSetList` skols + = FV.delFVs (mkVarSet skols) + (tyCoFVsOfWC wanted `unionFV` tyCoFVsOfTypes (map evVarPred givens)) -tyCoVarsOfBag :: (a -> TyCoVarSet) -> Bag a -> TyCoVarSet -tyCoVarsOfBag tvs_of = foldrBag (unionVarSet . tvs_of) emptyVarSet +tyCoFVsOfBag :: (a -> FV) -> Bag a -> FV +tyCoFVsOfBag tvs_of = foldrBag (unionFV . tvs_of) emptyFV -------------------------- dropDerivedSimples :: Cts -> Cts diff --git a/compiler/typecheck/TcSMonad.hs b/compiler/typecheck/TcSMonad.hs index ad86f7f..afd199f 100644 --- a/compiler/typecheck/TcSMonad.hs +++ b/compiler/typecheck/TcSMonad.hs @@ -93,6 +93,7 @@ module TcSMonad ( TcLevel, isTouchableMetaTyVarTcS, isFilledMetaTyVar_maybe, isFilledMetaTyVar, zonkTyCoVarsAndFV, zonkTcType, zonkTcTypes, zonkTcTyVar, zonkCo, + zonkTyCoVarsAndFVList, zonkSimples, zonkWC, -- References @@ -2756,6 +2757,9 @@ isFilledMetaTyVar tv = wrapTcS (TcM.isFilledMetaTyVar tv) zonkTyCoVarsAndFV :: TcTyCoVarSet -> TcS TcTyCoVarSet zonkTyCoVarsAndFV tvs = wrapTcS (TcM.zonkTyCoVarsAndFV tvs) +zonkTyCoVarsAndFVList :: [TcTyCoVar] -> TcS [TcTyCoVar] +zonkTyCoVarsAndFVList tvs = wrapTcS (TcM.zonkTyCoVarsAndFVList tvs) + zonkCo :: Coercion -> TcS Coercion zonkCo = wrapTcS . TcM.zonkCo diff --git a/compiler/typecheck/TcSimplify.hs b/compiler/typecheck/TcSimplify.hs index e22a5f6..39923cf 100644 --- a/compiler/typecheck/TcSimplify.hs +++ b/compiler/typecheck/TcSimplify.hs @@ -130,9 +130,8 @@ simpl_top wanteds | isEmptyWC wc = return wc | otherwise - = do { free_tvs <- TcS.zonkTyCoVarsAndFV (tyCoVarsOfWC wc) - ; let meta_tvs = varSetElems $ - filterVarSet (isTyVar <&&> isMetaTyVar) free_tvs + = do { free_tvs <- TcS.zonkTyCoVarsAndFVList (tyCoVarsOfWCList wc) + ; let meta_tvs = filter (isTyVar <&&> isMetaTyVar) free_tvs -- zonkTyCoVarsAndFV: the wc_first_go is not yet zonked -- filter isMetaTyVar: we might have runtime-skolems in GHCi, -- and we definitely don't want to try to assign to those! From git at git.haskell.org Thu Jul 14 13:53:30 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 14 Jul 2016 13:53:30 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Make simplifyInstanceContexts deterministic (1523188) Message-ID: <20160714135330.E39823A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/15231881e40d9717ac9eb8b4e3381d27adfea7ba/ghc >--------------------------------------------------------------- commit 15231881e40d9717ac9eb8b4e3381d27adfea7ba Author: Bartosz Nitka Date: Tue May 10 05:32:28 2016 -0700 Make simplifyInstanceContexts deterministic simplifyInstanceContexts used cmpType which is nondeterministic for canonicalising typeclass constraints in derived instances. Following changes make it deterministic as explained by the Note [Deterministic simplifyInstanceContexts]. Test Plan: ./validate Reviewers: simonmar, goldfire, simonpj, austin, bgamari Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2173 GHC Trac Issues: #4012 >--------------------------------------------------------------- 15231881e40d9717ac9eb8b4e3381d27adfea7ba compiler/basicTypes/Unique.hs | 15 ++++++++------- compiler/basicTypes/Var.hs | 14 ++++++++++++-- compiler/typecheck/TcDeriv.hs | 31 ++++++++++++++++++++++++++++--- compiler/types/Type.hs | 16 ++++++++++++++-- 4 files changed, 62 insertions(+), 14 deletions(-) diff --git a/compiler/basicTypes/Unique.hs b/compiler/basicTypes/Unique.hs index ca74373..eddf265 100644 --- a/compiler/basicTypes/Unique.hs +++ b/compiler/basicTypes/Unique.hs @@ -23,7 +23,7 @@ module Unique ( Unique, Uniquable(..), -- ** Constructors, destructors and operations on 'Unique's - hasKey, cmpByUnique, + hasKey, pprUnique, @@ -35,6 +35,7 @@ module Unique ( deriveUnique, -- Ditto newTagUnique, -- Used in CgCase initTyVarUnique, + nonDetCmpUnique, -- ** Making built-in uniques @@ -168,9 +169,6 @@ instance Uniquable FastString where instance Uniquable Int where getUnique i = mkUniqueGrimily i -cmpByUnique :: Uniquable a => a -> a -> Ordering -cmpByUnique x y = (getUnique x) `cmpUnique` (getUnique y) - {- ************************************************************************ * * @@ -204,8 +202,11 @@ eqUnique (MkUnique u1) (MkUnique u2) = u1 == u2 ltUnique (MkUnique u1) (MkUnique u2) = u1 < u2 leUnique (MkUnique u1) (MkUnique u2) = u1 <= u2 -cmpUnique :: Unique -> Unique -> Ordering -cmpUnique (MkUnique u1) (MkUnique u2) +-- Provided here to make it explicit at the call-site that it can +-- introduce non-determinism. +-- See Note [Unique Determinism] +nonDetCmpUnique :: Unique -> Unique -> Ordering +nonDetCmpUnique (MkUnique u1) (MkUnique u2) = if u1 == u2 then EQ else if u1 < u2 then LT else GT instance Eq Unique where @@ -217,7 +218,7 @@ instance Ord Unique where a <= b = leUnique a b a > b = not (leUnique a b) a >= b = not (ltUnique a b) - compare a b = cmpUnique a b + compare a b = nonDetCmpUnique a b ----------------- instance Uniquable Unique where diff --git a/compiler/basicTypes/Var.hs b/compiler/basicTypes/Var.hs index d6bd609..c70a304 100644 --- a/compiler/basicTypes/Var.hs +++ b/compiler/basicTypes/Var.hs @@ -64,7 +64,9 @@ module Var ( -- ** Modifying 'TyVar's setTyVarName, setTyVarUnique, setTyVarKind, updateTyVarKind, - updateTyVarKindM + updateTyVarKindM, + + nonDetCmpVar ) where @@ -80,6 +82,7 @@ import Util import DynFlags import Outputable +import Unique (nonDetCmpUnique) import Data.Data {- @@ -269,7 +272,14 @@ instance Ord Var where a < b = realUnique a < realUnique b a >= b = realUnique a >= realUnique b a > b = realUnique a > realUnique b - a `compare` b = varUnique a `compare` varUnique b + a `compare` b = a `nonDetCmpVar` b + +-- | Compare Vars by their Uniques. +-- This is what Ord Var does, provided here to make it explicit at the +-- call-site that it can introduce non-determinism. +-- See Note [Unique Determinism] +nonDetCmpVar :: Var -> Var -> Ordering +nonDetCmpVar a b = varUnique a `nonDetCmpUnique` varUnique b instance Data Var where -- don't traverse? diff --git a/compiler/typecheck/TcDeriv.hs b/compiler/typecheck/TcDeriv.hs index c74b450..944c513 100644 --- a/compiler/typecheck/TcDeriv.hs +++ b/compiler/typecheck/TcDeriv.hs @@ -1862,6 +1862,29 @@ this by simplifying the RHS to a form in which - the list is sorted by tyvar (major key) and then class (minor key) - no duplicates, of course +Note [Deterministic simplifyInstanceContexts] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Canonicalisation uses cmpType which is nondeterministic. Sorting +with cmpType puts the returned lists in a nondeterministic order. +If we were to return them, we'd get class constraints in +nondeterministic order. + +Consider: + + data ADT a b = Z a b deriving Eq + +The generated code could be either: + + instance (Eq a, Eq b) => Eq (Z a b) where + +Or: + + instance (Eq b, Eq a) => Eq (Z a b) where + +To prevent the order from being nondeterministic we only +canonicalize when comparing and return them in the same order as +simplifyDeriv returned them. +See also Note [cmpType nondeterminism] -} @@ -1909,8 +1932,10 @@ simplifyInstanceContexts infer_specs else iterate_deriv (n+1) new_solns } - eqSolution = eqListBy (eqListBy eqType) - + eqSolution a b = eqListBy (eqListBy eqType) (canSolution a) (canSolution b) + -- Canonicalise for comparison + -- See Note [Deterministic simplifyInstanceContexts] + canSolution = map (sortBy cmpType) ------------------------------------------------------------------ gen_soln :: DerivSpec ThetaOrigin -> TcM ThetaType gen_soln (DS { ds_loc = loc, ds_tvs = tyvars @@ -1925,7 +1950,7 @@ simplifyInstanceContexts infer_specs -- Claim: the result instance declaration is guaranteed valid -- Hence no need to call: -- checkValidInstance tyvars theta clas inst_tys - ; return (sortBy cmpType theta) } -- Canonicalise before returning the solution + ; return theta } where the_pred = mkClassPred clas inst_tys diff --git a/compiler/types/Type.hs b/compiler/types/Type.hs index b4a123b..69cf69f 100644 --- a/compiler/types/Type.hs +++ b/compiler/types/Type.hs @@ -223,6 +223,7 @@ import FastString import Pair import ListSetOps import Digraph +import Unique ( nonDetCmpUnique ) import Maybes ( orElse ) import Data.Maybe ( isJust, mapMaybe ) @@ -2098,6 +2099,16 @@ eqVarBndrs _ _ _= Nothing -- Now here comes the real worker +{- +Note [cmpType nondeterminism] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +cmpType is implemented in terms of cmpTypeX. cmpTypeX uses cmpTc which +compares TyCons by their Unique value. Using Uniques for ordering leads +to nondeterminism. We hit the same problem in the TyVarTy case, comparing +type variables is nondeterministic, note the call to nonDetCmpVar in cmpTypeX. +See Note [Unique Determinism] for more details. +-} + cmpType :: Type -> Type -> Ordering cmpType t1 t2 -- we know k1 and k2 have the same kind, because they both have kind *. @@ -2160,7 +2171,7 @@ cmpTypeX env orig_t1 orig_t2 = | Just t2' <- coreViewOneStarKind t2 = go env t1 t2' go env (TyVarTy tv1) (TyVarTy tv2) - = liftOrdering $ rnOccL env tv1 `compare` rnOccR env tv2 + = liftOrdering $ rnOccL env tv1 `nonDetCmpVar` rnOccR env tv2 go env (ForAllTy (Named tv1 _) t1) (ForAllTy (Named tv2 _) t2) = go env (tyVarKind tv1) (tyVarKind tv2) `thenCmpTy` go (rnBndr2 env tv1 tv2) t1 t2 @@ -2211,10 +2222,11 @@ cmpTypesX _ _ [] = GT -- | Compare two 'TyCon's. NB: This should /never/ see the "star synonyms", -- as recognized by Kind.isStarKindSynonymTyCon. See Note -- [Kind Constraint and kind *] in Kind. +-- See Note [cmpType nondeterminism] cmpTc :: TyCon -> TyCon -> Ordering cmpTc tc1 tc2 = ASSERT( not (isStarKindSynonymTyCon tc1) && not (isStarKindSynonymTyCon tc2) ) - u1 `compare` u2 + u1 `nonDetCmpUnique` u2 where u1 = tyConUnique tc1 u2 = tyConUnique tc2 From git at git.haskell.org Thu Jul 14 13:53:33 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 14 Jul 2016 13:53:33 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Kill varSetElems in tcInferPatSynDecl (c93f3f8) Message-ID: <20160714135333.8D21B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/c93f3f87a895ef4bbe631ab4e5886460a0790dba/ghc >--------------------------------------------------------------- commit c93f3f87a895ef4bbe631ab4e5886460a0790dba Author: Bartosz Nitka Date: Mon May 16 03:27:53 2016 -0700 Kill varSetElems in tcInferPatSynDecl varSetElems introduces unnecessary non-determinism and while I didn't estabilish experimentally that this matters here I'm convinced that it will, because I expect pattern synonyms to end up in interface files. Test Plan: ./validate Reviewers: austin, simonmar, bgamari, mpickering, simonpj Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2206 GHC Trac Issues: #4012 >--------------------------------------------------------------- c93f3f87a895ef4bbe631ab4e5886460a0790dba compiler/typecheck/TcPatSyn.hs | 42 ++++++++++++++++++++++++++---------------- 1 file changed, 26 insertions(+), 16 deletions(-) diff --git a/compiler/typecheck/TcPatSyn.hs b/compiler/typecheck/TcPatSyn.hs index 633b8d6..3cf1a86 100644 --- a/compiler/typecheck/TcPatSyn.hs +++ b/compiler/typecheck/TcPatSyn.hs @@ -47,6 +47,7 @@ import FieldLabel import Bag import Util import ErrUtils +import FV import Control.Monad ( unless, zipWithM ) import Data.List( partition ) #if __GLASGOW_HASKELL__ < 709 @@ -219,9 +220,8 @@ tcInferPatSynDecl PSB{ psb_id = lname@(L _ name), psb_args = details, ; (qtvs, req_dicts, ev_binds) <- simplifyInfer tclvl False [] named_taus wanted - ; let (ex_vars, prov_dicts) = tcCollectEx lpat' + ; let ((ex_tvs, ex_vars), prov_dicts) = tcCollectEx lpat' univ_tvs = filter (not . (`elemVarSet` ex_vars)) qtvs - ex_tvs = varSetElems ex_vars prov_theta = map evVarPred prov_dicts req_theta = map evVarPred req_dicts @@ -948,34 +948,44 @@ nonBidirectionalErr name = failWithTc $ -- These are used in computing the type of a pattern synonym and also -- in generating matcher functions, since success continuations need -- to be passed these pattern-bound evidences. -tcCollectEx :: LPat Id -> (TyVarSet, [EvVar]) -tcCollectEx pat = go pat +tcCollectEx + :: LPat Id + -> ( ([Var], VarSet) -- Existentially-bound type variables as a + -- deterministically ordered list and a set. + -- See Note [Deterministic FV] in FV + , [EvVar] + ) +tcCollectEx pat = let (fv, evs) = go pat in (fvVarListVarSet fv, evs) where - go :: LPat Id -> (TyVarSet, [EvVar]) + go :: LPat Id -> (FV, [EvVar]) go = go1 . unLoc - go1 :: Pat Id -> (TyVarSet, [EvVar]) + go1 :: Pat Id -> (FV, [EvVar]) go1 (LazyPat p) = go p go1 (AsPat _ p) = go p go1 (ParPat p) = go p go1 (BangPat p) = go p - go1 (ListPat ps _ _) = mconcat . map go $ ps - go1 (TuplePat ps _ _) = mconcat . map go $ ps - go1 (PArrPat ps _) = mconcat . map go $ ps + go1 (ListPat ps _ _) = mergeMany . map go $ ps + go1 (TuplePat ps _ _) = mergeMany . map go $ ps + go1 (PArrPat ps _) = mergeMany . map go $ ps go1 (ViewPat _ p _) = go p - go1 con at ConPatOut{} = mappend (mkVarSet (pat_tvs con), pat_dicts con) $ + go1 con at ConPatOut{} = merge (FV.mkFVs (pat_tvs con), pat_dicts con) $ goConDetails $ pat_args con go1 (SigPatOut p _) = go p go1 (CoPat _ p _) = go1 p go1 (NPlusKPat n k _ geq subtract _) = pprPanic "TODO: NPlusKPat" $ ppr n $$ ppr k $$ ppr geq $$ ppr subtract - go1 _ = mempty + go1 _ = empty - goConDetails :: HsConPatDetails Id -> (TyVarSet, [EvVar]) - goConDetails (PrefixCon ps) = mconcat . map go $ ps - goConDetails (InfixCon p1 p2) = go p1 `mappend` go p2 + goConDetails :: HsConPatDetails Id -> (FV, [EvVar]) + goConDetails (PrefixCon ps) = mergeMany . map go $ ps + goConDetails (InfixCon p1 p2) = go p1 `merge` go p2 goConDetails (RecCon HsRecFields{ rec_flds = flds }) - = mconcat . map goRecFd $ flds + = mergeMany . map goRecFd $ flds - goRecFd :: LHsRecField Id (LPat Id) -> (TyVarSet, [EvVar]) + goRecFd :: LHsRecField Id (LPat Id) -> (FV, [EvVar]) goRecFd (L _ HsRecField{ hsRecFieldArg = p }) = go p + + merge (vs1, evs1) (vs2, evs2) = (vs1 `unionFV` vs2, evs1 ++ evs2) + mergeMany = foldr merge empty + empty = (emptyFV, []) From git at git.haskell.org Thu Jul 14 13:53:36 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 14 Jul 2016 13:53:36 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Kill varSetElemsWellScoped in quantifyTyVars (a2fdee3) Message-ID: <20160714135336.488C43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/a2fdee3cdaa3f37b8ea9a9b866ea68f59f8d470a/ghc >--------------------------------------------------------------- commit a2fdee3cdaa3f37b8ea9a9b866ea68f59f8d470a Author: Bartosz Nitka Date: Tue Apr 26 05:58:24 2016 -0700 Kill varSetElemsWellScoped in quantifyTyVars varSetElemsWellScoped introduces unnecessary non-determinism in inferred type signatures. Removing this instance required changing the representation of TcDepVars to use deterministic sets. This is the last occurence of varSetElemsWellScoped, allowing me to finally remove it. Test Plan: ./validate I will update the expected outputs when commiting, some reordering of type variables in types is expected. Reviewers: goldfire, simonpj, austin, bgamari Reviewed By: simonpj Subscribers: thomie, simonmar Differential Revision: https://phabricator.haskell.org/D2135 GHC Trac Issues: #4012 >--------------------------------------------------------------- a2fdee3cdaa3f37b8ea9a9b866ea68f59f8d470a compiler/basicTypes/VarSet.hs | 11 +++- compiler/typecheck/TcHsType.hs | 2 +- compiler/typecheck/TcMType.hs | 44 +++++++++---- compiler/typecheck/TcSimplify.hs | 39 ++++++++++-- compiler/typecheck/TcType.hs | 46 +++++++++----- compiler/types/Type.hs | 13 ++-- compiler/types/Type.hs-boot | 4 +- compiler/utils/UniqDFM.hs | 12 +++- compiler/utils/UniqDSet.hs | 8 ++- compiler/utils/UniqFM.hs | 5 +- .../tests/dependent/should_fail/T11334b.stderr | 6 +- testsuite/tests/driver/werror.stderr | 2 +- testsuite/tests/gadt/gadt13.stderr | 12 ++-- testsuite/tests/gadt/gadt7.stderr | 18 +++--- .../tests/ghci.debugger/scripts/break026.stdout | 20 +++--- testsuite/tests/ghci/scripts/T11524a.stdout | 2 +- testsuite/tests/ghci/scripts/T7587.stdout | 2 +- testsuite/tests/ghci/scripts/T7730.stdout | 4 +- testsuite/tests/ghci/scripts/T7939.stdout | 4 +- testsuite/tests/ghci/scripts/T8776.stdout | 2 +- .../indexed-types/should_compile/T3017.stderr | 2 +- .../indexed-types/should_compile/T8889.stderr | 2 +- .../tests/indexed-types/should_fail/T7354.stderr | 8 +-- .../tests/indexed-types/should_fail/T8518.stderr | 8 +-- testsuite/tests/module/mod71.stderr | 10 +-- testsuite/tests/module/mod72.stderr | 2 +- .../tests/parser/should_compile/read014.stderr | 2 +- .../tests/parser/should_fail/readFail003.stderr | 6 +- .../should_compile/ExtraConstraints3.stderr | 72 +++++++++++----------- .../partial-sigs/should_compile/NamedTyVar.stderr | 4 +- .../partial-sigs/should_compile/SkipMany.stderr | 2 +- .../partial-sigs/should_compile/T10438.stderr | 4 +- .../should_compile/UncurryNamed.stderr | 2 +- .../WarningWildcardInstantiations.stderr | 30 ++++----- .../tests/partial-sigs/should_fail/T10045.stderr | 12 ++-- .../should_fail/WildcardInstantiations.stderr | 28 ++++----- .../tests/patsyn/should_compile/T11213.stderr | 2 +- testsuite/tests/polykinds/T7438.stderr | 16 ++--- testsuite/tests/polykinds/T7524.stderr | 2 +- testsuite/tests/rename/should_fail/T2993.stderr | 2 +- .../tests/typecheck/should_compile/T10971a.stderr | 2 +- .../tests/typecheck/should_compile/tc141.stderr | 6 +- .../tests/typecheck/should_compile/tc168.stderr | 2 +- .../tests/typecheck/should_compile/tc231.stderr | 2 +- testsuite/tests/typecheck/should_fail/T5853.stderr | 24 ++++---- .../tests/typecheck/should_fail/T6018fail.stderr | 6 +- testsuite/tests/typecheck/should_fail/T7453.stderr | 18 +++--- testsuite/tests/typecheck/should_fail/T7734.stderr | 12 ++-- testsuite/tests/typecheck/should_fail/T8142.stderr | 2 +- testsuite/tests/typecheck/should_fail/T9109.stderr | 12 ++-- .../tests/typecheck/should_fail/tcfail004.stderr | 6 +- .../tests/typecheck/should_fail/tcfail033.stderr | 8 +-- .../tests/typecheck/should_fail/tcfail049.stderr | 2 +- .../tests/typecheck/should_fail/tcfail050.stderr | 2 +- .../tests/typecheck/should_fail/tcfail140.stderr | 4 +- .../tests/typecheck/should_fail/tcfail198.stderr | 8 +-- 56 files changed, 341 insertions(+), 247 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc a2fdee3cdaa3f37b8ea9a9b866ea68f59f8d470a From git at git.haskell.org Thu Jul 14 13:53:38 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 14 Jul 2016 13:53:38 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Remove some varSetElems in dsCmdStmt (3bf8340) Message-ID: <20160714135338.E5F253A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/3bf83403b77cc95e2bb32f8556a7c1b4ab4eab67/ghc >--------------------------------------------------------------- commit 3bf83403b77cc95e2bb32f8556a7c1b4ab4eab67 Author: Bartosz Nitka Date: Wed May 11 07:47:15 2016 -0700 Remove some varSetElems in dsCmdStmt varSetElems introduces unnecessary determinism and it's easy to preserve determinism here. Test Plan: ./validate Reviewers: goldfire, simonmar, austin, bgamari, simonpj Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2195 GHC Trac Issues: #4012 >--------------------------------------------------------------- 3bf83403b77cc95e2bb32f8556a7c1b4ab4eab67 compiler/deSugar/DsArrows.hs | 8 +++++--- 1 file changed, 5 insertions(+), 3 deletions(-) diff --git a/compiler/deSugar/DsArrows.hs b/compiler/deSugar/DsArrows.hs index ea10b74..cdf839a 100644 --- a/compiler/deSugar/DsArrows.hs +++ b/compiler/deSugar/DsArrows.hs @@ -48,6 +48,7 @@ import VarSet import SrcLoc import ListSetOps( assocDefault ) import Data.List +import Util data DsCmdEnv = DsCmdEnv { arr_id, compose_id, first_id, app_id, choice_id, loop_id :: CoreExpr @@ -786,7 +787,7 @@ dsCmdStmt ids local_vars out_ids (BindStmt pat cmd _ _ _) env_ids = do (core_cmd, fv_cmd, env_ids1) <- dsfixCmd ids local_vars unitTy pat_ty cmd let pat_vars = mkVarSet (collectPatBinders pat) let - env_ids2 = varSetElems (mkVarSet out_ids `minusVarSet` pat_vars) + env_ids2 = filterOut (`elemVarSet` pat_vars) out_ids env_ty2 = mkBigCoreVarTupTy env_ids2 -- multiplexing function @@ -863,8 +864,9 @@ dsCmdStmt ids local_vars out_ids , recS_later_rets = later_rets, recS_rec_rets = rec_rets }) env_ids = do let - env2_id_set = mkVarSet out_ids `minusVarSet` mkVarSet later_ids - env2_ids = varSetElems env2_id_set + later_ids_set = mkVarSet later_ids + env2_ids = filterOut (`elemVarSet` later_ids_set) out_ids + env2_id_set = mkVarSet env2_ids env2_ty = mkBigCoreVarTupTy env2_ids -- post_loop_fn = \((later_ids),(env2_ids)) -> (out_ids) From git at git.haskell.org Thu Jul 14 13:53:41 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 14 Jul 2016 13:53:41 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Kill varSetElems in markNominal (352391e) Message-ID: <20160714135341.92A933A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/352391e779365f5598a4c4422e24bcd0279d7dc8/ghc >--------------------------------------------------------------- commit 352391e779365f5598a4c4422e24bcd0279d7dc8 Author: Bartosz Nitka Date: Tue Apr 26 13:04:08 2016 -0700 Kill varSetElems in markNominal varSetElems introduces unnecessary nondeterminism and it was straighforward to just get a deterministic list. Test Plan: ./validate Reviewers: austin, goldfire, bgamari, simonmar, simonpj Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2145 GHC Trac Issues: #4012 >--------------------------------------------------------------- 352391e779365f5598a4c4422e24bcd0279d7dc8 compiler/typecheck/TcTyDecls.hs | 21 +++++++++++---------- compiler/types/TyCoRep.hs | 2 +- 2 files changed, 12 insertions(+), 11 deletions(-) diff --git a/compiler/typecheck/TcTyDecls.hs b/compiler/typecheck/TcTyDecls.hs index a4b6537..53b1c08 100644 --- a/compiler/typecheck/TcTyDecls.hs +++ b/compiler/typecheck/TcTyDecls.hs @@ -31,7 +31,7 @@ module TcTyDecls( import TcRnMonad import TcEnv import TcBinds( tcRecSelBinds ) -import TyCoRep( Type(..), TyBinder(..), delBinderVar ) +import TyCoRep( Type(..), TyBinder(..), delBinderVarFV ) import TcType import TysWiredIn( unitTy ) import MkCore( rEC_SEL_ERROR_ID ) @@ -61,6 +61,7 @@ import Maybes import Data.List import Bag import FastString +import FV import Control.Monad @@ -726,21 +727,21 @@ irExTyVars orig_tvs thing = go emptyVarSet orig_tvs markNominal :: TyVarSet -- local variables -> Type -> RoleM () -markNominal lcls ty = let nvars = get_ty_vars ty `minusVarSet` lcls in - mapM_ (updateRole Nominal) (varSetElems nvars) +markNominal lcls ty = let nvars = fvVarList (FV.delFVs lcls $ get_ty_vars ty) in + mapM_ (updateRole Nominal) nvars where -- get_ty_vars gets all the tyvars (no covars!) from a type *without* -- recurring into coercions. Recall: coercions are totally ignored during -- role inference. See [Coercions in role inference] - get_ty_vars (TyVarTy tv) = unitVarSet tv - get_ty_vars (AppTy t1 t2) = get_ty_vars t1 `unionVarSet` get_ty_vars t2 - get_ty_vars (TyConApp _ tys) = foldr (unionVarSet . get_ty_vars) emptyVarSet tys + get_ty_vars (TyVarTy tv) = FV.unitFV tv + get_ty_vars (AppTy t1 t2) = get_ty_vars t1 `unionFV` get_ty_vars t2 + get_ty_vars (TyConApp _ tys) = mapUnionFV get_ty_vars tys get_ty_vars (ForAllTy bndr ty) - = get_ty_vars ty `delBinderVar` bndr - `unionVarSet` (tyCoVarsOfType $ binderType bndr) - get_ty_vars (LitTy {}) = emptyVarSet + = delBinderVarFV bndr (get_ty_vars ty) + `unionFV` (tyCoFVsOfType $ binderType bndr) + get_ty_vars (LitTy {}) = emptyFV get_ty_vars (CastTy ty _) = get_ty_vars ty - get_ty_vars (CoercionTy _) = emptyVarSet + get_ty_vars (CoercionTy _) = emptyFV -- like lookupRoles, but with Nominal tags at the end for oversaturated TyConApps lookupRolesX :: TyCon -> RoleM [Role] diff --git a/compiler/types/TyCoRep.hs b/compiler/types/TyCoRep.hs index 7054ed5..59799e1 100644 --- a/compiler/types/TyCoRep.hs +++ b/compiler/types/TyCoRep.hs @@ -45,7 +45,7 @@ module TyCoRep ( -- Functions over binders binderType, delBinderVar, isInvisibleBinder, isVisibleBinder, - isNamedBinder, isAnonBinder, + isNamedBinder, isAnonBinder, delBinderVarFV, -- Functions over coercions pickLR, From git at git.haskell.org Thu Jul 14 13:53:44 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 14 Jul 2016 13:53:44 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Make accept (1f07ade) Message-ID: <20160714135344.5B32A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/1f07ade0366fa5c018be271ff9d8ef376db4bcb8/ghc >--------------------------------------------------------------- commit 1f07ade0366fa5c018be271ff9d8ef376db4bcb8 Author: Bartosz Nitka Date: Mon May 16 12:47:25 2016 -0700 Make accept Summary: Test Plan: Reviewers: Subscribers: Tasks: Blame Revision: >--------------------------------------------------------------- 1f07ade0366fa5c018be271ff9d8ef376db4bcb8 testsuite/tests/ado/ado004.stderr | 16 +- testsuite/tests/determinism/determ007/A.hs | 3 + testsuite/tests/determinism/determ007/Makefile | 13 ++ testsuite/tests/determinism/determ007/all.T | 4 + .../determ007.stdout} | 0 testsuite/tests/determinism/determ008/A.hs | 3 + testsuite/tests/determinism/determ008/Makefile | 13 ++ testsuite/tests/determinism/determ008/all.T | 4 + .../determ008.stdout} | 0 testsuite/tests/determinism/determ009/A.hs | 4 + testsuite/tests/determinism/determ009/Makefile | 13 ++ testsuite/tests/determinism/determ009/all.T | 4 + .../determ009.stdout} | 0 testsuite/tests/determinism/determ011/A.hs | 26 +++ testsuite/tests/determinism/determ011/Makefile | 13 ++ testsuite/tests/determinism/determ011/all.T | 4 + .../determ011.stdout} | 0 testsuite/tests/determinism/determ012/A.hs | 10 + testsuite/tests/determinism/determ012/Makefile | 13 ++ testsuite/tests/determinism/determ012/all.T | 4 + .../tests/determinism/determ012/determ012.stdout | 2 + testsuite/tests/determinism/determ013/A.hs | 19 ++ testsuite/tests/determinism/determ013/Makefile | 13 ++ testsuite/tests/determinism/determ013/all.T | 4 + .../tests/determinism/determ013/determ013.stdout | 2 + .../T10934.hs => determinism/determ014/A.hs} | 0 testsuite/tests/determinism/determ014/Makefile | 13 ++ testsuite/tests/determinism/determ014/all.T | 4 + .../tests/determinism/determ014/determ014.stdout | 2 + testsuite/tests/determinism/determ015/A.hs | 59 ++++++ testsuite/tests/determinism/determ015/Makefile | 13 ++ testsuite/tests/determinism/determ015/all.T | 4 + .../determ015.stdout} | 0 testsuite/tests/determinism/determ016/A.hs | 19 ++ testsuite/tests/determinism/determ016/Makefile | 13 ++ testsuite/tests/determinism/determ016/all.T | 4 + .../determ016.stdout} | 0 testsuite/tests/determinism/determ017/A.hs | 215 +++++++++++++++++++++ testsuite/tests/determinism/determ017/Makefile | 13 ++ testsuite/tests/determinism/determ017/all.T | 4 + .../determ017.stdout} | 0 .../tests/ghci.debugger/scripts/break006.stderr | 4 +- testsuite/tests/ghci/scripts/T6018ghcifail.stderr | 4 +- testsuite/tests/typecheck/should_fail/T5095.stderr | 2 +- .../typecheck/should_fail/T6018failclosed.stderr | 144 +++++++------- .../tests/typecheck/should_fail/tcfail133.stderr | 2 +- 46 files changed, 620 insertions(+), 86 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 1f07ade0366fa5c018be271ff9d8ef376db4bcb8 From git at git.haskell.org Thu Jul 14 13:53:47 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 14 Jul 2016 13:53:47 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Refactor validity checking for type/data instances (308c21f) Message-ID: <20160714135347.0FD093A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/308c21fc4c3cf08854d186c10963c51eab5c3db7/ghc >--------------------------------------------------------------- commit 308c21fc4c3cf08854d186c10963c51eab5c3db7 Author: Simon Peyton Jones Date: Fri Jan 22 16:40:55 2016 +0000 Refactor validity checking for type/data instances I found that there was some code duplication going on, so I've put more into the shared function checkValidFamPats. I did some refactoring in checkConsistentFamInst too, preparatory to #11450; the error messages change a little but no change in behaviour. >--------------------------------------------------------------- 308c21fc4c3cf08854d186c10963c51eab5c3db7 compiler/typecheck/TcInstDcls.hs | 9 +- compiler/typecheck/TcTyClsDecls.hs | 2 + compiler/typecheck/TcValidity.hs | 154 ++++++++++++--------- .../indexed-types/should_fail/SimpleFail2a.stderr | 11 +- 4 files changed, 101 insertions(+), 75 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 308c21fc4c3cf08854d186c10963c51eab5c3db7 From git at git.haskell.org Thu Jul 14 13:53:49 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 14 Jul 2016 13:53:49 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Make inert_model and inert_eqs deterministic sets (6b079a2) Message-ID: <20160714135349.BBB703A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/6b079a206c1ead10fe0e9c169b3250a79f01549c/ghc >--------------------------------------------------------------- commit 6b079a206c1ead10fe0e9c169b3250a79f01549c Author: Bartosz Nitka Date: Tue May 17 05:45:43 2016 -0700 Make inert_model and inert_eqs deterministic sets The order inert_model and intert_eqs fold affects the order that the typechecker looks at things. I've been able to experimentally confirm that the order of equalities and the order of the model matter for determinism. This is just a straigthforward replacement of nondeterministic VarEnv for deterministic DVarEnv. Test Plan: ./validate Reviewers: simonpj, goldfire, austin, bgamari, simonmar Reviewed By: simonmar Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2232 GHC Trac Issues: #4012 >--------------------------------------------------------------- 6b079a206c1ead10fe0e9c169b3250a79f01549c compiler/basicTypes/VarEnv.hs | 28 +++++++++-- compiler/typecheck/TcFlatten.hs | 4 +- compiler/typecheck/TcInteract.hs | 2 +- compiler/typecheck/TcSMonad.hs | 58 +++++++++++----------- compiler/utils/UniqDFM.hs | 22 +++++++- .../tests/indexed-types/should_fail/T3330a.stderr | 5 +- .../tests/indexed-types/should_fail/T4174.stderr | 4 +- .../tests/indexed-types/should_fail/T4179.stderr | 6 +-- .../tests/indexed-types/should_fail/T9662.stderr | 4 +- testsuite/tests/polykinds/T9017.stderr | 4 +- testsuite/tests/typecheck/should_fail/T7869.stderr | 8 ++- 11 files changed, 93 insertions(+), 52 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 6b079a206c1ead10fe0e9c169b3250a79f01549c From git at git.haskell.org Thu Jul 14 13:53:52 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 14 Jul 2016 13:53:52 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Kill varSetElems in tidyFreeTyCoVars (97036fe) Message-ID: <20160714135352.6EC253A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/97036fe7d86e0532784170a2805f362f5a58a309/ghc >--------------------------------------------------------------- commit 97036fe7d86e0532784170a2805f362f5a58a309 Author: Bartosz Nitka Date: Wed May 18 10:36:49 2016 -0700 Kill varSetElems in tidyFreeTyCoVars I haven't observed this to have an effect on nondeterminism, but tidyOccName appears to modify the TidyOccEnv in a way dependent on the order of inputs. It's easy enough to change it to be deterministic to be on the safe side. Test Plan: ./validate Reviewers: simonmar, austin, bgamari, simonpj Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2238 GHC Trac Issues: #4012 >--------------------------------------------------------------- 97036fe7d86e0532784170a2805f362f5a58a309 compiler/typecheck/TcErrors.hs | 8 +- compiler/typecheck/TcRnMonad.hs | 2 +- compiler/typecheck/TcValidity.hs | 10 +- compiler/types/TyCoRep.hs | 8 +- .../tests/indexed-types/should_fail/T2693.stderr | 4 +- .../should_fail/overloadedlabelsfail01.stderr | 46 ++-- testsuite/tests/parser/should_fail/T7848.stderr | 4 +- testsuite/tests/rename/should_fail/T10618.stderr | 2 +- .../tests/typecheck/should_fail/T11355.stderr | 2 +- testsuite/tests/typecheck/should_fail/T5684.stderr | 286 ++++++++++----------- testsuite/tests/typecheck/should_fail/T7851.stderr | 4 +- .../tests/typecheck/should_fail/tcfail001.stderr | 2 +- 12 files changed, 189 insertions(+), 189 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 97036fe7d86e0532784170a2805f362f5a58a309 From git at git.haskell.org Thu Jul 14 13:53:55 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 14 Jul 2016 13:53:55 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Implement deterministic CallInfoSet (b46513d) Message-ID: <20160714135355.2717C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/b46513d224e527f3d4bbf829c802a2a394ce3b88/ghc >--------------------------------------------------------------- commit b46513d224e527f3d4bbf829c802a2a394ce3b88 Author: Bartosz Nitka Date: Mon Jun 6 04:36:21 2016 -0700 Implement deterministic CallInfoSet We need CallInfoSet to be deterministic because it determines the order that the binds get generated. Currently it's not deterministic because it's keyed on `CallKey = [Maybe Type]` and `Ord CallKey` is implemented with `cmpType` which is nondeterministic. See Note [CallInfoSet determinism] for more details. Test Plan: ./validate Reviewers: simonpj, bgamari, austin, simonmar Reviewed By: simonmar Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2242 GHC Trac Issues: #4012 >--------------------------------------------------------------- b46513d224e527f3d4bbf829c802a2a394ce3b88 compiler/specialise/Specialise.hs | 111 +++++++++++++++++++++++++------------- 1 file changed, 74 insertions(+), 37 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc b46513d224e527f3d4bbf829c802a2a394ce3b88 From git at git.haskell.org Thu Jul 14 13:53:58 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 14 Jul 2016 13:53:58 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Make Arrow desugaring deterministic (aff7cee) Message-ID: <20160714135358.E8B113A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/aff7cee7637f5f3f0fcfbd4817c96dd96001fecb/ghc >--------------------------------------------------------------- commit aff7cee7637f5f3f0fcfbd4817c96dd96001fecb Author: Bartosz Nitka Date: Tue May 24 04:44:37 2016 -0700 Make Arrow desugaring deterministic This kills two instances of varSetElems that turned out to be nondeterministic. I've tried to untangle this before, but it's a bit hard with the fixDs in the middle. Fortunately I now have a test case that proves that we need determinism here. Test Plan: ./validate, new testcase Reviewers: simonpj, simonmar, austin, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2258 GHC Trac Issues: #4012 >--------------------------------------------------------------- aff7cee7637f5f3f0fcfbd4817c96dd96001fecb compiler/coreSyn/CoreFVs.hs | 33 ++++++++++++ compiler/deSugar/DsArrows.hs | 63 +++++++++++----------- compiler/utils/UniqDFM.hs | 7 ++- testsuite/tests/determinism/determ018/A.hs | 32 +++++++++++ .../determinism/{determ013 => determ018}/Makefile | 2 +- .../determinism/{determ009 => determ018}/all.T | 4 +- .../determ018.stdout} | 0 7 files changed, 106 insertions(+), 35 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc aff7cee7637f5f3f0fcfbd4817c96dd96001fecb From git at git.haskell.org Thu Jul 14 13:54:01 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 14 Jul 2016 13:54:01 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Serialize vParallelTyCons in a stable order (69d2fdc) Message-ID: <20160714135401.AEB493A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/69d2fdc1f6568956a131b40a35af8443ce58551d/ghc >--------------------------------------------------------------- commit 69d2fdc1f6568956a131b40a35af8443ce58551d Author: Bartosz Nitka Date: Thu Jun 2 09:51:04 2016 -0700 Serialize vParallelTyCons in a stable order nameSetElems can introduce nondeterminism and while I haven't observed this being a problem in practice (possibly because this is dead code) there's no downside to doing this. Test Plan: ./validate Reviewers: bgamari, austin, simonpj, simonmar Reviewed By: simonmar Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2296 GHC Trac Issues: #4012 >--------------------------------------------------------------- 69d2fdc1f6568956a131b40a35af8443ce58551d compiler/iface/MkIface.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/iface/MkIface.hs b/compiler/iface/MkIface.hs index 1a31afd..1b9570c 100644 --- a/compiler/iface/MkIface.hs +++ b/compiler/iface/MkIface.hs @@ -326,7 +326,7 @@ mkIface_ hsc_env maybe_old_fingerprint , ifaceVectInfoTyCon = [tyConName t | (t, t_v) <- nameEnvElts vTyCon, t /= t_v] , ifaceVectInfoTyConReuse = [tyConName t | (t, t_v) <- nameEnvElts vTyCon, t == t_v] , ifaceVectInfoParallelVars = [Var.varName v | v <- varSetElems vParallelVars] - , ifaceVectInfoParallelTyCons = nameSetElems vParallelTyCons + , ifaceVectInfoParallelTyCons = nameSetElemsStable vParallelTyCons } ----------------------------- From git at git.haskell.org Thu Jul 14 13:54:04 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 14 Jul 2016 13:54:04 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Add nameSetElemsStable and fix the build (c07b619) Message-ID: <20160714135404.587B33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/c07b61978fed55faec7b910155964a785e8b52a1/ghc >--------------------------------------------------------------- commit c07b61978fed55faec7b910155964a785e8b52a1 Author: Bartosz Nitka Date: Thu Jun 2 10:34:57 2016 -0700 Add nameSetElemsStable and fix the build >--------------------------------------------------------------- c07b61978fed55faec7b910155964a785e8b52a1 compiler/basicTypes/NameSet.hs | 11 +++++++++++ compiler/utils/UniqFM.hs | 6 +++++- 2 files changed, 16 insertions(+), 1 deletion(-) diff --git a/compiler/basicTypes/NameSet.hs b/compiler/basicTypes/NameSet.hs index 7bca479..b764bd9 100644 --- a/compiler/basicTypes/NameSet.hs +++ b/compiler/basicTypes/NameSet.hs @@ -13,6 +13,7 @@ module NameSet ( minusNameSet, elemNameSet, nameSetElems, extendNameSet, extendNameSetList, delFromNameSet, delListFromNameSet, isEmptyNameSet, foldNameSet, filterNameSet, intersectsNameSet, intersectNameSet, + nameSetElemsStable, -- * Free variables FreeVars, @@ -33,6 +34,8 @@ module NameSet ( import Name import UniqSet +import UniqFM +import Data.List (sortBy) {- ************************************************************************ @@ -84,6 +87,14 @@ delListFromNameSet set ns = foldl delFromNameSet set ns intersectsNameSet s1 s2 = not (isEmptyNameSet (s1 `intersectNameSet` s2)) +-- | Get the elements of a NameSet with some stable ordering. +-- See Note [Deterministic UniqFM] to learn about nondeterminism +nameSetElemsStable :: NameSet -> [Name] +nameSetElemsStable ns = + sortBy stableNameCmp $ nonDetEltsUFM ns + -- It's OK to use nonDetEltsUFM here because we immediately sort + -- with stableNameCmp + {- ************************************************************************ * * diff --git a/compiler/utils/UniqFM.hs b/compiler/utils/UniqFM.hs index 0df5a2d..0056287 100644 --- a/compiler/utils/UniqFM.hs +++ b/compiler/utils/UniqFM.hs @@ -64,7 +64,7 @@ module UniqFM ( isNullUFM, lookupUFM, lookupUFM_Directly, lookupWithDefaultUFM, lookupWithDefaultUFM_Directly, - eltsUFM, keysUFM, splitUFM, + eltsUFM, keysUFM, splitUFM, nonDetEltsUFM, ufmToSet_Directly, ufmToList, ufmToIntMap, joinUFM, pprUniqFM, pprUFM, pluralUFM @@ -304,6 +304,10 @@ ufmToList (UFM m) = map (\(k, v) -> (getUnique k, v)) $ M.toList m ufmToIntMap :: UniqFM elt -> M.IntMap elt ufmToIntMap (UFM m) = m +-- See Note [Deterministic UniqFM] to learn about nondeterminism +nonDetEltsUFM :: UniqFM elt -> [elt] +nonDetEltsUFM (UFM m) = M.elems m + -- Hoopl joinUFM :: JoinFun v -> JoinFun (UniqFM v) joinUFM eltJoin l (OldFact old) (NewFact new) = foldUFM_Directly add (NoChange, old) new From git at git.haskell.org Thu Jul 14 13:54:07 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 14 Jul 2016 13:54:07 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Add -foptimal-applicative-do (4a93d25) Message-ID: <20160714135407.964AE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/4a93d258b3948610e5389432af7c3d041cebbc87/ghc >--------------------------------------------------------------- commit 4a93d258b3948610e5389432af7c3d041cebbc87 Author: Simon Marlow Date: Fri Mar 4 13:06:42 2016 +0000 Add -foptimal-applicative-do Summary: The algorithm for ApplicativeDo rearrangement is based on a heuristic that runs in O(n^2). This patch adds the optimal algorithm, which is O(n^3), selected by a flag (-foptimal-applicative-do). It finds better solutions in a small number of cases (about 2% of the cases where ApplicativeDo makes a difference), but it can be very slow for large do expressions. I'm mainly adding it for experimental reasons. ToDo: user guide docs Test Plan: validate Reviewers: simonpj, bgamari, austin, niteria, erikd Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1969 >--------------------------------------------------------------- 4a93d258b3948610e5389432af7c3d041cebbc87 compiler/main/DynFlags.hs | 2 + compiler/rename/RnExpr.hs | 226 ++++++++++++++++--------- docs/users_guide/glasgow_exts.rst | 17 ++ testsuite/tests/ado/ado-optimal.hs | 59 +++++++ testsuite/tests/ado/ado-optimal.stdout | 1 + testsuite/tests/ado/ado004.hs | 9 + testsuite/tests/ado/ado004.stderr | 6 + testsuite/tests/ado/all.T | 1 + utils/mkUserGuidePart/Options/Optimizations.hs | 6 + 9 files changed, 251 insertions(+), 76 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 4a93d258b3948610e5389432af7c3d041cebbc87 From git at git.haskell.org Thu Jul 14 13:54:11 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 14 Jul 2016 13:54:11 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Desugar ApplicativeDo and RecDo deterministically (f7e6362) Message-ID: <20160714135411.8FAD13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/f7e63623c93f6f344fbcde75dcc557ebe356e8d0/ghc >--------------------------------------------------------------- commit f7e63623c93f6f344fbcde75dcc557ebe356e8d0 Author: Bartosz Nitka Date: Mon Jun 6 06:08:54 2016 -0700 Desugar ApplicativeDo and RecDo deterministically This fixes a problem described in Note [Deterministic ApplicativeDo and RecursiveDo desugaring]. Test Plan: ./validate + new testcase Reviewers: simonpj, bgamari, austin, simonmar Reviewed By: simonmar Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2287 GHC Trac Issues: #4012 >--------------------------------------------------------------- f7e63623c93f6f344fbcde75dcc557ebe356e8d0 compiler/basicTypes/Name.hs | 4 +- compiler/basicTypes/NameSet.hs | 2 + compiler/rename/RnExpr.hs | 43 +++++++++++++--- testsuite/tests/determinism/determ019/A.hs | 57 ++++++++++++++++++++++ .../determinism/{determ013 => determ019}/Makefile | 2 +- .../determinism/{determ007 => determ019}/all.T | 4 +- .../determ019.stdout} | 0 7 files changed, 101 insertions(+), 11 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc f7e63623c93f6f344fbcde75dcc557ebe356e8d0 From git at git.haskell.org Thu Jul 14 13:54:14 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 14 Jul 2016 13:54:14 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Use DVarSet in Vectorise.Exp (2aa7a22) Message-ID: <20160714135414.7A6043A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/2aa7a225841fc0369736f42abacd4afe2db4984f/ghc >--------------------------------------------------------------- commit 2aa7a225841fc0369736f42abacd4afe2db4984f Author: Bartosz Nitka Date: Tue Jun 7 06:28:51 2016 -0700 Use DVarSet in Vectorise.Exp I believe this part of code is a bit unused. That's probably why it never became a problem in my testing. I'm changing to deterministic sets here to be safer. Test Plan: ./validate Reviewers: simonmar, austin, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2312 GHC Trac Issues: #4012 >--------------------------------------------------------------- 2aa7a225841fc0369736f42abacd4afe2db4984f compiler/vectorise/Vectorise/Exp.hs | 53 ++++++++++++++++++------------------- 1 file changed, 26 insertions(+), 27 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 2aa7a225841fc0369736f42abacd4afe2db4984f From git at git.haskell.org Thu Jul 14 13:54:17 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 14 Jul 2016 13:54:17 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Make vectInfoParallelVars a DVarSet (d639251) Message-ID: <20160714135417.551E23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/d639251c7a13a488947a7f96ce707cbcb446f124/ghc >--------------------------------------------------------------- commit d639251c7a13a488947a7f96ce707cbcb446f124 Author: Bartosz Nitka Date: Tue Jun 7 07:19:30 2016 -0700 Make vectInfoParallelVars a DVarSet We dump it in the interface file, so we need to do it in a deterministic order. I haven't seen any problems with this during my testing, but that's probably because it's unused. Test Plan: ./validate Reviewers: simonmar, austin, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2313 GHC Trac Issues: #4012 >--------------------------------------------------------------- d639251c7a13a488947a7f96ce707cbcb446f124 compiler/iface/MkIface.hs | 2 +- compiler/iface/TcIface.hs | 2 +- compiler/main/HscTypes.hs | 6 +++--- compiler/main/TidyPgm.hs | 11 ++++++----- compiler/vectorise/Vectorise/Env.hs | 7 ++++--- compiler/vectorise/Vectorise/Exp.hs | 4 ++-- compiler/vectorise/Vectorise/Monad.hs | 2 +- compiler/vectorise/Vectorise/Monad/Global.hs | 2 +- 8 files changed, 19 insertions(+), 17 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc d639251c7a13a488947a7f96ce707cbcb446f124 From git at git.haskell.org Thu Jul 14 13:54:20 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 14 Jul 2016 13:54:20 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Make UnitIdMap a deterministic map (16b7376) Message-ID: <20160714135420.35E123A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/16b73765e2a156366ef8f14fc39bcdea991a65d4/ghc >--------------------------------------------------------------- commit 16b73765e2a156366ef8f14fc39bcdea991a65d4 Author: Bartosz Nitka Date: Mon Jun 6 08:54:17 2016 -0700 Make UnitIdMap a deterministic map This impacts at least the order in which version macros are generated. It's pretty hard to track what kind of nondeterminism is benign and this should have no performance impact as the number of packages should be relatively small. Test Plan: ./validate Reviewers: simonmar, austin, bgamari, ezyang Reviewed By: ezyang Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2308 GHC Trac Issues: #4012 >--------------------------------------------------------------- 16b73765e2a156366ef8f14fc39bcdea991a65d4 compiler/main/Packages.hs | 53 ++++++++++++++++++++++++----------------------- compiler/utils/UniqDFM.hs | 7 ++++++- 2 files changed, 33 insertions(+), 27 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 16b73765e2a156366ef8f14fc39bcdea991a65d4 From git at git.haskell.org Thu Jul 14 13:54:22 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 14 Jul 2016 13:54:22 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Use UniqFM for SigOf (94cd5c4) Message-ID: <20160714135422.E106E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/94cd5c4fba764405899784e96ca391e5cf24028b/ghc >--------------------------------------------------------------- commit 94cd5c4fba764405899784e96ca391e5cf24028b Author: Bartosz Nitka Date: Mon Jun 13 07:35:32 2016 -0700 Use UniqFM for SigOf Summary: The Ord instance for ModuleName is currently implemented in terms of Uniques causing potential determinism problems. I plan to change it to use the actual FastStrings and in preparation for that I'm switching to UniqFM where it's possible (you need *one* Unique per key, and you can't get the keys back), so that the performance doesn't suffer. Test Plan: ./validate Reviewers: simonmar, austin, ezyang, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2320 GHC Trac Issues: #4012 >--------------------------------------------------------------- 94cd5c4fba764405899784e96ca391e5cf24028b compiler/main/DynFlags.hs | 9 +++++---- 1 file changed, 5 insertions(+), 4 deletions(-) diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index f6598b9..0a944b7 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -164,6 +164,7 @@ import CmdLineParser import Constants import Panic import Util +import UniqFM import Maybes import MonadUtils import qualified Pretty @@ -629,10 +630,10 @@ instance Show SafeHaskellMode where instance Outputable SafeHaskellMode where ppr = text . show -type SigOf = Map ModuleName Module +type SigOf = ModuleNameEnv Module getSigOf :: DynFlags -> ModuleName -> Maybe Module -getSigOf dflags n = Map.lookup n (sigOf dflags) +getSigOf dflags n = lookupUFM (sigOf dflags) n -- | Contains not only a collection of 'GeneralFlag's but also a plethora of -- information relating to the compilation of a single file or GHC session @@ -1438,7 +1439,7 @@ defaultDynFlags mySettings = ghcMode = CompManager, ghcLink = LinkBinary, hscTarget = defaultHscTarget (sTargetPlatform mySettings), - sigOf = Map.empty, + sigOf = emptyUFM, verbosity = 0, optLevel = 0, debugLevel = 0, @@ -1981,7 +1982,7 @@ parseSigOf :: String -> SigOf parseSigOf str = case filter ((=="").snd) (readP_to_S parse str) of [(r, "")] -> r _ -> throwGhcException $ CmdLineError ("Can't parse -sig-of: " ++ str) - where parse = Map.fromList <$> sepBy parseEntry (R.char ',') + where parse = listToUFM <$> sepBy parseEntry (R.char ',') parseEntry = do n <- tok $ parseModuleName -- ToDo: deprecate this 'is' syntax? From git at git.haskell.org Thu Jul 14 13:54:25 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 14 Jul 2016 13:54:25 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Make checkFamInstConsistency less expensive (770fafe) Message-ID: <20160714135425.A047A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/770fafe7b31df6d933d17587131e524179b91e79/ghc >--------------------------------------------------------------- commit 770fafe7b31df6d933d17587131e524179b91e79 Author: Bartosz Nitka Date: Tue Jun 21 15:54:00 2016 -0700 Make checkFamInstConsistency less expensive Doing canonicalization on every comparison turned out to be very expensive. Caching the canonicalization through the smart `modulePair` constructor gives `8%` reduction in allocations on `haddock.compiler` and `8.5%` reduction in allocations on `haddock.Cabal`. Possibly other things as well, but it's really visible in Haddock. Test Plan: ./validate Reviewers: jstolarek, simonpj, austin, simonmar, bgamari Reviewed By: simonpj, simonmar Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2350 GHC Trac Issues: #12191 >--------------------------------------------------------------- 770fafe7b31df6d933d17587131e524179b91e79 compiler/typecheck/FamInst.hs | 32 +++++++++++++++----------------- testsuite/tests/perf/haddock/all.T | 10 ++++++++-- 2 files changed, 23 insertions(+), 19 deletions(-) diff --git a/compiler/typecheck/FamInst.hs b/compiler/typecheck/FamInst.hs index 1d9e1ce..784bc81 100644 --- a/compiler/typecheck/FamInst.hs +++ b/compiler/typecheck/FamInst.hs @@ -40,8 +40,8 @@ import Pair import Panic import VarSet import Control.Monad -import Data.Map (Map) -import qualified Data.Map as Map +import Data.Set (Set) +import qualified Data.Set as Set #if __GLASGOW_HASKELL__ < 709 import Prelude hiding ( and ) @@ -124,28 +124,25 @@ certain that the modules in our `HscTypes.dep_finsts' are consistent.) -- whose family instances need to be checked for consistency. -- data ModulePair = ModulePair Module Module + -- Invariant: first Module < second Module + -- use the smart constructor + deriving (Ord, Eq) --- canonical order of the components of a module pair --- -canon :: ModulePair -> (Module, Module) -canon (ModulePair m1 m2) | m1 < m2 = (m1, m2) - | otherwise = (m2, m1) - -instance Eq ModulePair where - mp1 == mp2 = canon mp1 == canon mp2 - -instance Ord ModulePair where - mp1 `compare` mp2 = canon mp1 `compare` canon mp2 +-- | Smart constructor that establishes the invariant +modulePair :: Module -> Module -> ModulePair +modulePair a b + | a < b = ModulePair a b + | otherwise = ModulePair b a instance Outputable ModulePair where ppr (ModulePair m1 m2) = angleBrackets (ppr m1 <> comma <+> ppr m2) -- Sets of module pairs -- -type ModulePairSet = Map ModulePair () +type ModulePairSet = Set ModulePair listToSet :: [ModulePair] -> ModulePairSet -listToSet l = Map.fromList (zip l (repeat ())) +listToSet l = Set.fromList l checkFamInstConsistency :: [Module] -> [Module] -> TcM () checkFamInstConsistency famInstMods directlyImpMods @@ -170,7 +167,8 @@ checkFamInstConsistency famInstMods directlyImpMods -- instances of okPairs are consistent ; criticalPairs = listToSet $ allPairs famInstMods -- all pairs that we need to consider - ; toCheckPairs = Map.keys $ criticalPairs `Map.difference` okPairs + ; toCheckPairs = + Set.elems $ criticalPairs `Set.difference` okPairs -- the difference gives us the pairs we need to check now } @@ -178,7 +176,7 @@ checkFamInstConsistency famInstMods directlyImpMods } where allPairs [] = [] - allPairs (m:ms) = map (ModulePair m) ms ++ allPairs ms + allPairs (m:ms) = map (modulePair m) ms ++ allPairs ms check hpt_fam_insts (ModulePair m1 m2) = do { env1 <- getFamInsts hpt_fam_insts m1 diff --git a/testsuite/tests/perf/haddock/all.T b/testsuite/tests/perf/haddock/all.T index de45ea4..6ee448f 100644 --- a/testsuite/tests/perf/haddock/all.T +++ b/testsuite/tests/perf/haddock/all.T @@ -52,7 +52,7 @@ test('haddock.base', test('haddock.Cabal', [unless(in_tree_compiler(), skip), req_haddock ,stats_num_field('bytes allocated', - [(wordsize(64), 10941742184, 5) + [(wordsize(64), 10070330520, 5) # 2012-08-14: 3255435248 (amd64/Linux) # 2012-08-29: 3324606664 (amd64/Linux, new codegen) # 2012-10-08: 3373401360 (amd64/Linux) @@ -78,6 +78,11 @@ test('haddock.Cabal', # 2015-12-22: 10519532424 (amd64/Linux) - Lots of new Semigroup instances in Cabal # 2016-03-29: 11517963232 (amd64/Linux) - not yet investigated # 2016-03-30: 10941742184 (amd64/Linux) - defer inlining of Int* Ord methods + # 2016-04-06: 11542374816 (amd64/Linux) - CSE improvements and others + # 2016-04-07: 10963514352 (amd64/Linux) - Revert to what phabricator claims + # 2016-05-22: 11805238152 (amd64/Linux) - Make Generic1 poly-kinded + # 2016-06-05: 10997887320 (amd64/Linux) - Refactor derived Generic instances to reduce allocations + # 2016-06-21: 10070330520 (amd64/Linux) - D2350: Make checkFamInstConsistency less expensive ,(platform('i386-unknown-mingw32'), 3293415576, 5) # 2012-10-30: 1733638168 (x86/Windows) @@ -99,7 +104,7 @@ test('haddock.Cabal', test('haddock.compiler', [unless(in_tree_compiler(), skip), req_haddock ,stats_num_field('bytes allocated', - [(wordsize(64), 58017214568, 10) + [(wordsize(64), 55314944264, 10) # 2012P-08-14: 26070600504 (amd64/Linux) # 2012-08-29: 26353100288 (amd64/Linux, new CG) # 2012-09-18: 26882813032 (amd64/Linux) @@ -113,6 +118,7 @@ test('haddock.compiler', # 2015-12-03: 44721228752 (amd64/Linux) slow creep upwards # 2015-12-15: 49395782136 (amd64/Linux) more creep, following kind-equalities # 2015-12-17: 58017214568 (amd64/Linux) update Haddock to master + # 2016-06-21: 55314944264 (amd64/Linux) D2350: Make checkFamInstConsistency less expensive ,(platform('i386-unknown-mingw32'), 902576468, 10) # 2012-10-30: 13773051312 (x86/Windows) From git at git.haskell.org Thu Jul 14 13:54:28 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 14 Jul 2016 13:54:28 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Make the Ord Module independent of Unique order (2nd try) (eb59bf7) Message-ID: <20160714135428.6F3F33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/eb59bf7143f6133dae2452d1e7d2c302dab1709a/ghc >--------------------------------------------------------------- commit eb59bf7143f6133dae2452d1e7d2c302dab1709a Author: Bartosz Nitka Date: Thu Jun 9 08:50:32 2016 -0700 Make the Ord Module independent of Unique order (2nd try) The `Ord Module` instance currently uses `Unique`s for comparison. We don't want to use the `Unique` order because it can introduce nondeterminism. This switches `Ord ModuleName` and `Ord UnitId` to use lexicographic ordering making `Ord Module` deterministic transitively. I've run `nofib` and it doesn't make a measurable difference. See also Note [ModuleEnv determinism and performance]. This fixes #12191 - the regression, that the previous version of this patch had. Test Plan: ./validate run nofib: P112 Reviewers: simonmar, bgamari, austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2354 GHC Trac Issues: #4012, #12191 >--------------------------------------------------------------- eb59bf7143f6133dae2452d1e7d2c302dab1709a compiler/basicTypes/Module.hs | 99 +++++++++++++++------- compiler/typecheck/FamInst.hs | 35 +++++++- testsuite/tests/driver/sigof01/all.T | 2 +- .../should_fail/overloadedrecfldsfail10.stderr | 4 +- testsuite/tests/rename/should_fail/T11071.stderr | 2 +- testsuite/tests/rename/should_fail/T11071a.stderr | 32 +++---- .../tests/typecheck/should_fail/T6018fail.stderr | 4 +- 7 files changed, 122 insertions(+), 56 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc eb59bf7143f6133dae2452d1e7d2c302dab1709a From git at git.haskell.org Thu Jul 14 13:54:31 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 14 Jul 2016 13:54:31 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Add a new determinism test (052fe1d) Message-ID: <20160714135431.E2B983A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/052fe1d2c3425c0ff2b301da9018e2791ef75443/ghc >--------------------------------------------------------------- commit 052fe1d2c3425c0ff2b301da9018e2791ef75443 Author: Bartosz Nitka Date: Thu Jun 30 06:59:02 2016 -0700 Add a new determinism test This is one of the testcases that I forgot to commit >--------------------------------------------------------------- 052fe1d2c3425c0ff2b301da9018e2791ef75443 testsuite/tests/determinism/determ021/A.hs | 8 ++++++++ testsuite/tests/determinism/determ021/Makefile | 11 +++++++++++ .../determinism/{determ009 => determ021}/all.T | 4 ++-- .../tests/determinism/determ021/determ021.stdout | 22 ++++++++++++++++++++++ 4 files changed, 43 insertions(+), 2 deletions(-) diff --git a/testsuite/tests/determinism/determ021/A.hs b/testsuite/tests/determinism/determ021/A.hs new file mode 100644 index 0000000..773a012 --- /dev/null +++ b/testsuite/tests/determinism/determ021/A.hs @@ -0,0 +1,8 @@ +{-# LANGUAGE ApplicativeDo #-} +{-# OPTIONS_GHC -ddump-types #-} +module A where + +test2 f = do + x <- f 3 + y <- f 4 + return (x + y) diff --git a/testsuite/tests/determinism/determ021/Makefile b/testsuite/tests/determinism/determ021/Makefile new file mode 100644 index 0000000..e88edef --- /dev/null +++ b/testsuite/tests/determinism/determ021/Makefile @@ -0,0 +1,11 @@ +TOP=../../.. +include $(TOP)/mk/boilerplate.mk +include $(TOP)/mk/test.mk + +determ021: + $(RM) A.hi A.o + '$(TEST_HC)' $(TEST_HC_OPTS) -O -dinitial-unique=0 -dunique-increment=1 A.hs + $(CP) A.hi A.normal.hi + $(RM) A.hi A.o + '$(TEST_HC)' $(TEST_HC_OPTS) -O -dinitial-unique=16777215 -dunique-increment=-1 A.hs + diff A.hi A.normal.hi diff --git a/testsuite/tests/determinism/determ009/all.T b/testsuite/tests/determinism/determ021/all.T similarity index 50% copy from testsuite/tests/determinism/determ009/all.T copy to testsuite/tests/determinism/determ021/all.T index 7cae393..35af362 100644 --- a/testsuite/tests/determinism/determ009/all.T +++ b/testsuite/tests/determinism/determ021/all.T @@ -1,4 +1,4 @@ -test('determ009', +test('determ021', extra_clean(['A.o', 'A.hi', 'A.normal.hi']), run_command, - ['$MAKE -s --no-print-directory determ009']) + ['$MAKE -s --no-print-directory determ021']) diff --git a/testsuite/tests/determinism/determ021/determ021.stdout b/testsuite/tests/determinism/determ021/determ021.stdout new file mode 100644 index 0000000..747064f --- /dev/null +++ b/testsuite/tests/determinism/determ021/determ021.stdout @@ -0,0 +1,22 @@ +[1 of 1] Compiling A ( A.hs, A.o ) +TYPE SIGNATURES + test2 :: + forall t b (f :: * -> *). + (Num b, Num t, Applicative f) => + (t -> f b) -> f b +TYPE CONSTRUCTORS +COERCION AXIOMS +Dependent modules: [] +Dependent packages: [base-4.9.0.0, ghc-prim-0.5.0.0, + integer-gmp-1.0.0.1] +[1 of 1] Compiling A ( A.hs, A.o ) +TYPE SIGNATURES + test2 :: + forall t b (f :: * -> *). + (Num b, Num t, Applicative f) => + (t -> f b) -> f b +TYPE CONSTRUCTORS +COERCION AXIOMS +Dependent modules: [] +Dependent packages: [base-4.9.0.0, ghc-prim-0.5.0.0, + integer-gmp-1.0.0.1] From git at git.haskell.org Thu Jul 14 13:54:34 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 14 Jul 2016 13:54:34 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Refactor match to not use Unique order (a844f70) Message-ID: <20160714135434.9ECF43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/a844f707c8b2af46dfa3a2a905f48634ed314084/ghc >--------------------------------------------------------------- commit a844f707c8b2af46dfa3a2a905f48634ed314084 Author: Bartosz Nitka Date: Wed Jun 29 03:27:49 2016 -0700 Refactor match to not use Unique order Unique order can introduce nondeterminism. As a step towards removing the Ord Unique instance I've refactored the code to use deterministic sets instead. Test Plan: ./validate Reviewers: simonmar, austin, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2369 GHC Trac Issues: #4012 >--------------------------------------------------------------- a844f707c8b2af46dfa3a2a905f48634ed314084 compiler/deSugar/Match.hs | 32 +++++++++++++++++++++++--------- 1 file changed, 23 insertions(+), 9 deletions(-) diff --git a/compiler/deSugar/Match.hs b/compiler/deSugar/Match.hs index fc70cc6..ecbed46 100644 --- a/compiler/deSugar/Match.hs +++ b/compiler/deSugar/Match.hs @@ -46,6 +46,8 @@ import Util import Name import Outputable import BasicTypes ( isGenerated ) +import Unique +import UniqDFM import Control.Monad( when, unless ) import qualified Data.Map as Map @@ -196,9 +198,9 @@ match vars@(v:_) ty eqns -- Eqns *can* be empty match_group [] = panic "match_group" match_group eqns@((group,_) : _) = case group of - PgCon {} -> matchConFamily vars ty (subGroup [(c,e) | (PgCon c, e) <- eqns]) + PgCon {} -> matchConFamily vars ty (subGroupUniq [(c,e) | (PgCon c, e) <- eqns]) PgSyn {} -> matchPatSyn vars ty (dropGroup eqns) - PgLit {} -> matchLiterals vars ty (subGroup [(l,e) | (PgLit l, e) <- eqns]) + PgLit {} -> matchLiterals vars ty (subGroupOrd [(l,e) | (PgLit l, e) <- eqns]) PgAny -> matchVariables vars ty (dropGroup eqns) PgN {} -> matchNPats vars ty (dropGroup eqns) PgNpK {} -> matchNPlusKPats vars ty (dropGroup eqns) @@ -809,22 +811,34 @@ groupEquations dflags eqns same_gp :: (PatGroup,EquationInfo) -> (PatGroup,EquationInfo) -> Bool (pg1,_) `same_gp` (pg2,_) = pg1 `sameGroup` pg2 -subGroup :: Ord a => [(a, EquationInfo)] -> [[EquationInfo]] +subGroup :: (m -> [[EquationInfo]]) -- Map.elems + -> m -- Map.empty + -> (a -> m -> Maybe [EquationInfo]) -- Map.lookup + -> (a -> [EquationInfo] -> m -> m) -- Map.insert + -> [(a, EquationInfo)] -> [[EquationInfo]] -- Input is a particular group. The result sub-groups the -- equations by with particular constructor, literal etc they match. -- Each sub-list in the result has the same PatGroup -- See Note [Take care with pattern order] -subGroup group - = map reverse $ Map.elems $ foldl accumulate Map.empty group +-- Parameterized by map operations to allow different implementations +-- and constraints, eg. types without Ord instance. +subGroup elems empty lookup insert group + = map reverse $ elems $ foldl accumulate empty group where accumulate pg_map (pg, eqn) - = case Map.lookup pg pg_map of - Just eqns -> Map.insert pg (eqn:eqns) pg_map - Nothing -> Map.insert pg [eqn] pg_map - + = case lookup pg pg_map of + Just eqns -> insert pg (eqn:eqns) pg_map + Nothing -> insert pg [eqn] pg_map -- pg_map :: Map a [EquationInfo] -- Equations seen so far in reverse order of appearance +subGroupOrd :: Ord a => [(a, EquationInfo)] -> [[EquationInfo]] +subGroupOrd = subGroup Map.elems Map.empty Map.lookup Map.insert + +subGroupUniq :: Uniquable a => [(a, EquationInfo)] -> [[EquationInfo]] +subGroupUniq = + subGroup eltsUDFM emptyUDFM (flip lookupUDFM) (\k v m -> addToUDFM m k v) + {- Note [Pattern synonym groups] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ If we see From git at git.haskell.org Thu Jul 14 13:54:37 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 14 Jul 2016 13:54:37 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Make accept (8ed4318) Message-ID: <20160714135437.49CCF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/8ed4318af25820aca86b6a96c33ab3aedce8f32c/ghc >--------------------------------------------------------------- commit 8ed4318af25820aca86b6a96c33ab3aedce8f32c Author: Bartosz Nitka Date: Wed Jul 13 12:41:45 2016 -0700 Make accept >--------------------------------------------------------------- 8ed4318af25820aca86b6a96c33ab3aedce8f32c testsuite/tests/ado/ado004.stderr | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/testsuite/tests/ado/ado004.stderr b/testsuite/tests/ado/ado004.stderr index 2bb2e6d..8f5a816 100644 --- a/testsuite/tests/ado/ado004.stderr +++ b/testsuite/tests/ado/ado004.stderr @@ -6,8 +6,8 @@ TYPE SIGNATURES (Num b, Num t, Applicative f) => (t -> f b) -> f b test2a :: - forall (f :: * -> *) b t. - (Num t, Num b, Functor f) => + forall t b (f :: * -> *). + (Num b, Num t, Functor f) => (t -> f b) -> f b test2b :: forall (m :: * -> *) a t. (Num t, Monad m) => (t -> a) -> m a From git at git.haskell.org Thu Jul 14 22:16:24 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 14 Jul 2016 22:16:24 +0000 (UTC) Subject: [commit: ghc] master: Added type family dependency to Data.Type.Bool.Not (37aeff6) Message-ID: <20160714221624.41FCD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/37aeff631766eebf5820b980d614bef78960291a/ghc >--------------------------------------------------------------- commit 37aeff631766eebf5820b980d614bef78960291a Author: Baldur Blöndal Date: Thu Jul 14 18:09:03 2016 -0400 Added type family dependency to Data.Type.Bool.Not Summary: Signed-off-by: Baldur Blöndal Reviewers: goldfire, RyanGlScott, austin, bgamari, hvr Reviewed By: RyanGlScott, austin Subscribers: RyanGlScott, thomie Differential Revision: https://phabricator.haskell.org/D2268 GHC Trac Issues: #12057 >--------------------------------------------------------------- 37aeff631766eebf5820b980d614bef78960291a libraries/base/Data/Type/Bool.hs | 11 ++++++----- libraries/base/changelog.md | 2 ++ 2 files changed, 8 insertions(+), 5 deletions(-) diff --git a/libraries/base/Data/Type/Bool.hs b/libraries/base/Data/Type/Bool.hs index cfd4bfa..4309b6d 100644 --- a/libraries/base/Data/Type/Bool.hs +++ b/libraries/base/Data/Type/Bool.hs @@ -1,6 +1,5 @@ -{-# LANGUAGE Safe #-} -{-# LANGUAGE TypeFamilies, TypeOperators, DataKinds, NoImplicitPrelude, - PolyKinds #-} +{-# LANGUAGE TypeFamilyDependencies, Safe, PolyKinds #-} +{-# LANGUAGE TypeFamilies, TypeOperators, DataKinds, NoImplicitPrelude #-} ----------------------------------------------------------------------------- -- | @@ -49,7 +48,9 @@ type family a || b where a || a = a infixr 2 || --- | Type-level "not" -type family Not a where +-- | Type-level "not". An injective type family since @4.10.0.0 at . +-- +-- @since 4.7.0.0 +type family Not a = res | res -> a where Not 'False = 'True Not 'True = 'False diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index 5a2e90f..ecf6a82 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -3,6 +3,8 @@ ## next *TBA* * Bundled with GHC *TBA* + * `Data.Type.Bool.Not` given a type family dependency (#12057). + * `Foreign.Ptr` now exports the constructors for `IntPtr` and `WordPtr` (#11983) From git at git.haskell.org Fri Jul 15 18:18:36 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 15 Jul 2016 18:18:36 +0000 (UTC) Subject: [commit: ghc] master: Bring comments in TcGenGenerics up to date (b35e01c) Message-ID: <20160715181836.C90043A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b35e01c6c39d9f2d58009722e24d89049aa94287/ghc >--------------------------------------------------------------- commit b35e01c6c39d9f2d58009722e24d89049aa94287 Author: Ryan Scott Date: Fri Jul 15 14:17:24 2016 -0400 Bring comments in TcGenGenerics up to date [ci skip] >--------------------------------------------------------------- b35e01c6c39d9f2d58009722e24d89049aa94287 compiler/typecheck/TcGenGenerics.hs | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/compiler/typecheck/TcGenGenerics.hs b/compiler/typecheck/TcGenGenerics.hs index a734ae8..5757e98 100644 --- a/compiler/typecheck/TcGenGenerics.hs +++ b/compiler/typecheck/TcGenGenerics.hs @@ -135,7 +135,8 @@ canDoGenerics :: TyCon -> Validity -- Check (a) from Note [Requirements for deriving Generic and Rep] is taken -- care of because canDoGenerics is applied to rep tycons. -- --- It returns Nothing if deriving is possible. It returns (Just reason) if not. +-- It returns IsValid if deriving is possible. It returns (NotValid reason) +-- if not. canDoGenerics tc = mergeErrors ( -- Check (b) from Note [Requirements for deriving Generic and Rep]. @@ -221,7 +222,8 @@ explicitly, even though foldDataConArgs is also doing this internally. -- Checks (a) through (c) from Note [Requirements for deriving Generic and Rep] -- are taken care of by the call to canDoGenerics. -- --- It returns Nothing if deriving is possible. It returns (Just reason) if not. +-- It returns IsValid if deriving is possible. It returns (NotValid reason) +-- if not. canDoGenerics1 :: TyCon -> Validity canDoGenerics1 rep_tc = canDoGenerics rep_tc `andValid` additionalChecks From git at git.haskell.org Sat Jul 16 21:40:31 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 16 Jul 2016 21:40:31 +0000 (UTC) Subject: [commit: ghc] master: Log heap profiler samples to event log (a9bc547) Message-ID: <20160716214031.16DC73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a9bc54766ddd1bdb011f1656ad58fb409055d08f/ghc >--------------------------------------------------------------- commit a9bc54766ddd1bdb011f1656ad58fb409055d08f Author: Ben Gamari Date: Thu Jun 16 15:03:01 2016 +0200 Log heap profiler samples to event log Test Plan: Try it Reviewers: hvr, simonmar, austin, erikd Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1722 GHC Trac Issues: #11094 >--------------------------------------------------------------- a9bc54766ddd1bdb011f1656ad58fb409055d08f compiler/main/DynFlags.hs | 1 + compiler/main/Packages.hs | 4 +- docs/users_guide/8.2.1-notes.rst | 4 + docs/users_guide/eventlog-formats.rst | 119 ++++++++++++++++++++++ docs/users_guide/index.rst | 1 + docs/users_guide/profiling.rst | 24 ++++- includes/rts/Config.h | 8 +- includes/rts/EventLogFormat.h | 11 +- mk/config.mk.in | 23 +++-- mk/ways.mk | 41 +++++--- rts/ProfHeap.c | 32 +++++- rts/Trace.c | 43 ++++++++ rts/Trace.h | 19 ++++ rts/eventlog/EventLog.c | 183 ++++++++++++++++++++++++++++++++++ rts/eventlog/EventLog.h | 20 ++++ 15 files changed, 497 insertions(+), 36 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc a9bc54766ddd1bdb011f1656ad58fb409055d08f From git at git.haskell.org Sat Jul 16 21:40:33 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 16 Jul 2016 21:40:33 +0000 (UTC) Subject: [commit: ghc] master: IfaceEnv: Only check for built-in OccNames if mod is GHC.Types (ffe4660) Message-ID: <20160716214033.B5EAD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ffe4660510a7ba4adce846f316db455ccd91142a/ghc >--------------------------------------------------------------- commit ffe4660510a7ba4adce846f316db455ccd91142a Author: Ben Gamari Date: Sat Jul 16 23:38:51 2016 +0200 IfaceEnv: Only check for built-in OccNames if mod is GHC.Types This check is not entirely cheap and will not succeed unless we are looking for something in the module where built-in syntax lives, GHC.Types. Reviewers: simonpj, austin Subscribers: simonpj, thomie, osa1 Differential Revision: https://phabricator.haskell.org/D2400 >--------------------------------------------------------------- ffe4660510a7ba4adce846f316db455ccd91142a compiler/iface/IfaceEnv.hs | 28 +++++++++++----- compiler/prelude/TysWiredIn.hs | 67 ++++++++++++++++++++++++------------- testsuite/tests/perf/compiler/all.T | 4 ++- 3 files changed, 66 insertions(+), 33 deletions(-) diff --git a/compiler/iface/IfaceEnv.hs b/compiler/iface/IfaceEnv.hs index 0c8d8e9..ff2f648 100644 --- a/compiler/iface/IfaceEnv.hs +++ b/compiler/iface/IfaceEnv.hs @@ -33,6 +33,7 @@ import Module import FastString import FastStringEnv import IfaceType +import PrelNames ( gHC_TYPES, gHC_PRIM, gHC_TUPLE ) import UniqSupply import SrcLoc import Util @@ -184,26 +185,37 @@ See Note [The Name Cache] above. Note [Built-in syntax and the OrigNameCache] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -You might think that usin isBuiltInOcc_maybe in lookupOrigNameCache is -unnecessary because tuple TyCon/DataCons are parsed as Exact RdrNames -and *don't* appear as original names in interface files (because -serialization gives them special treatment), so we will never look -them up in the original name cache. -However, there are two reasons why we might look up an Orig RdrName: +Built-in syntax like tuples and unboxed sums are quite ubiquitous. To lower +their cost we use two tricks, + + b. We specially encode tuple Names in interface files' symbols tables to avoid + having to look up their names at all while loading interface files. See + Note [Symbol table representation of names] in BinIface for details. + + a. We don't include them in the Orig name cache but instead parse their + OccNames (in isBuiltInOcc_maybe) to avoid bloating the name cache with + them. + +Why is the second measure necessary? Good question; afterall, 1) the parser +emits built-in syntax directly as Exact RdrNames, and 2) built-in syntax never +needs to looked-up during interface loading due to (a). It turns out that there +are two reasons why we might look up an Orig RdrName for built-in syntax, * If you use setRdrNameSpace on an Exact RdrName it may be turned into an Orig RdrName. * Template Haskell turns a BuiltInSyntax Name into a TH.NameG (DsMeta.globalVar), and parses a NameG into an Orig RdrName - (Convert.thRdrName). So, eg $(do { reify '(,); ... }) will + (Convert.thRdrName). So, e.g. $(do { reify '(,); ... }) will go this route (Trac #8954). + -} lookupOrigNameCache :: OrigNameCache -> Module -> OccName -> Maybe Name lookupOrigNameCache nc mod occ - | Just name <- isBuiltInOcc_maybe occ + | mod == gHC_TYPES || mod == gHC_PRIM || mod == gHC_TUPLE + , Just name <- isBuiltInOcc_maybe occ = -- See Note [Known-key names], 3(c) in PrelNames -- Special case for tuples; there are too many -- of them to pre-populate the original-name cache diff --git a/compiler/prelude/TysWiredIn.hs b/compiler/prelude/TysWiredIn.hs index 8465cd9..86f1dde 100644 --- a/compiler/prelude/TysWiredIn.hs +++ b/compiler/prelude/TysWiredIn.hs @@ -5,6 +5,7 @@ -} {-# LANGUAGE CPP #-} +{-# LANGUAGE OverloadedStrings #-} -- | This module is about types that can be defined in Haskell, but which -- must be wired into the compiler nonetheless. C.f module TysPrim @@ -134,7 +135,6 @@ import {-# SOURCE #-} ConLike import TyCon import Class ( Class, mkClass ) import RdrName -import UniqFM import Name import NameSet ( NameSet, mkNameSet, elemNameSet ) import BasicTypes ( Arity, Boxity(..), @@ -148,6 +148,12 @@ import Outputable import Util import BooleanFormula ( mkAnd ) +import qualified Data.ByteString.Char8 as BS +#if !MIN_VERSION_bytestring(0,10,8) +import qualified Data.ByteString.Internal as BSI +import qualified Data.ByteString.Unsafe as BSU +#endif + alpha_tyvar :: [TyVar] alpha_tyvar = [alphaTyVar] @@ -181,8 +187,7 @@ names in PrelNames, so they use wTcQual, wDataQual, etc -- define here. -- -- Because of their infinite nature, this list excludes tuples, Any and implicit --- parameter TyCons. Instead, we have a hack in lookupOrigNameCache to deal with --- these names. +-- parameter TyCons (see Note [Built-in syntax and the OrigNameCache]). -- -- See also Note [Known-key names] wiredInTyCons :: [TyCon] @@ -636,19 +641,42 @@ decl in GHC.Classes, so I think this part may not work properly. But it's unused I think. -} -builtInOccNames :: UniqFM (OccName -> Name) -builtInOccNames = listToUFM $ - [ (fsLit "[]", choose_ns listTyConName nilDataConName) - , (fsLit ":" , const consDataConName) - , (fsLit "[::]", const parrTyConName) - , (fsLit "()", tup_name Boxed 0) - , (fsLit "(##)", tup_name Unboxed 0) - ] ++ - [ (fsLit $ "("++replicate n ','++")", tup_name Boxed (n+1)) | n <- [1..62] ] ++ - [ (fsLit $ "(#"++replicate n ','++"#)", tup_name Unboxed (n+1)) | n <- [1..62] ] +-- | Built in syntax isn't "in scope" so these OccNames map to wired-in Names +-- with BuiltInSyntax. However, this should only be necessary while resolving +-- names produced by Template Haskell splices since we take care to encode +-- built-in syntax names specially in interface files. See +-- Note [Symbol table representation of names]. +isBuiltInOcc_maybe :: OccName -> Maybe Name +isBuiltInOcc_maybe occ = + case name of + "[]" -> Just $ choose_ns listTyConName nilDataConName + ":" -> Just consDataConName + "[::]" -> Just parrTyConName + "()" -> Just $ tup_name Boxed 0 + "(##)" -> Just $ tup_name Unboxed 0 + _ | Just rest <- "(" `stripPrefix` name + , (commas, rest') <- BS.span (==',') rest + , ")" <- rest' + -> Just $ tup_name Boxed (1+BS.length commas) + _ | Just rest <- "(#" `stripPrefix` name + , (commas, rest') <- BS.span (==',') rest + , "#)" <- rest' + -> Just $ tup_name Unboxed (1+BS.length commas) + _ -> Nothing where - choose_ns :: Name -> Name -> OccName -> Name - choose_ns tc dc occ + -- TODO: Drop when bytestring 0.10.8 can be assumed +#if MIN_VERSION_bytestring(0,10,8) + stripPrefix = BS.stripPrefix +#else + stripPrefix bs1@(BSI.PS _ _ l1) bs2 + | bs1 `BS.isPrefixOf` bs2 = Just (BSU.unsafeDrop l1 bs2) + | otherwise = Nothing +#endif + + name = fastStringToByteString $ occNameFS occ + + choose_ns :: Name -> Name -> Name + choose_ns tc dc | isTcClsNameSpace ns = tc | isDataConNameSpace ns = dc | otherwise = pprPanic "tup_name" (ppr occ) @@ -658,15 +686,6 @@ builtInOccNames = listToUFM $ = choose_ns (getName (tupleTyCon boxity arity)) (getName (tupleDataCon boxity arity)) - -isBuiltInOcc_maybe :: OccName -> Maybe Name --- Built in syntax isn't "in scope" so these OccNames --- map to wired-in Names with BuiltInSyntax -isBuiltInOcc_maybe occ - = case lookupUFM builtInOccNames (occNameFS occ) of - Just f -> Just (f occ) - Nothing -> Nothing - mkTupleOcc :: NameSpace -> Boxity -> Arity -> OccName -- No need to cache these, the caching is done in mk_tuple mkTupleOcc ns Boxed ar = mkOccName ns (mkBoxedTupleStr ar) diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index 386040c..f0308bf 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -513,7 +513,7 @@ test('T5321FD', # 2014-07-31: 211699816 (Windows) (-11%) # (due to better optCoercion, 5e7406d9, #9233) # 2016-04-06: 250757460 (x86/Linux) - (wordsize(64), 532365376, 10)]) + (wordsize(64), 477840432, 10)]) # prev: 418306336 # 29/08/2012: 492905640 # (increase due to new codegen) @@ -532,6 +532,8 @@ test('T5321FD', # not recognize that the application is bottom) # 2015-10-28: 532365376 # D757: emit Typeable instances at site of type definition + # 2016-07-16: 477840432 + # Optimize handling of built-in OccNames ], compile,['']) From git at git.haskell.org Sun Jul 17 07:53:37 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 17 Jul 2016 07:53:37 +0000 (UTC) Subject: [commit: ghc] master: Binary: Use ByteString's copy in getBS (24f5f36) Message-ID: <20160717075337.E44B53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/24f5f368d8ed0b5f113c2753b2b2bdc99957dcb2/ghc >--------------------------------------------------------------- commit 24f5f368d8ed0b5f113c2753b2b2bdc99957dcb2 Author: Ben Gamari Date: Sat Jul 16 23:41:46 2016 +0200 Binary: Use ByteString's copy in getBS It's unclear how much of an effect on runtime this will have, but if nothing else the code generation may be a tad better since the system's `memcpy` will be used. Test Plan: Validate Reviewers: simonmar, austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2401 >--------------------------------------------------------------- 24f5f368d8ed0b5f113c2753b2b2bdc99957dcb2 compiler/utils/Binary.hs | 31 ++++++++++++------------------- 1 file changed, 12 insertions(+), 19 deletions(-) diff --git a/compiler/utils/Binary.hs b/compiler/utils/Binary.hs index 9f8d926..9f7c03d 100644 --- a/compiler/utils/Binary.hs +++ b/compiler/utils/Binary.hs @@ -70,7 +70,7 @@ import SrcLoc import Foreign import Data.Array import Data.ByteString (ByteString) -import qualified Data.ByteString.Internal as BS +import qualified Data.ByteString as BS import qualified Data.ByteString.Unsafe as BS import Data.IORef import Data.Char ( ord, chr ) @@ -664,7 +664,7 @@ getDictionary bh = do -- The Symbol Table --------------------------------------------------------- --- On disk, the symbol table is an array of IfaceExtName, when +-- On disk, the symbol table is an array of IfExtName, when -- reading it in we turn it into a SymbolTable. type SymbolTable = Array Int Name @@ -692,25 +692,18 @@ putBS bh bs = go (n+1) go 0 -{- -- possible faster version, not quite there yet: -getBS bh at BinMem{} = do - (I# l) <- get bh - arr <- readIORef (arr_r bh) - off <- readFastMutInt (off_r bh) - return $! (mkFastSubBytesBA# arr off l) --} getBS :: BinHandle -> IO ByteString getBS bh = do - l <- get bh - fp <- mallocForeignPtrBytes l - withForeignPtr fp $ \ptr -> do - let go n | n == l = return $ BS.fromForeignPtr fp 0 l - | otherwise = do - b <- getByte bh - pokeElemOff ptr n b - go (n+1) - -- - go 0 + l <- get bh :: IO Int + arr <- readIORef (_arr_r bh) + sz <- readFastMutInt (_sz_r bh) + off <- readFastMutInt (_off_r bh) + when (off + l > sz) $ + ioError (mkIOError eofErrorType "Data.Binary.getBS" Nothing Nothing) + writeFastMutInt (_off_r bh) (off+l) + withForeignPtr arr $ \ptr -> do + bs <- BS.unsafePackCStringLen (castPtr $ ptr `plusPtr` off, fromIntegral l) + return $! BS.copy bs instance Binary ByteString where put_ bh f = putBS bh f From git at git.haskell.org Sun Jul 17 07:53:40 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 17 Jul 2016 07:53:40 +0000 (UTC) Subject: [commit: ghc] master: Bugfix for bug 11632: `readLitChar` should consume null characters (0f0cdb6) Message-ID: <20160717075340.8F33D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0f0cdb6827803015a9a3924fdafaef8dbcde048f/ghc >--------------------------------------------------------------- commit 0f0cdb6827803015a9a3924fdafaef8dbcde048f Author: Ben Gamari Date: Sun Jul 17 00:12:52 2016 +0200 Bugfix for bug 11632: `readLitChar` should consume null characters Test Plan: The tests have been included. This change deals with a relatively minor edge case and should not break unrelated functionality. Reviewers: thomie, #core_libraries_committee, ekmett, bgamari Reviewed By: #core_libraries_committee, ekmett, bgamari Subscribers: bgamari, ekmett Differential Revision: https://phabricator.haskell.org/D2391 GHC Trac Issues: #11632 >--------------------------------------------------------------- 0f0cdb6827803015a9a3924fdafaef8dbcde048f libraries/base/GHC/Read.hs | 8 +++++++- libraries/base/Text/Read/Lex.hs | 11 ++++++++++- libraries/base/tests/readLitChar.hs | 5 ++++- libraries/base/tests/readLitChar.stdout | 4 ++++ 4 files changed, 25 insertions(+), 3 deletions(-) diff --git a/libraries/base/GHC/Read.hs b/libraries/base/GHC/Read.hs index 54fbc28..d7df82f 100644 --- a/libraries/base/GHC/Read.hs +++ b/libraries/base/GHC/Read.hs @@ -229,7 +229,13 @@ lex s = readP_to_S L.hsLex s -- lexLitChar :: ReadS String -- As defined by H2010 lexLitChar = readP_to_S (do { (s, _) <- P.gather L.lexChar ; - return s }) + let s' = removeNulls s in + return s' }) + where + -- remove nulls from end of the character if they exist + removeNulls [] = [] + removeNulls ('\\':'&':xs) = removeNulls xs + removeNulls (first:rest) = first : removeNulls rest -- There was a skipSpaces before the P.gather L.lexChar, -- but that seems inconsistent with readLitChar diff --git a/libraries/base/Text/Read/Lex.hs b/libraries/base/Text/Read/Lex.hs index 7054be9..d0d39c6 100644 --- a/libraries/base/Text/Read/Lex.hs +++ b/libraries/base/Text/Read/Lex.hs @@ -253,7 +253,16 @@ lexLitChar = return (Char c) lexChar :: ReadP Char -lexChar = do { (c,_) <- lexCharE; return c } +lexChar = do { (c,_) <- lexCharE; consumeEmpties; return c } + where + -- Consumes the string "\&" repeatedly and greedily (will only produce one match) + consumeEmpties :: ReadP () + consumeEmpties = do + rest <- look + case rest of + ('\\':'&':_) -> string "\\&" >> consumeEmpties + _ -> return () + lexCharE :: ReadP (Char, Bool) -- "escaped or not"? lexCharE = diff --git a/libraries/base/tests/readLitChar.hs b/libraries/base/tests/readLitChar.hs index 7dc01e3..e287d22 100644 --- a/libraries/base/tests/readLitChar.hs +++ b/libraries/base/tests/readLitChar.hs @@ -9,4 +9,7 @@ main = putStrLn (show $ readLitChar "'A'") putStrLn (show $ lexLitChar "A") putStrLn (show $ lexLitChar "'A'") - + putStrLn (show $ lexLitChar "\\243\\&1") + putStrLn (show $ lexLitChar "a\\&1") + putStrLn (show $ lexLitChar "a\\&\\&1") + putStrLn (show $ lexLitChar "a\\&\\&") diff --git a/libraries/base/tests/readLitChar.stdout b/libraries/base/tests/readLitChar.stdout index 649c342..db7bc5b 100644 --- a/libraries/base/tests/readLitChar.stdout +++ b/libraries/base/tests/readLitChar.stdout @@ -2,3 +2,7 @@ [('\'',"A'")] [("A","")] [("'","A'")] +[("\\243","1")] +[("a","1")] +[("a","1")] +[("a","")] From git at git.haskell.org Sun Jul 17 07:53:43 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 17 Jul 2016 07:53:43 +0000 (UTC) Subject: [commit: ghc] master: CodeGen: Way to dump cmm only once (#11717) (1ba79fa) Message-ID: <20160717075343.4A82C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1ba79fa4d0e13e61a805fa458bcf2e690710d88b/ghc >--------------------------------------------------------------- commit 1ba79fa4d0e13e61a805fa458bcf2e690710d88b Author: Vladimir Trubilov Date: Sun Jul 17 00:13:22 2016 +0200 CodeGen: Way to dump cmm only once (#11717) The `-ddump-cmm` put all stages of Cmm processing into one output. This patch changes its behavior and adds two more options to make Cmm dumping flexible. - `-ddump-cmm-from-stg` dumps only initial version of Cmm right after STG->Cmm codegen - `-ddump-cmm` dumps the final result of the Cmm pipeline processing - `-ddump-cmm-verbose` dumps intermediate output of each Cmm pipeline step - `-ddump-cmm-proc` and `-ddump-cmm-caf` seems were lost. Now enabled Test Plan: ./validate Reviewers: thomie, simonmar, austin, bgamari Reviewed By: thomie, simonmar Subscribers: simonpj, thomie Differential Revision: https://phabricator.haskell.org/D2393 GHC Trac Issues: #11717 >--------------------------------------------------------------- 1ba79fa4d0e13e61a805fa458bcf2e690710d88b compiler/cmm/CmmParse.y | 4 +--- compiler/cmm/CmmPipeline.hs | 27 +++++++++++----------- compiler/main/DynFlags.hs | 20 ++++++++++++---- compiler/main/HscMain.hs | 15 ++++++------ docs/users_guide/8.0.2-notes.rst | 11 +++++++++ docs/users_guide/debugging.rst | 12 +++++++++- testsuite/tests/codeGen/should_compile/Makefile | 4 ++-- utils/mkUserGuidePart/Options/CompilerDebugging.hs | 10 +++++++- 8 files changed, 71 insertions(+), 32 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 1ba79fa4d0e13e61a805fa458bcf2e690710d88b From git at git.haskell.org Sun Jul 17 07:53:46 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 17 Jul 2016 07:53:46 +0000 (UTC) Subject: [commit: ghc] master: Pretty: remove a harmful $! (#12227) (89a8be7) Message-ID: <20160717075346.54CE03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/89a8be71a3715c948cebcb19ac81f84da0e6270e/ghc >--------------------------------------------------------------- commit 89a8be71a3715c948cebcb19ac81f84da0e6270e Author: Thomas Miedema Date: Sun Jul 17 00:13:45 2016 +0200 Pretty: remove a harmful $! (#12227) This is backport of [1] for GHC's copy of Pretty. See Note [Differences between libraries/pretty and compiler/utils/Pretty.hs]. [1] http://git.haskell.org/packages/pretty.git/commit/bbe9270c5f849a5bb74c9166a5f4202cfb0dba22 https://github.com/haskell/pretty/issues/32 https://github.com/haskell/pretty/pull/35 Reviewers: bgamari, austin Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D2397 GHC Trac Issues: #12227 >--------------------------------------------------------------- 89a8be71a3715c948cebcb19ac81f84da0e6270e compiler/utils/Pretty.hs | 45 ++++++++++- testsuite/tests/perf/compiler/T12227.hs | 137 ++++++++++++++++++++++++++++++++ testsuite/tests/perf/compiler/all.T | 20 ++++- 3 files changed, 199 insertions(+), 3 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 89a8be71a3715c948cebcb19ac81f84da0e6270e From git at git.haskell.org Sun Jul 17 07:53:48 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 17 Jul 2016 07:53:48 +0000 (UTC) Subject: [commit: ghc] master: hp2ps: fix invalid PostScript for names with parentheses (5df92f6) Message-ID: <20160717075348.F16353A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5df92f6776b31b375a80865e7db1f330d929c18f/ghc >--------------------------------------------------------------- commit 5df92f6776b31b375a80865e7db1f330d929c18f Author: Ben Gamari Date: Sun Jul 17 00:14:04 2016 +0200 hp2ps: fix invalid PostScript for names with parentheses The names in the .hp files may contain un-matched opening parentheses, so escape them. GHC Trac: #9517 Reviewers: bgamari, austin Reviewed By: bgamari, austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2398 GHC Trac Issues: #9517 >--------------------------------------------------------------- 5df92f6776b31b375a80865e7db1f330d929c18f utils/hp2ps/Key.c | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/utils/hp2ps/Key.c b/utils/hp2ps/Key.c index 22ad106..b7742cf 100644 --- a/utils/hp2ps/Key.c +++ b/utils/hp2ps/Key.c @@ -44,7 +44,8 @@ escape(char *result, const char *name) { while (*name != '\0') { - if (*name == '\\') + // escape parentheses too, because "name" could contain un-matched ones + if (*name == '\\' || *name == '(' || *name == ')') { *result++ = '\\'; } From git at git.haskell.org Mon Jul 18 13:16:14 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 18 Jul 2016 13:16:14 +0000 (UTC) Subject: [commit: ghc] master: Fix misspellings of the word "instance" in comments (d213ab3) Message-ID: <20160718131614.E1D5F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d213ab3fa0cc2a39d9f74df11c8a3451ac34411c/ghc >--------------------------------------------------------------- commit d213ab3fa0cc2a39d9f74df11c8a3451ac34411c Author: Ryan Scott Date: Mon Jul 18 09:14:36 2016 -0400 Fix misspellings of the word "instance" in comments [ci skip] >--------------------------------------------------------------- d213ab3fa0cc2a39d9f74df11c8a3451ac34411c compiler/rename/RnNames.hs | 2 +- compiler/rename/RnSource.hs | 2 +- compiler/typecheck/TcInstDcls.hs | 4 ++-- compiler/typecheck/TcValidity.hs | 2 +- compiler/types/TyCon.hs | 2 +- libraries/base/GHC/Base.hs | 2 +- testsuite/tests/deriving/should_compile/drv015.hs | 2 +- 7 files changed, 8 insertions(+), 8 deletions(-) diff --git a/compiler/rename/RnNames.hs b/compiler/rename/RnNames.hs index ab27b6a..51a231c 100644 --- a/compiler/rename/RnNames.hs +++ b/compiler/rename/RnNames.hs @@ -1466,7 +1466,7 @@ dupExport_ok :: Name -> IE RdrName -> IE RdrName -> Bool -- Example of "yes" (Trac #2436) -- module M( C(..), T(..) ) where -- class C a where { data T a } --- instace C Int where { data T Int = TInt } +-- instance C Int where { data T Int = TInt } -- -- Example of "yes" (Trac #2436) -- module Foo ( T ) where diff --git a/compiler/rename/RnSource.hs b/compiler/rename/RnSource.hs index 67cf7fd..adfec6f 100644 --- a/compiler/rename/RnSource.hs +++ b/compiler/rename/RnSource.hs @@ -1268,7 +1268,7 @@ if the data instance is an assocaited type of an enclosing class instance. with different dependency structure!) Ugh. For now we simply don't allow promotion of data constructors for -data instaces. See Note [AFamDataCon: not promoting data family +data instances. See Note [AFamDataCon: not promoting data family constructors] in TcEnv -} diff --git a/compiler/typecheck/TcInstDcls.hs b/compiler/typecheck/TcInstDcls.hs index 21eea28..220923d 100644 --- a/compiler/typecheck/TcInstDcls.hs +++ b/compiler/typecheck/TcInstDcls.hs @@ -888,7 +888,7 @@ wrapId wrapper id = mkHsWrap wrapper (HsVar (noLoc id)) {- Note [Typechecking plan for instance declarations] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -For intance declarations we generate the following bindings and implication +For instance declarations we generate the following bindings and implication constraints. Example: instance Ord a => Ord [a] where compare = @@ -1516,7 +1516,7 @@ mkDefMethBind :: Class -> [Type] -> Id -> Name -> TcM (LHsBind Name, [LSig Name] -- The is a default method (vanailla or generic) defined in the class -- So make a binding op = $dmop @t1 @t2 -- where $dmop is the name of the default method in the class, --- and t1,t2 are the instace types. +-- and t1,t2 are the instance types. -- See Note [Default methods in instances] for why we use -- visible type application here mkDefMethBind clas inst_tys sel_id dm_name diff --git a/compiler/typecheck/TcValidity.hs b/compiler/typecheck/TcValidity.hs index 4653eaa..49767fe 100644 --- a/compiler/typecheck/TcValidity.hs +++ b/compiler/typecheck/TcValidity.hs @@ -130,7 +130,7 @@ And this is what checkAmbiguity does. What about this, though? g :: C [a] => Int Is every call to 'g' ambiguous? After all, we might have - intance C [a] where ... + instance C [a] where ... at the call site. So maybe that type is ok! Indeed even f's quintessentially ambiguous type might, just possibly be callable: with -XFlexibleInstances we could have diff --git a/compiler/types/TyCon.hs b/compiler/types/TyCon.hs index d825712..a31ecdd 100644 --- a/compiler/types/TyCon.hs +++ b/compiler/types/TyCon.hs @@ -852,7 +852,7 @@ data AlgTyConFlav [Type] -- Argument types (mentions the tyConTyVars of this TyCon) -- Match in length the tyConTyVars of the family TyCon - -- E.g. data intance T [a] = ... + -- E.g. data instance T [a] = ... -- gives a representation tycon: -- data R:TList a = ... -- axiom co a :: T [a] ~ R:TList a diff --git a/libraries/base/GHC/Base.hs b/libraries/base/GHC/Base.hs index 9e4467b..03e9648 100644 --- a/libraries/base/GHC/Base.hs +++ b/libraries/base/GHC/Base.hs @@ -50,7 +50,7 @@ GHC.Num Class: Num, plus instances for Int GHC.Real Classes: Real, Integral, Fractional, RealFrac plus instances for Int, Integer Types: Ratio, Rational - plus intances for classes so far + plus instances for classes so far Rational is needed here because it is mentioned in the signature of 'toRational' in class Real diff --git a/testsuite/tests/deriving/should_compile/drv015.hs b/testsuite/tests/deriving/should_compile/drv015.hs index b8575b2..f76da45 100644 --- a/testsuite/tests/deriving/should_compile/drv015.hs +++ b/testsuite/tests/deriving/should_compile/drv015.hs @@ -1,7 +1,7 @@ -- July 07: I'm changing this from "should_compile" to "should_fail". -- It would generate an instance decl like --- insance (Show (f a), Show (g a)) => Show (Pair1 f g a) +-- instance (Show (f a), Show (g a)) => Show (Pair1 f g a) -- and that is not Haskell 98. -- -- See Note [Exotic derived instance contexts] in TcSimplify. From git at git.haskell.org Mon Jul 18 13:57:07 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 18 Jul 2016 13:57:07 +0000 (UTC) Subject: [commit: ghc] branch 'wip/generics-flip' created Message-ID: <20160718135707.0AEB93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/generics-flip Referencing: cb12bdf942df5e61771d69bbb6049f3b23ed580c From git at git.haskell.org Mon Jul 18 13:57:10 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 18 Jul 2016 13:57:10 +0000 (UTC) Subject: [commit: ghc] wip/generics-flip: Implement unboxed sum primitive type (2cef534) Message-ID: <20160718135710.336CA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/generics-flip Link : http://ghc.haskell.org/trac/ghc/changeset/2cef53497114c9ff36110d3a3109bd925d00c30c/ghc >--------------------------------------------------------------- commit 2cef53497114c9ff36110d3a3109bd925d00c30c Author: Ömer Sinan Ağacan Date: Mon Jul 18 10:50:24 2016 +0200 Implement unboxed sum primitive type This patch implements primitive unboxed sum types, as described in https://ghc.haskell.org/trac/ghc/wiki/UnpackedSumTypes. Main changes are: - Add new syntax for unboxed sums types, terms and patterns. Hidden behind `-XUnboxedSums`. - Add unlifted unboxed sum type constructors and data constructors, extend type and pattern checkers and desugarer. - Add new RuntimeRep for unboxed sums. - Extend unarise pass to translate unboxed sums to unboxed tuples right before code generation. - Add `StgRubbishArg` to `StgArg`, and a new type `CmmArg` for better code generation when sum values are involved. - Add user manual section for unboxed sums. Some other changes: - Generalize `UbxTupleRep` to `MultiRep` and `UbxTupAlt` to `MultiValAlt` to be able to use those with both sums and tuples. - Don't use `tyConPrimRep` in `isVoidTy`: `tyConPrimRep` is really wrong, given an `Any` `TyCon`, there's no way to tell what its kind is, but `kindPrimRep` and in turn `tyConPrimRep` returns `PtrRep`. - Fix some bugs on the way: #12375. Not included in this patch: - Update Haddock for new the new unboxed sum syntax. - `TemplateHaskell` support is left as future work. For reviewers: - Front-end code is mostly trivial and adapted from unboxed tuple code for type checking, pattern checking, renaming, desugaring etc. - Main translation routines are in `RepType` and `UnariseStg`. Documentation in `UnariseStg` should be enough for understanding what's going on. Credits: - Johan Tibell wrote the initial front-end and interface file extensions. Reviewers: simonpj, bgamari, alanz, goldfire, RyanGlScott, austin, simonmar, hvr, erikd Subscribers: Iceland_jack, ggreif, ezyang, RyanGlScott, goldfire, thomie, mpickering Differential Revision: https://phabricator.haskell.org/D2259 >--------------------------------------------------------------- 2cef53497114c9ff36110d3a3109bd925d00c30c compiler/basicTypes/BasicTypes.hs | 28 +- compiler/basicTypes/DataCon.hs | 7 +- compiler/basicTypes/Id.hs | 3 +- compiler/basicTypes/IdInfo.hs | 2 +- compiler/basicTypes/Unique.hs | 9 + compiler/cmm/CLabel.hs | 4 +- compiler/cmm/CmmExpr.hs | 12 +- compiler/cmm/CmmLayoutStack.hs | 2 +- compiler/cmm/CmmLive.hs | 4 +- compiler/cmm/CmmParse.y | 8 +- compiler/cmm/CmmUtils.hs | 22 +- compiler/cmm/MkGraph.hs | 74 +- compiler/cmm/PprCmmExpr.hs | 9 + compiler/codeGen/StgCmm.hs | 8 +- compiler/codeGen/StgCmmBind.hs | 10 +- compiler/codeGen/StgCmmClosure.hs | 3 +- compiler/codeGen/StgCmmCon.hs | 3 +- compiler/codeGen/StgCmmEnv.hs | 37 +- compiler/codeGen/StgCmmExpr.hs | 30 +- compiler/codeGen/StgCmmForeign.hs | 7 +- compiler/codeGen/StgCmmHeap.hs | 20 +- compiler/codeGen/StgCmmLayout.hs | 28 +- compiler/codeGen/StgCmmMonad.hs | 19 +- compiler/codeGen/StgCmmPrim.hs | 25 +- compiler/codeGen/StgCmmUtils.hs | 35 +- compiler/coreSyn/CoreArity.hs | 3 + compiler/coreSyn/CoreLint.hs | 12 +- compiler/deSugar/Check.hs | 5 + compiler/deSugar/Coverage.hs | 3 + compiler/deSugar/DsArrows.hs | 1 + compiler/deSugar/DsExpr.hs | 7 + compiler/deSugar/DsForeign.hs | 1 + compiler/deSugar/Match.hs | 7 + compiler/ghc.cabal.in | 1 + compiler/ghc.mk | 1 + compiler/ghci/ByteCodeGen.hs | 146 ++-- compiler/ghci/ByteCodeItbls.hs | 4 +- compiler/ghci/RtClosureInspect.hs | 33 +- compiler/hsSyn/HsExpr.hs | 11 + compiler/hsSyn/HsPat.hs | 19 +- compiler/hsSyn/HsTypes.hs | 7 + compiler/hsSyn/HsUtils.hs | 1 + compiler/iface/BinIface.hs | 139 +++- compiler/iface/MkIface.hs | 1 + compiler/main/Constants.hs | 3 + compiler/main/DynFlags.hs | 1 + compiler/main/InteractiveEval.hs | 3 +- compiler/parser/Lexer.x | 11 +- compiler/parser/Parser.y | 41 +- compiler/parser/RdrHsSyn.hs | 29 +- compiler/prelude/PrelNames.hs | 9 +- compiler/prelude/PrimOp.hs | 5 +- compiler/prelude/TysWiredIn.hs | 121 +++- compiler/prelude/TysWiredIn.hs-boot | 2 + compiler/profiling/SCCfinal.hs | 8 +- compiler/rename/RnExpr.hs | 4 + compiler/rename/RnPat.hs | 5 + compiler/rename/RnTypes.hs | 8 + compiler/simplStg/RepType.hs | 326 +++++++++ compiler/simplStg/RepType.hs-boot | 17 + compiler/simplStg/SimplStg.hs | 3 + compiler/simplStg/StgStats.hs | 2 +- compiler/simplStg/UnariseStg.hs | 755 ++++++++++++++++----- compiler/stgSyn/CoreToStg.hs | 28 +- compiler/stgSyn/StgLint.hs | 32 +- compiler/stgSyn/StgSyn.hs | 45 +- compiler/stranal/WwLib.hs | 1 + compiler/typecheck/TcExpr.hs | 9 + compiler/typecheck/TcHsSyn.hs | 23 +- compiler/typecheck/TcHsType.hs | 11 +- compiler/typecheck/TcPat.hs | 13 + compiler/typecheck/TcPatSyn.hs | 5 + compiler/typecheck/TcRnTypes.hs | 1 + compiler/typecheck/TcType.hs | 25 +- compiler/types/TyCoRep.hs | 13 +- compiler/types/TyCon.hs | 76 ++- compiler/types/Type.hs | 136 +--- compiler/types/Type.hs-boot | 1 - compiler/utils/Outputable.hs | 8 + compiler/vectorise/Vectorise/Builtins/Base.hs | 2 +- compiler/vectorise/Vectorise/Type/TyConDecl.hs | 6 + docs/users_guide/glasgow_exts.rst | 77 +++ includes/stg/MiscClosures.h | 1 + .../ghc-boot-th/GHC/LanguageExtensions/Type.hs | 1 + libraries/ghc-prim/GHC/Types.hs | 1 + rts/StgMiscClosures.cmm | 3 + testsuite/tests/driver/T4437.hs | 3 +- testsuite/tests/unboxedsums/Makefile | 10 + testsuite/tests/unboxedsums/T12375.hs | 17 + testsuite/tests/unboxedsums/T12375.stdout | 1 + testsuite/tests/unboxedsums/all.T | 25 + testsuite/tests/unboxedsums/empty_sum.hs | 20 + testsuite/tests/unboxedsums/empty_sum.stdout | 3 + testsuite/tests/unboxedsums/ffi1.hs | 11 + testsuite/tests/unboxedsums/ffi1.stderr | 23 + testsuite/tests/unboxedsums/module/Lib.hs | 16 + testsuite/tests/unboxedsums/module/Main.hs | 11 + testsuite/tests/unboxedsums/module/Makefile | 16 + testsuite/tests/unboxedsums/module/all.T | 4 + testsuite/tests/unboxedsums/module/sum_mod.stdout | 3 + testsuite/tests/unboxedsums/sum_rr.hs | 8 + testsuite/tests/unboxedsums/sum_rr.stderr | 7 + testsuite/tests/unboxedsums/thunk.hs | 8 + testsuite/tests/unboxedsums/thunk.stdout | 1 + testsuite/tests/unboxedsums/unarise.hs | 17 + .../cgrun052.stdout => unboxedsums/unarise.stdout} | 0 testsuite/tests/unboxedsums/unboxedsums1.hs | 81 +++ testsuite/tests/unboxedsums/unboxedsums1.stdout | 14 + testsuite/tests/unboxedsums/unboxedsums10.hs | 15 + testsuite/tests/unboxedsums/unboxedsums10.stdout | 2 + testsuite/tests/unboxedsums/unboxedsums11.hs | 15 + testsuite/tests/unboxedsums/unboxedsums11.stdout | 2 + testsuite/tests/unboxedsums/unboxedsums2.hs | 34 + testsuite/tests/unboxedsums/unboxedsums2.stdin | 2 + testsuite/tests/unboxedsums/unboxedsums2.stdout | 4 + testsuite/tests/unboxedsums/unboxedsums3.hs | 33 + testsuite/tests/unboxedsums/unboxedsums3.stdout | 6 + testsuite/tests/unboxedsums/unboxedsums4.hs | 3 + testsuite/tests/unboxedsums/unboxedsums4.stderr | 2 + testsuite/tests/unboxedsums/unboxedsums5.hs | 12 + testsuite/tests/unboxedsums/unboxedsums6.hs | 35 + testsuite/tests/unboxedsums/unboxedsums6.stdout | 2 + testsuite/tests/unboxedsums/unboxedsums7.hs | 24 + testsuite/tests/unboxedsums/unboxedsums7.stdout | 1 + testsuite/tests/unboxedsums/unboxedsums8.hs | 37 + testsuite/tests/unboxedsums/unboxedsums8.stdout | 3 + testsuite/tests/unboxedsums/unboxedsums9.hs | 26 + testsuite/tests/unboxedsums/unboxedsums9.stdout | 4 + utils/mkUserGuidePart/Options/Language.hs | 6 + 129 files changed, 2562 insertions(+), 687 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 2cef53497114c9ff36110d3a3109bd925d00c30c From git at git.haskell.org Mon Jul 18 13:57:13 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 18 Jul 2016 13:57:13 +0000 (UTC) Subject: [commit: ghc] wip/generics-flip: testsuite: Add regression test for #11381 (8e1e52f) Message-ID: <20160718135713.5D35E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/generics-flip Link : http://ghc.haskell.org/trac/ghc/changeset/8e1e52ffd0b05bd1f865ce0421a4cae957bf41a5/ghc >--------------------------------------------------------------- commit 8e1e52ffd0b05bd1f865ce0421a4cae957bf41a5 Author: Ben Gamari Date: Mon Jul 18 13:16:00 2016 +0200 testsuite: Add regression test for #11381 >--------------------------------------------------------------- 8e1e52ffd0b05bd1f865ce0421a4cae957bf41a5 testsuite/tests/typecheck/should_compile/T11381.hs | 10 ++++++++++ testsuite/tests/typecheck/should_compile/all.T | 1 + 2 files changed, 11 insertions(+) diff --git a/testsuite/tests/typecheck/should_compile/T11381.hs b/testsuite/tests/typecheck/should_compile/T11381.hs new file mode 100644 index 0000000..9d4d731 --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T11381.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE TypeInType, TypeFamilies #-} +module Kinds where + +import GHC.Types + +type family G (a :: Type) :: Type +type instance G Int = Bool + +type family F (a :: Type) :: G a +type instance F Int = True diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index 7333ffb..995fa2a 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -531,3 +531,4 @@ test('T12067', extra_clean(['T12067a.hi', 'T12067a.o']), multimod_compile, ['T12067', '-v0']) test('T12185', normal, compile, ['']) test('T12133', normal, compile, ['']) +test('T12381', normal, compile, ['']) From git at git.haskell.org Mon Jul 18 13:57:16 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 18 Jul 2016 13:57:16 +0000 (UTC) Subject: [commit: ghc] wip/generics-flip: Flip around imports of GHC.Generics (cb12bdf) Message-ID: <20160718135716.0D1363A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/generics-flip Link : http://ghc.haskell.org/trac/ghc/changeset/cb12bdf942df5e61771d69bbb6049f3b23ed580c/ghc >--------------------------------------------------------------- commit cb12bdf942df5e61771d69bbb6049f3b23ed580c Author: Ben Gamari Date: Mon Jul 18 15:54:16 2016 +0200 Flip around imports of GHC.Generics Previously we had, GHC.Generics imports GHC.Ptr Data.Monoid imports GHC.Generics Data.Foldable imports GHC.Generics Data.Foldable imports Data.Monoid Prelude imports Data.Foldable Unfortunately this meant that any program importing Prelude (essentially all programs) would end up pulling in GHC.Generics and GHC.Ptr unnecessarily. Hopefully helps #12367. >--------------------------------------------------------------- cb12bdf942df5e61771d69bbb6049f3b23ed580c libraries/base/Data/Foldable.hs | 36 ---------------------- libraries/base/Data/Monoid.hs | 19 +++++------- libraries/base/GHC/Generics.hs | 67 +++++++++++++++++++++++++++++++++++++++-- 3 files changed, 72 insertions(+), 50 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc cb12bdf942df5e61771d69bbb6049f3b23ed580c From git at git.haskell.org Mon Jul 18 14:12:01 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 18 Jul 2016 14:12:01 +0000 (UTC) Subject: [commit: ghc] master: Make DeriveFunctor work with unboxed tuples (3fa3fe8) Message-ID: <20160718141201.98A903A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3fa3fe8a9a8afa67829e12efa5d25b76e58a185a/ghc >--------------------------------------------------------------- commit 3fa3fe8a9a8afa67829e12efa5d25b76e58a185a Author: Ryan Scott Date: Mon Jul 18 09:28:42 2016 -0400 Make DeriveFunctor work with unboxed tuples Summary: Unboxed tuples have `RuntimeRep` arguments which `-XDeriveFunctor` was mistaking for actual data constructor arguments. As a result, a derived `Functor` instance for a datatype that contained an unboxed tuple would generate twice as many arguments as it needed for an unboxed tuple pattern match or expression. The solution is to simply put `dropRuntimeRepArgs` in the right place. Fixes #12399. Test Plan: ./validate Reviewers: austin, hvr, bgamari Reviewed By: bgamari Subscribers: thomie, osa1 Differential Revision: https://phabricator.haskell.org/D2404 GHC Trac Issues: #12399 >--------------------------------------------------------------- 3fa3fe8a9a8afa67829e12efa5d25b76e58a185a compiler/typecheck/TcGenDeriv.hs | 8 ++++++-- testsuite/tests/deriving/should_compile/T12399.hs | 7 +++++++ testsuite/tests/deriving/should_compile/all.T | 1 + 3 files changed, 14 insertions(+), 2 deletions(-) diff --git a/compiler/typecheck/TcGenDeriv.hs b/compiler/typecheck/TcGenDeriv.hs index 53a79f8..2eb8c07 100644 --- a/compiler/typecheck/TcGenDeriv.hs +++ b/compiler/typecheck/TcGenDeriv.hs @@ -1701,7 +1701,11 @@ functorLikeTraverse var (FT { ft_triv = caseTrivial, ft_var = caseVar = (caseTyApp fun_ty (last xrs), True) | otherwise = (caseWrongArg, True) -- Non-decomposable (eg type function) where - (xrs,xcs) = unzip (map (go co) args) + -- When folding over an unboxed tuple, we must explicitly drop the + -- runtime rep arguments, or else GHC will generate twice as many + -- variables in a unboxed tuple pattern match and expression as it + -- actually needs. See Trac #12399 + (xrs,xcs) = unzip (map (go co) (dropRuntimeRepArgs args)) go co (ForAllTy (TvBndr v vis) x) | isVisibleArgFlag vis = panic "unexpected visible binder" | v /= var && xc = (caseForAll v xr,True) @@ -2813,7 +2817,7 @@ a is the last type variable in a given datatype): * ft_tup: A tuple type which mentions the last type variable in at least one of its fields. The TyCon argument of ft_tup represents the particular tuple's type constructor. - Examples: (a, Int), (Maybe a, [a], Either a Int) + Examples: (a, Int), (Maybe a, [a], Either a Int), (# Int, a #) * ft_ty_app: A type is being applied to the last type parameter, where the applied type does not mention the last type parameter (if it diff --git a/testsuite/tests/deriving/should_compile/T12399.hs b/testsuite/tests/deriving/should_compile/T12399.hs new file mode 100644 index 0000000..c3429f8 --- /dev/null +++ b/testsuite/tests/deriving/should_compile/T12399.hs @@ -0,0 +1,7 @@ +{-# LANGUAGE DeriveFunctor, MagicHash, UnboxedTuples #-} +module T12399 where + +import GHC.Exts + +newtype RmLoopsM a = RmLoopsM { runRmLoops :: Int# -> (# Int#, a #) } + deriving Functor diff --git a/testsuite/tests/deriving/should_compile/all.T b/testsuite/tests/deriving/should_compile/all.T index a81c4ce..e42e34d 100644 --- a/testsuite/tests/deriving/should_compile/all.T +++ b/testsuite/tests/deriving/should_compile/all.T @@ -71,3 +71,4 @@ test('T11732b', normal, compile, ['']) test('T11732c', normal, compile, ['']) test('T11833', normal, compile, ['']) test('T12245', normal, compile, ['']) +test('T12399', normal, compile, ['']) From git at git.haskell.org Mon Jul 18 14:12:04 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 18 Jul 2016 14:12:04 +0000 (UTC) Subject: [commit: ghc] master: Fix Template Haskell reification of unboxed tuple types (514c4a4) Message-ID: <20160718141204.EE9143A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/514c4a4741f3881672f1ccc1fe6d08a5d596bb87/ghc >--------------------------------------------------------------- commit 514c4a4741f3881672f1ccc1fe6d08a5d596bb87 Author: Ryan Scott Date: Mon Jul 18 09:29:05 2016 -0400 Fix Template Haskell reification of unboxed tuple types Summary: Previously, Template Haskell reified unboxed tuple types as boxed tuples with twice the appropriate arity. Fixes #12403. Test Plan: make test TEST=T12403 Reviewers: hvr, goldfire, austin, bgamari Reviewed By: goldfire Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2405 GHC Trac Issues: #12403 >--------------------------------------------------------------- 514c4a4741f3881672f1ccc1fe6d08a5d596bb87 compiler/typecheck/TcSplice.hs | 4 +++- docs/users_guide/8.0.2-notes.rst | 6 ++++++ testsuite/tests/th/{T10697_decided_1.hs => T12403.hs} | 5 +++-- testsuite/tests/th/T12403.stdout | 1 + testsuite/tests/th/all.T | 2 ++ 5 files changed, 15 insertions(+), 3 deletions(-) diff --git a/compiler/typecheck/TcSplice.hs b/compiler/typecheck/TcSplice.hs index fa68d2e..6ae1ba4 100644 --- a/compiler/typecheck/TcSplice.hs +++ b/compiler/typecheck/TcSplice.hs @@ -1819,7 +1819,9 @@ reify_tc_app tc tys tc_binders = tyConBinders tc tc_res_kind = tyConResKind tc - r_tc | isTupleTyCon tc = if isPromotedDataCon tc + r_tc | isUnboxedTupleTyCon tc = TH.UnboxedTupleT (arity `div` 2) + -- See Note [Unboxed tuple RuntimeRep vars] in TyCon + | isTupleTyCon tc = if isPromotedDataCon tc then TH.PromotedTupleT arity else TH.TupleT arity | tc `hasKey` listTyConKey = TH.ListT diff --git a/docs/users_guide/8.0.2-notes.rst b/docs/users_guide/8.0.2-notes.rst index d5d442f..39ad028 100644 --- a/docs/users_guide/8.0.2-notes.rst +++ b/docs/users_guide/8.0.2-notes.rst @@ -32,6 +32,12 @@ Compiler initial cmm from STG-to-C-- code generation and :ghc-flag:`-ddump-cmm-verbose` to obtain the intermediates from all C-- pipeline stages. +Template Haskell +~~~~~~~~~~~~~~~~ + +- Reifying types that contain unboxed tuples now works correctly. (Previously, + Template Haskell reified unboxed tuples as boxed tuples with twice their + appropriate arity.) TODO FIXME Heading title ~~~~~~~~~~~~~~~~~~~~~~~~ diff --git a/testsuite/tests/th/T10697_decided_1.hs b/testsuite/tests/th/T12403.hs similarity index 50% copy from testsuite/tests/th/T10697_decided_1.hs copy to testsuite/tests/th/T12403.hs index 241cec3..d4aad62 100644 --- a/testsuite/tests/th/T10697_decided_1.hs +++ b/testsuite/tests/th/T12403.hs @@ -1,11 +1,12 @@ {-# LANGUAGE TemplateHaskell #-} +{-# LANGUAGE UnboxedTuples #-} module Main where import Language.Haskell.TH -data T = T {-# UNPACK #-} !Int !Int Int +data T = T (# Int, Int #) $(return []) main :: IO () -main = putStrLn $(reifyConStrictness 'T >>= stringE . show) +main = putStrLn $(reify ''T >>= stringE . pprint) diff --git a/testsuite/tests/th/T12403.stdout b/testsuite/tests/th/T12403.stdout new file mode 100644 index 0000000..9b75e8b --- /dev/null +++ b/testsuite/tests/th/T12403.stdout @@ -0,0 +1 @@ +data Main.T = Main.T ((# , #) GHC.Types.Int GHC.Types.Int) diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index ff2d6d4..3f448d7 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -418,3 +418,5 @@ test('T11484', normal, compile, ['-v0']) test('T8761', normal, compile, ['-v0 -ddump-splices -dsuppress-uniques']) test('T12130', extra_clean(['T12130a.hi','T12130a.o']), multimod_compile, ['T12130', '-v0 ' + config.ghc_th_way_flags]) +test('T12403', omit_ways(['ghci']), + compile_and_run, ['-v0 -ddump-splices -dsuppress-uniques']) From git at git.haskell.org Mon Jul 18 17:52:40 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 18 Jul 2016 17:52:40 +0000 (UTC) Subject: [commit: ghc] master: Make okConIdOcc recognize unboxed tuples (1fc41d3) Message-ID: <20160718175240.447AC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1fc41d3274b5bf62f027aa6c7df57998db494938/ghc >--------------------------------------------------------------- commit 1fc41d3274b5bf62f027aa6c7df57998db494938 Author: Ryan Scott Date: Mon Jul 18 13:51:53 2016 -0400 Make okConIdOcc recognize unboxed tuples Summary: `okConIdOcc`, which validates that a type or constructor name is valid for splicing using Template Haskell, has a special case for tuples, but neglects to look for unboxed tuples, causing some sensible Template Haskell code involving unboxed tuples to be rejected. Fixes #12407. Test Plan: make test TEST=T12407 Reviewers: austin, bgamari, hvr, goldfire Reviewed By: goldfire Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2410 GHC Trac Issues: #12407 >--------------------------------------------------------------- 1fc41d3274b5bf62f027aa6c7df57998db494938 compiler/basicTypes/Lexeme.hs | 21 +++++++++++++-------- testsuite/tests/th/T12407.hs | 17 +++++++++++++++++ testsuite/tests/th/all.T | 1 + 3 files changed, 31 insertions(+), 8 deletions(-) diff --git a/compiler/basicTypes/Lexeme.hs b/compiler/basicTypes/Lexeme.hs index 22515c1..ef5fa12 100644 --- a/compiler/basicTypes/Lexeme.hs +++ b/compiler/basicTypes/Lexeme.hs @@ -154,18 +154,23 @@ okVarSymOcc str = all okSymChar str && -- starts with an acceptable letter? okConIdOcc :: String -> Bool okConIdOcc str = okIdOcc str || - is_tuple_name1 str + is_tuple_name1 True str || + -- Is it a boxed tuple... + is_tuple_name1 False str + -- ...or an unboxed tuple (Trac #12407)? where -- check for tuple name, starting at the beginning - is_tuple_name1 ('(' : rest) = is_tuple_name2 rest - is_tuple_name1 _ = False + is_tuple_name1 True ('(' : rest) = is_tuple_name2 True rest + is_tuple_name1 False ('(' : '#' : rest) = is_tuple_name2 False rest + is_tuple_name1 _ _ = False -- check for tuple tail - is_tuple_name2 ")" = True - is_tuple_name2 (',' : rest) = is_tuple_name2 rest - is_tuple_name2 (ws : rest) - | isSpace ws = is_tuple_name2 rest - is_tuple_name2 _ = False + is_tuple_name2 True ")" = True + is_tuple_name2 False "#)" = True + is_tuple_name2 boxed (',' : rest) = is_tuple_name2 boxed rest + is_tuple_name2 boxed (ws : rest) + | isSpace ws = is_tuple_name2 boxed rest + is_tuple_name2 _ _ = False -- | Is this an acceptable symbolic constructor name, assuming it -- starts with an acceptable character? diff --git a/testsuite/tests/th/T12407.hs b/testsuite/tests/th/T12407.hs new file mode 100644 index 0000000..daa3e34 --- /dev/null +++ b/testsuite/tests/th/T12407.hs @@ -0,0 +1,17 @@ +{-# LANGUAGE TemplateHaskell #-} +{-# LANGUAGE UnboxedTuples #-} +module T12407 where + +import Language.Haskell.TH.Lib +import Language.Haskell.TH.Syntax + +$(do let ubxTup = conT (unboxedTupleTypeName 2) `appT` conT ''Int + `appT` conT ''Int + x <- newName "x" + y <- newName "y" + + [d| f :: $(ubxTup) -> $(ubxTup) + f $(conP (unboxedTupleDataName 2) [varP x, varP y]) + = $(conE (unboxedTupleDataName 2) `appE` varE x + `appE` varE y) + |]) diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index 3f448d7..5cece92 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -420,3 +420,4 @@ test('T12130', extra_clean(['T12130a.hi','T12130a.o']), multimod_compile, ['T12130', '-v0 ' + config.ghc_th_way_flags]) test('T12403', omit_ways(['ghci']), compile_and_run, ['-v0 -ddump-splices -dsuppress-uniques']) +test('T12407', omit_ways(['ghci']), compile, ['-v0']) From git at git.haskell.org Mon Jul 18 17:57:39 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 18 Jul 2016 17:57:39 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Fix two buglets in 17eb241 noticed by Richard (6edd2a7) Message-ID: <20160718175739.646AE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/6edd2a71eb63ae7c94032c51675fb0998cfe21fc/ghc >--------------------------------------------------------------- commit 6edd2a71eb63ae7c94032c51675fb0998cfe21fc Author: Simon Peyton Jones Date: Wed Apr 20 15:56:44 2016 +0100 Fix two buglets in 17eb241 noticed by Richard These are corner cases in 17eb241 Refactor computing dependent type vars and I couldn't even come up with a test case * In TcSimplify.simplifyInfer, in the promotion step, be sure to promote kind variables as well as type variables. * In TcType.spiltDepVarsOfTypes, the CoercionTy case, be sure to get the free coercion variables too. >--------------------------------------------------------------- 6edd2a71eb63ae7c94032c51675fb0998cfe21fc compiler/typecheck/TcSimplify.hs | 29 +++++++++++++++-------------- compiler/typecheck/TcType.hs | 7 +------ 2 files changed, 16 insertions(+), 20 deletions(-) diff --git a/compiler/typecheck/TcSimplify.hs b/compiler/typecheck/TcSimplify.hs index 70de14c..853976c 100644 --- a/compiler/typecheck/TcSimplify.hs +++ b/compiler/typecheck/TcSimplify.hs @@ -604,10 +604,10 @@ simplifyInfer rhs_tclvl apply_mr sigs name_taus wanteds -- Decide what type variables and constraints to quantify ; zonked_taus <- mapM (TcM.zonkTcType . snd) name_taus - ; let zonked_tau_tkvs = splitDepVarsOfTypes zonked_taus + ; let zonked_tau_dvs = splitDepVarsOfTypes zonked_taus ; (qtvs, bound_theta) <- decideQuantification apply_mr sigs name_taus - quant_pred_candidates zonked_tau_tkvs + quant_pred_candidates zonked_tau_dvs -- Promote any type variables that are free in the inferred type -- of the function: @@ -621,24 +621,25 @@ simplifyInfer rhs_tclvl apply_mr sigs name_taus wanteds -- we don't quantify over beta (since it is fixed by envt) -- so we must promote it! The inferred type is just -- f :: beta -> beta - ; zonked_tau_tvs <- TcM.zonkTyCoVarsAndFV (dv_tvs zonked_tau_tkvs) + ; zonked_tau_tkvs <- TcM.zonkTyCoVarsAndFV $ + dv_kvs zonked_tau_dvs `unionVarSet` dv_tvs zonked_tau_dvs -- decideQuantification turned some meta tyvars into -- quantified skolems, so we have to zonk again - ; let phi_tvs = tyCoVarsOfTypes bound_theta - `unionVarSet` zonked_tau_tvs + ; let phi_tkvs = tyCoVarsOfTypes bound_theta -- Already zonked + `unionVarSet` zonked_tau_tkvs + promote_tkvs = closeOverKinds phi_tkvs `delVarSetList` qtvs - promote_tvs = closeOverKinds phi_tvs `delVarSetList` qtvs - ; MASSERT2( closeOverKinds promote_tvs `subVarSet` promote_tvs - , ppr phi_tvs $$ - ppr (closeOverKinds phi_tvs) $$ - ppr promote_tvs $$ - ppr (closeOverKinds promote_tvs) ) + ; MASSERT2( closeOverKinds promote_tkvs `subVarSet` promote_tkvs + , ppr phi_tkvs $$ + ppr (closeOverKinds phi_tkvs) $$ + ppr promote_tkvs $$ + ppr (closeOverKinds promote_tkvs) ) -- we really don't want a type to be promoted when its kind isn't! -- promoteTyVar ignores coercion variables ; outer_tclvl <- TcM.getTcLevel - ; mapM_ (promoteTyVar outer_tclvl) (varSetElems promote_tvs) + ; mapM_ (promoteTyVar outer_tclvl) (varSetElems promote_tkvs) -- Emit an implication constraint for the -- remaining constraints from the RHS @@ -664,8 +665,8 @@ simplifyInfer rhs_tclvl apply_mr sigs name_taus wanteds ; traceTc "} simplifyInfer/produced residual implication for quantification" $ vcat [ text "quant_pred_candidates =" <+> ppr quant_pred_candidates , text "zonked_taus" <+> ppr zonked_taus - , text "zonked_tau_tvs=" <+> ppr zonked_tau_tvs - , text "promote_tvs=" <+> ppr promote_tvs + , text "zonked_tau_dvs=" <+> ppr zonked_tau_dvs + , text "promote_tvs=" <+> ppr promote_tkvs , text "bound_theta =" <+> ppr bound_theta , text "qtvs =" <+> ppr qtvs , text "implic =" <+> ppr implic ] diff --git a/compiler/typecheck/TcType.hs b/compiler/typecheck/TcType.hs index 4f7d861..1e3f72b 100644 --- a/compiler/typecheck/TcType.hs +++ b/compiler/typecheck/TcType.hs @@ -931,12 +931,7 @@ split_dep_vars = go go (LitTy {}) = mempty go (CastTy ty co) = go ty `mappend` Pair (tyCoVarsOfCo co) emptyVarSet - go (CoercionTy co) = go_co co - - go_co co = let Pair ty1 ty2 = coercionKind co in - -- co :: ty1 ~ ty2 - go ty1 `mappend` go ty2 - + go (CoercionTy co) = Pair (tyCoVarsOfCo co) emptyVarSet isTouchableOrFmv ctxt_tclvl tv = ASSERT2( isTcTyVar tv, ppr tv ) From git at git.haskell.org Mon Jul 18 17:57:42 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 18 Jul 2016 17:57:42 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Make benign non-determinism in pretty-printing more obvious (d4e29d2) Message-ID: <20160718175742.0CD373A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/d4e29d21e1488cfe0d14ad1144726f1adf874744/ghc >--------------------------------------------------------------- commit d4e29d21e1488cfe0d14ad1144726f1adf874744 Author: Bartosz Nitka Date: Mon Apr 18 07:32:03 2016 -0700 Make benign non-determinism in pretty-printing more obvious This change takes us one step closer to being able to remove `varSetElemsWellScoped`. The end goal is to make every source of non-determinism obvious at the source level, so that when we achieve determinism it doesn't get broken accidentally. Test Plan: compile GHC Reviewers: simonmar, goldfire, simonpj, austin, bgamari Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2123 GHC Trac Issues: #4012 >--------------------------------------------------------------- d4e29d21e1488cfe0d14ad1144726f1adf874744 compiler/basicTypes/VarSet.hs | 21 ++++++++++++++++++++- compiler/typecheck/FamInst.hs | 4 ++-- compiler/typecheck/FunDeps.hs | 6 +++--- compiler/utils/UniqFM.hs | 20 +++++++++++++++++++- 4 files changed, 44 insertions(+), 7 deletions(-) diff --git a/compiler/basicTypes/VarSet.hs b/compiler/basicTypes/VarSet.hs index 1cd9e21..8ece555 100644 --- a/compiler/basicTypes/VarSet.hs +++ b/compiler/basicTypes/VarSet.hs @@ -21,6 +21,7 @@ module VarSet ( lookupVarSet, lookupVarSetByName, mapVarSet, sizeVarSet, seqVarSet, elemVarSetByKey, partitionVarSet, + pluralVarSet, pprVarSet, -- * Deterministic Var set types DVarSet, DIdSet, DTyVarSet, DTyCoVarSet, @@ -45,8 +46,9 @@ import Unique import Name ( Name ) import UniqSet import UniqDSet -import UniqFM( disjointUFM ) +import UniqFM( disjointUFM, pluralUFM, pprUFM ) import UniqDFM( disjointUDFM ) +import Outputable (SDoc) -- | A non-deterministic set of variables. -- See Note [Deterministic UniqFM] in UniqDFM for explanation why it's not @@ -169,6 +171,23 @@ transCloVarSet fn seeds seqVarSet :: VarSet -> () seqVarSet s = sizeVarSet s `seq` () +-- | Determines the pluralisation suffix appropriate for the length of a set +-- in the same way that plural from Outputable does for lists. +pluralVarSet :: VarSet -> SDoc +pluralVarSet = pluralUFM + +-- | Pretty-print a non-deterministic set. +-- The order of variables is non-deterministic and for pretty-printing that +-- shouldn't be a problem. +-- Having this function helps contain the non-determinism created with +-- varSetElems. +pprVarSet :: ([Var] -> SDoc) -- ^ The pretty printing function to use on the + -- elements + -> VarSet -- ^ The things to be pretty printed + -> SDoc -- ^ 'SDoc' where the things have been pretty + -- printed +pprVarSet = pprUFM + -- Deterministic VarSet -- See Note [Deterministic UniqFM] in UniqDFM for explanation why we need -- DVarSet. diff --git a/compiler/typecheck/FamInst.hs b/compiler/typecheck/FamInst.hs index 2ff256d..1d9e1ce 100644 --- a/compiler/typecheck/FamInst.hs +++ b/compiler/typecheck/FamInst.hs @@ -562,12 +562,12 @@ unusedInjectiveVarsErr (Pair invis_vars vis_vars) errorBuilder tyfamEqn = errorBuilder (injectivityErrorHerald True $$ msg) [tyfamEqn] where - tvs = varSetElemsWellScoped (invis_vars `unionVarSet` vis_vars) + tvs = invis_vars `unionVarSet` vis_vars has_types = not $ isEmptyVarSet vis_vars has_kinds = not $ isEmptyVarSet invis_vars doc = sep [ what <+> text "variable" <> - plural tvs <+> pprQuotedList tvs + pluralVarSet tvs <+> pprVarSet (pprQuotedList . toposortTyVars) tvs , text "cannot be inferred from the right-hand side." ] what = case (has_types, has_kinds) of (True, True) -> text "Type and kind" diff --git a/compiler/typecheck/FunDeps.hs b/compiler/typecheck/FunDeps.hs index 87fb4ff..776a9f1 100644 --- a/compiler/typecheck/FunDeps.hs +++ b/compiler/typecheck/FunDeps.hs @@ -387,7 +387,7 @@ checkInstCoverage be_liberal clas theta inst_taus liberal_undet_tvs = (`minusVarSet` closed_ls_tvs) <$> rs_tvs conserv_undet_tvs = (`minusVarSet` ls_tvs) <$> rs_tvs - undet_list = varSetElemsWellScoped (fold undetermined_tvs) + undet_set = fold undetermined_tvs msg = vcat [ -- text "ls_tvs" <+> ppr ls_tvs -- , text "closed ls_tvs" <+> ppr (closeOverKinds ls_tvs) @@ -407,8 +407,8 @@ checkInstCoverage be_liberal clas theta inst_taus else text "do not jointly") <+> text "determine rhs type"<>plural rs <+> pprQuotedList rs ] - , text "Un-determined variable" <> plural undet_list <> colon - <+> pprWithCommas ppr undet_list + , text "Un-determined variable" <> pluralVarSet undet_set <> colon + <+> pprVarSet (pprWithCommas ppr) undet_set , ppWhen (isEmptyVarSet $ pSnd undetermined_tvs) $ text "(Use -fprint-explicit-kinds to see the kind variables in the types)" , ppWhen (not be_liberal && diff --git a/compiler/utils/UniqFM.hs b/compiler/utils/UniqFM.hs index e261df7..4a5f14f 100644 --- a/compiler/utils/UniqFM.hs +++ b/compiler/utils/UniqFM.hs @@ -67,7 +67,7 @@ module UniqFM ( eltsUFM, keysUFM, splitUFM, ufmToSet_Directly, ufmToList, - joinUFM, pprUniqFM + joinUFM, pprUniqFM, pprUFM, pluralUFM ) where import Unique ( Uniquable(..), Unique, getKey ) @@ -327,3 +327,21 @@ pprUniqFM ppr_elt ufm = brackets $ fsep $ punctuate comma $ [ ppr uq <+> text ":->" <+> ppr_elt elt | (uq, elt) <- ufmToList ufm ] + +-- | Pretty-print a non-deterministic set. +-- The order of variables is non-deterministic and for pretty-printing that +-- shouldn't be a problem. +-- Having this function helps contain the non-determinism created with +-- eltsUFM. +pprUFM :: ([a] -> SDoc) -- ^ The pretty printing function to use on the elements + -> UniqFM a -- ^ The things to be pretty printed + -> SDoc -- ^ 'SDoc' where the things have been pretty + -- printed +pprUFM pp ufm = pp (eltsUFM ufm) + +-- | Determines the pluralisation suffix appropriate for the length of a set +-- in the same way that plural from Outputable does for lists. +pluralUFM :: UniqFM a -> SDoc +pluralUFM ufm + | sizeUFM ufm == 1 = empty + | otherwise = char 's' From git at git.haskell.org Mon Jul 18 17:57:44 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 18 Jul 2016 17:57:44 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Refactor computing dependent type vars (ce6d237) Message-ID: <20160718175744.B47AD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/ce6d237c8e52c8b7436aef25c07abcf6d8381daf/ghc >--------------------------------------------------------------- commit ce6d237c8e52c8b7436aef25c07abcf6d8381daf Author: Simon Peyton Jones Date: Mon Apr 18 15:01:13 2016 +0100 Refactor computing dependent type vars There should be no change in behaviour here * Move splitDepVarsOfType(s) from Type to TcType * Define data type TcType.TcDepVars, document what it means, and use it where appropriate, notably in splitDepVarsOfType(s) * Use it in TcMType.quantifyTyVars and friends >--------------------------------------------------------------- ce6d237c8e52c8b7436aef25c07abcf6d8381daf compiler/typecheck/TcHsType.hs | 29 ++++++------ compiler/typecheck/TcMType.hs | 56 ++++++++++++----------- compiler/typecheck/TcPatSyn.hs | 22 ++++----- compiler/typecheck/TcSimplify.hs | 33 +++++++------- compiler/typecheck/TcType.hs | 96 ++++++++++++++++++++++++++++++++++++++++ compiler/types/Type.hs | 42 ------------------ 6 files changed, 165 insertions(+), 113 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc ce6d237c8e52c8b7436aef25c07abcf6d8381daf From git at git.haskell.org Mon Jul 18 17:57:47 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 18 Jul 2016 17:57:47 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Kill varSetElems in markNominal (dfff8e1) Message-ID: <20160718175747.596AB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/dfff8e1a105570455b9b0bbb7a59ec8991a8c1bc/ghc >--------------------------------------------------------------- commit dfff8e1a105570455b9b0bbb7a59ec8991a8c1bc Author: Bartosz Nitka Date: Tue Apr 26 13:04:08 2016 -0700 Kill varSetElems in markNominal varSetElems introduces unnecessary nondeterminism and it was straighforward to just get a deterministic list. Test Plan: ./validate Reviewers: austin, goldfire, bgamari, simonmar, simonpj Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2145 GHC Trac Issues: #4012 >--------------------------------------------------------------- dfff8e1a105570455b9b0bbb7a59ec8991a8c1bc compiler/typecheck/TcTyDecls.hs | 21 +++++++++++---------- compiler/types/TyCoRep.hs | 2 +- 2 files changed, 12 insertions(+), 11 deletions(-) diff --git a/compiler/typecheck/TcTyDecls.hs b/compiler/typecheck/TcTyDecls.hs index a4b6537..53b1c08 100644 --- a/compiler/typecheck/TcTyDecls.hs +++ b/compiler/typecheck/TcTyDecls.hs @@ -31,7 +31,7 @@ module TcTyDecls( import TcRnMonad import TcEnv import TcBinds( tcRecSelBinds ) -import TyCoRep( Type(..), TyBinder(..), delBinderVar ) +import TyCoRep( Type(..), TyBinder(..), delBinderVarFV ) import TcType import TysWiredIn( unitTy ) import MkCore( rEC_SEL_ERROR_ID ) @@ -61,6 +61,7 @@ import Maybes import Data.List import Bag import FastString +import FV import Control.Monad @@ -726,21 +727,21 @@ irExTyVars orig_tvs thing = go emptyVarSet orig_tvs markNominal :: TyVarSet -- local variables -> Type -> RoleM () -markNominal lcls ty = let nvars = get_ty_vars ty `minusVarSet` lcls in - mapM_ (updateRole Nominal) (varSetElems nvars) +markNominal lcls ty = let nvars = fvVarList (FV.delFVs lcls $ get_ty_vars ty) in + mapM_ (updateRole Nominal) nvars where -- get_ty_vars gets all the tyvars (no covars!) from a type *without* -- recurring into coercions. Recall: coercions are totally ignored during -- role inference. See [Coercions in role inference] - get_ty_vars (TyVarTy tv) = unitVarSet tv - get_ty_vars (AppTy t1 t2) = get_ty_vars t1 `unionVarSet` get_ty_vars t2 - get_ty_vars (TyConApp _ tys) = foldr (unionVarSet . get_ty_vars) emptyVarSet tys + get_ty_vars (TyVarTy tv) = FV.unitFV tv + get_ty_vars (AppTy t1 t2) = get_ty_vars t1 `unionFV` get_ty_vars t2 + get_ty_vars (TyConApp _ tys) = mapUnionFV get_ty_vars tys get_ty_vars (ForAllTy bndr ty) - = get_ty_vars ty `delBinderVar` bndr - `unionVarSet` (tyCoVarsOfType $ binderType bndr) - get_ty_vars (LitTy {}) = emptyVarSet + = delBinderVarFV bndr (get_ty_vars ty) + `unionFV` (tyCoFVsOfType $ binderType bndr) + get_ty_vars (LitTy {}) = emptyFV get_ty_vars (CastTy ty _) = get_ty_vars ty - get_ty_vars (CoercionTy _) = emptyVarSet + get_ty_vars (CoercionTy _) = emptyFV -- like lookupRoles, but with Nominal tags at the end for oversaturated TyConApps lookupRolesX :: TyCon -> RoleM [Role] diff --git a/compiler/types/TyCoRep.hs b/compiler/types/TyCoRep.hs index 7054ed5..59799e1 100644 --- a/compiler/types/TyCoRep.hs +++ b/compiler/types/TyCoRep.hs @@ -45,7 +45,7 @@ module TyCoRep ( -- Functions over binders binderType, delBinderVar, isInvisibleBinder, isVisibleBinder, - isNamedBinder, isAnonBinder, + isNamedBinder, isAnonBinder, delBinderVarFV, -- Functions over coercions pickLR, From git at git.haskell.org Mon Jul 18 17:57:50 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 18 Jul 2016 17:57:50 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Kill varSetElemsWellScoped in quantifyTyVars (2844eaf) Message-ID: <20160718175750.0D2F63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/2844eaf5e6272755416b9d6e4aa58ef00285ddd8/ghc >--------------------------------------------------------------- commit 2844eaf5e6272755416b9d6e4aa58ef00285ddd8 Author: Bartosz Nitka Date: Tue Apr 26 05:58:24 2016 -0700 Kill varSetElemsWellScoped in quantifyTyVars varSetElemsWellScoped introduces unnecessary non-determinism in inferred type signatures. Removing this instance required changing the representation of TcDepVars to use deterministic sets. This is the last occurence of varSetElemsWellScoped, allowing me to finally remove it. Test Plan: ./validate I will update the expected outputs when commiting, some reordering of type variables in types is expected. Reviewers: goldfire, simonpj, austin, bgamari Reviewed By: simonpj Subscribers: thomie, simonmar Differential Revision: https://phabricator.haskell.org/D2135 GHC Trac Issues: #4012 >--------------------------------------------------------------- 2844eaf5e6272755416b9d6e4aa58ef00285ddd8 compiler/basicTypes/VarSet.hs | 11 +++- compiler/typecheck/TcHsType.hs | 2 +- compiler/typecheck/TcMType.hs | 44 +++++++++---- compiler/typecheck/TcSimplify.hs | 39 ++++++++++-- compiler/typecheck/TcType.hs | 46 +++++++++----- compiler/types/Type.hs | 13 ++-- compiler/types/Type.hs-boot | 4 +- compiler/utils/UniqDFM.hs | 16 ++++- compiler/utils/UniqDSet.hs | 8 ++- compiler/utils/UniqFM.hs | 5 +- .../tests/dependent/should_fail/T11334b.stderr | 6 +- testsuite/tests/driver/werror.stderr | 2 +- testsuite/tests/gadt/gadt13.stderr | 12 ++-- testsuite/tests/gadt/gadt7.stderr | 18 +++--- .../tests/ghci.debugger/scripts/break026.stdout | 20 +++--- testsuite/tests/ghci/scripts/T11524a.stdout | 2 +- testsuite/tests/ghci/scripts/T7587.stdout | 2 +- testsuite/tests/ghci/scripts/T7730.stdout | 4 +- testsuite/tests/ghci/scripts/T7939.stdout | 4 +- testsuite/tests/ghci/scripts/T8776.stdout | 2 +- .../indexed-types/should_compile/T3017.stderr | 2 +- .../indexed-types/should_compile/T8889.stderr | 2 +- .../tests/indexed-types/should_fail/T7354.stderr | 8 +-- .../tests/indexed-types/should_fail/T8518.stderr | 8 +-- testsuite/tests/module/mod71.stderr | 10 +-- testsuite/tests/module/mod72.stderr | 2 +- .../tests/parser/should_compile/read014.stderr | 2 +- .../tests/parser/should_fail/readFail003.stderr | 6 +- .../should_compile/ExtraConstraints3.stderr | 72 +++++++++++----------- .../partial-sigs/should_compile/NamedTyVar.stderr | 4 +- .../partial-sigs/should_compile/SkipMany.stderr | 2 +- .../partial-sigs/should_compile/T10438.stderr | 4 +- .../should_compile/UncurryNamed.stderr | 2 +- .../WarningWildcardInstantiations.stderr | 30 ++++----- .../tests/partial-sigs/should_fail/T10045.stderr | 12 ++-- .../should_fail/WildcardInstantiations.stderr | 28 ++++----- .../tests/patsyn/should_compile/T11213.stderr | 2 +- testsuite/tests/polykinds/T7438.stderr | 16 ++--- testsuite/tests/polykinds/T7524.stderr | 2 +- testsuite/tests/rename/should_fail/T2993.stderr | 2 +- .../tests/typecheck/should_compile/T10971a.stderr | 2 +- .../tests/typecheck/should_compile/tc141.stderr | 6 +- .../tests/typecheck/should_compile/tc168.stderr | 2 +- .../tests/typecheck/should_compile/tc231.stderr | 2 +- testsuite/tests/typecheck/should_fail/T5853.stderr | 24 ++++---- .../tests/typecheck/should_fail/T6018fail.stderr | 6 +- testsuite/tests/typecheck/should_fail/T7453.stderr | 18 +++--- testsuite/tests/typecheck/should_fail/T7734.stderr | 12 ++-- testsuite/tests/typecheck/should_fail/T8142.stderr | 2 +- testsuite/tests/typecheck/should_fail/T9109.stderr | 12 ++-- .../tests/typecheck/should_fail/tcfail004.stderr | 6 +- .../tests/typecheck/should_fail/tcfail033.stderr | 8 +-- .../tests/typecheck/should_fail/tcfail049.stderr | 2 +- .../tests/typecheck/should_fail/tcfail050.stderr | 2 +- .../tests/typecheck/should_fail/tcfail140.stderr | 4 +- .../tests/typecheck/should_fail/tcfail198.stderr | 8 +-- 56 files changed, 345 insertions(+), 247 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 2844eaf5e6272755416b9d6e4aa58ef00285ddd8 From git at git.haskell.org Mon Jul 18 17:57:52 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 18 Jul 2016 17:57:52 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Kill varSetElems in TcErrors (44c0a5b) Message-ID: <20160718175752.A989B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/44c0a5b8564bd164e7fde55abe2c79dd0c0c8fe7/ghc >--------------------------------------------------------------- commit 44c0a5b8564bd164e7fde55abe2c79dd0c0c8fe7 Author: Bartosz Nitka Date: Tue Apr 26 08:47:21 2016 -0700 Kill varSetElems in TcErrors The uses of varSetElems in these places are unnecessary and while it doesn't intruduce non-determinism in the ABI the plan is to get rid of all varSetElems to get some compile time guarantees. Test Plan: ./validate Reviewers: austin, simonmar, bgamari, goldfire, simonpj Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2141 GHC Trac Issues: #4012 >--------------------------------------------------------------- 44c0a5b8564bd164e7fde55abe2c79dd0c0c8fe7 compiler/typecheck/TcErrors.hs | 14 ++++----- .../tests/dependent/should_fail/T11407.stderr | 2 +- .../tests/indexed-types/should_fail/T2693.stderr | 8 ++--- testsuite/tests/typecheck/should_fail/T4921.stderr | 34 +++++++++++----------- 4 files changed, 29 insertions(+), 29 deletions(-) diff --git a/compiler/typecheck/TcErrors.hs b/compiler/typecheck/TcErrors.hs index 1418a2b..96c5530 100644 --- a/compiler/typecheck/TcErrors.hs +++ b/compiler/typecheck/TcErrors.hs @@ -52,6 +52,7 @@ import StaticFlags ( opt_PprStyle_Debug ) import ListSetOps ( equivClasses ) import Maybes import qualified GHC.LanguageExtensions as LangExt +import FV ( fvVarList, unionFV ) import Control.Monad ( when ) import Data.List ( partition, mapAccumL, nub, sortBy ) @@ -175,7 +176,7 @@ report_unsolved mb_binds_var err_as_warn type_errors expr_holes type_holes wante free_tvs = tyCoVarsOfWC wanted ; traceTc "reportUnsolved (after zonking and tidying):" $ - vcat [ pprTvBndrs (varSetElems free_tvs) + vcat [ pprVarSet pprTvBndrs free_tvs , ppr wanted ] ; warn_redundant <- woptM Opt_WarnRedundantConstraints @@ -1333,8 +1334,8 @@ mkTyVarEqErr dflags ctxt report ct oriented tv1 ty2 interesting_tyvars = filter (not . isEmptyVarSet . tyCoVarsOfType . tyVarKind) $ filter isTyVar $ - varSetElems $ - tyCoVarsOfType ty1 `unionVarSet` tyCoVarsOfType ty2 + fvVarList $ + tyCoFVsOfType ty1 `unionFV` tyCoFVsOfType ty2 extra3 = relevant_bindings $ ppWhen (not (null interesting_tyvars)) $ hang (text "Type variable kinds:") 2 $ @@ -2419,10 +2420,9 @@ getAmbigTkvs :: Ct -> ([Var],[Var]) getAmbigTkvs ct = partition (`elemVarSet` dep_tkv_set) ambig_tkvs where - tkv_set = tyCoVarsOfCt ct - ambig_tkv_set = filterVarSet isAmbiguousTyVar tkv_set - dep_tkv_set = tyCoVarsOfTypes (map tyVarKind (varSetElems tkv_set)) - ambig_tkvs = varSetElems ambig_tkv_set + tkvs = tyCoVarsOfCtList ct + ambig_tkvs = filter isAmbiguousTyVar tkvs + dep_tkv_set = tyCoVarsOfTypes (map tyVarKind tkvs) getSkolemInfo :: [Implication] -> TcTyVar -> ([TcTyVar], SkolemInfo) -- Get the skolem info for a type variable diff --git a/testsuite/tests/dependent/should_fail/T11407.stderr b/testsuite/tests/dependent/should_fail/T11407.stderr index b5d95bf..b07aa2b 100644 --- a/testsuite/tests/dependent/should_fail/T11407.stderr +++ b/testsuite/tests/dependent/should_fail/T11407.stderr @@ -4,5 +4,5 @@ T11407.hs:10:40: error: • In the second argument of ‘UhOh’, namely ‘(a :: x a)’ In the data instance declaration for ‘UhOh’ • Type variable kinds: - a :: k0 x :: k0 -> * + a :: k0 diff --git a/testsuite/tests/indexed-types/should_fail/T2693.stderr b/testsuite/tests/indexed-types/should_fail/T2693.stderr index 0c00711..a0ac4ea 100644 --- a/testsuite/tests/indexed-types/should_fail/T2693.stderr +++ b/testsuite/tests/indexed-types/should_fail/T2693.stderr @@ -1,7 +1,7 @@ T2693.hs:12:15: error: • Couldn't match expected type ‘(a8, b1)’ with actual type ‘TFn a6’ - The type variables ‘b1’, ‘a6’, ‘a8’ are ambiguous + The type variables ‘a6’, ‘a8’, ‘b1’ are ambiguous • In the first argument of ‘fst’, namely ‘x’ In the first argument of ‘(+)’, namely ‘fst x’ In the expression: fst x + fst x @@ -9,7 +9,7 @@ T2693.hs:12:15: error: T2693.hs:12:23: error: • Couldn't match expected type ‘(a8, b2)’ with actual type ‘TFn a7’ - The type variables ‘b2’, ‘a7’, ‘a8’ are ambiguous + The type variables ‘a7’, ‘a8’, ‘b2’ are ambiguous • In the first argument of ‘fst’, namely ‘x’ In the second argument of ‘(+)’, namely ‘fst x’ In the expression: fst x + fst x @@ -17,7 +17,7 @@ T2693.hs:12:23: error: T2693.hs:19:15: error: • Couldn't match expected type ‘(a5, b0)’ with actual type ‘TFn a2’ - The type variables ‘b0’, ‘a2’, ‘a5’ are ambiguous + The type variables ‘a2’, ‘a5’, ‘b0’ are ambiguous • In the first argument of ‘fst’, namely ‘x’ In the first argument of ‘(+)’, namely ‘fst x’ In the expression: fst x + snd x @@ -25,7 +25,7 @@ T2693.hs:19:15: error: T2693.hs:19:23: error: • Couldn't match expected type ‘(a3, a5)’ with actual type ‘TFn a4’ - The type variables ‘a3’, ‘a4’, ‘a5’ are ambiguous + The type variables ‘a4’, ‘a3’, ‘a5’ are ambiguous • In the first argument of ‘snd’, namely ‘x’ In the second argument of ‘(+)’, namely ‘snd x’ In the expression: fst x + snd x diff --git a/testsuite/tests/typecheck/should_fail/T4921.stderr b/testsuite/tests/typecheck/should_fail/T4921.stderr index 42d5a8a..8eff919 100644 --- a/testsuite/tests/typecheck/should_fail/T4921.stderr +++ b/testsuite/tests/typecheck/should_fail/T4921.stderr @@ -1,21 +1,21 @@ T4921.hs:10:9: error: - Ambiguous type variables ‘b1’, ‘a0’ arising from a use of ‘f’ - prevents the constraint ‘(C a0 b1)’ from being solved. - Relevant bindings include x :: a0 (bound at T4921.hs:10:1) - Probable fix: use a type annotation to specify what ‘b1’, ‘a0’ should be. - These potential instance exist: - instance C Int Char -- Defined at T4921.hs:7:10 - In the first argument of ‘fst’, namely ‘f’ - In the expression: fst f - In an equation for ‘x’: x = fst f + • Ambiguous type variables ‘a0’, ‘b1’ arising from a use of ‘f’ + prevents the constraint ‘(C a0 b1)’ from being solved. + Relevant bindings include x :: a0 (bound at T4921.hs:10:1) + Probable fix: use a type annotation to specify what ‘a0’, ‘b1’ should be. + These potential instance exist: + instance C Int Char -- Defined at T4921.hs:7:10 + • In the first argument of ‘fst’, namely ‘f’ + In the expression: fst f + In an equation for ‘x’: x = fst f T4921.hs:12:9: error: - Ambiguous type variable ‘b0’ arising from a use of ‘f’ - prevents the constraint ‘(C Int b0)’ from being solved. - Probable fix: use a type annotation to specify what ‘b0’ should be. - These potential instance exist: - instance C Int Char -- Defined at T4921.hs:7:10 - In the first argument of ‘fst’, namely ‘f’ - In the expression: fst f :: Int - In an equation for ‘y’: y = fst f :: Int + • Ambiguous type variable ‘b0’ arising from a use of ‘f’ + prevents the constraint ‘(C Int b0)’ from being solved. + Probable fix: use a type annotation to specify what ‘b0’ should be. + These potential instance exist: + instance C Int Char -- Defined at T4921.hs:7:10 + • In the first argument of ‘fst’, namely ‘f’ + In the expression: fst f :: Int + In an equation for ‘y’: y = fst f :: Int From git at git.haskell.org Mon Jul 18 17:57:55 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 18 Jul 2016 17:57:55 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Kill varSetElems try_tyvar_defaulting (9d2e414) Message-ID: <20160718175755.5A7993A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/9d2e414c8df15c1e0112e207f4a4e4bd031c2d66/ghc >--------------------------------------------------------------- commit 9d2e414c8df15c1e0112e207f4a4e4bd031c2d66 Author: Bartosz Nitka Date: Tue Apr 26 09:51:26 2016 -0700 Kill varSetElems try_tyvar_defaulting `varSetElems` introduces unnecessary nondeterminism and we can do the same thing deterministically for the same price. Test Plan: ./validate Reviewers: goldfire, austin, simonmar, bgamari, simonpj Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2143 GHC Trac Issues: #4012 >--------------------------------------------------------------- 9d2e414c8df15c1e0112e207f4a4e4bd031c2d66 compiler/typecheck/TcMType.hs | 7 +++++++ compiler/typecheck/TcRnTypes.hs | 37 +++++++++++++++++++++++++++---------- compiler/typecheck/TcSMonad.hs | 4 ++++ compiler/typecheck/TcSimplify.hs | 5 ++--- 4 files changed, 40 insertions(+), 13 deletions(-) diff --git a/compiler/typecheck/TcMType.hs b/compiler/typecheck/TcMType.hs index 5fefa2b..5fa0bc9 100644 --- a/compiler/typecheck/TcMType.hs +++ b/compiler/typecheck/TcMType.hs @@ -68,6 +68,7 @@ module TcMType ( tidyEvVar, tidyCt, tidySkolemInfo, skolemiseUnboundMetaTyVar, zonkTcTyVar, zonkTcTyVars, zonkTyCoVarsAndFV, zonkTcTypeAndFV, + zonkTyCoVarsAndFVList, zonkTcTypeAndSplitDepVars, zonkTcTypesAndSplitDepVars, zonkQuantifiedTyVar, zonkQuantifiedTyVarOrType, quantifyTyVars, quantifyZonkedTyVars, @@ -1202,6 +1203,12 @@ zonkTyCoVar tv | isTcTyVar tv = zonkTcTyVar tv zonkTyCoVarsAndFV :: TyCoVarSet -> TcM TyCoVarSet zonkTyCoVarsAndFV tycovars = tyCoVarsOfTypes <$> mapM zonkTyCoVar (varSetElems tycovars) +-- Takes a list of TyCoVars, zonks them and returns a +-- deterministically ordered list of their free variables. +zonkTyCoVarsAndFVList :: [TyCoVar] -> TcM [TyCoVar] +zonkTyCoVarsAndFVList tycovars = + tyCoVarsOfTypesList <$> mapM zonkTyCoVar tycovars + -- Takes a deterministic set of TyCoVars, zonks them and returns a -- deterministic set of their free variables. -- See Note [quantifyTyVars determinism]. diff --git a/compiler/typecheck/TcRnTypes.hs b/compiler/typecheck/TcRnTypes.hs index dccfd40..4755f8d 100644 --- a/compiler/typecheck/TcRnTypes.hs +++ b/compiler/typecheck/TcRnTypes.hs @@ -85,6 +85,7 @@ module TcRnTypes( andWC, unionsWC, mkSimpleWC, mkImplicWC, addInsols, addSimples, addImplics, tyCoVarsOfWC, dropDerivedWC, dropDerivedSimples, dropDerivedInsols, + tyCoVarsOfWCList, isDroppableDerivedLoc, insolubleImplic, arisesFromGivens, @@ -1608,22 +1609,38 @@ tyCoVarsOfCtsList = fvVarList . tyCoFVsOfCts tyCoFVsOfCts :: Cts -> FV tyCoFVsOfCts = foldrBag (unionFV . tyCoFVsOfCt) emptyFV +-- | Returns free variables of WantedConstraints as a non-deterministic +-- set. See Note [Deterministic FV] in FV. tyCoVarsOfWC :: WantedConstraints -> TyCoVarSet -- Only called on *zonked* things, hence no need to worry about flatten-skolems -tyCoVarsOfWC (WC { wc_simple = simple, wc_impl = implic, wc_insol = insol }) - = tyCoVarsOfCts simple `unionVarSet` - tyCoVarsOfBag tyCoVarsOfImplic implic `unionVarSet` - tyCoVarsOfCts insol +tyCoVarsOfWC = fvVarSet . tyCoFVsOfWC + +-- | Returns free variables of WantedConstraints as a deterministically +-- ordered list. See Note [Deterministic FV] in FV. +tyCoVarsOfWCList :: WantedConstraints -> [TyCoVar] +-- Only called on *zonked* things, hence no need to worry about flatten-skolems +tyCoVarsOfWCList = fvVarList . tyCoFVsOfWC -tyCoVarsOfImplic :: Implication -> TyCoVarSet +-- | Returns free variables of WantedConstraints as a composable FV +-- computation. See Note [Deterministic FV] in FV. +tyCoFVsOfWC :: WantedConstraints -> FV +-- Only called on *zonked* things, hence no need to worry about flatten-skolems +tyCoFVsOfWC (WC { wc_simple = simple, wc_impl = implic, wc_insol = insol }) + = tyCoFVsOfCts simple `unionFV` + tyCoFVsOfBag tyCoFVsOfImplic implic `unionFV` + tyCoFVsOfCts insol + +-- | Returns free variables of Implication as a composable FV computation. +-- See Note [Deterministic FV] in FV. +tyCoFVsOfImplic :: Implication -> FV -- Only called on *zonked* things, hence no need to worry about flatten-skolems -tyCoVarsOfImplic (Implic { ic_skols = skols +tyCoFVsOfImplic (Implic { ic_skols = skols , ic_given = givens, ic_wanted = wanted }) - = (tyCoVarsOfWC wanted `unionVarSet` tyCoVarsOfTypes (map evVarPred givens)) - `delVarSetList` skols + = FV.delFVs (mkVarSet skols) + (tyCoFVsOfWC wanted `unionFV` tyCoFVsOfTypes (map evVarPred givens)) -tyCoVarsOfBag :: (a -> TyCoVarSet) -> Bag a -> TyCoVarSet -tyCoVarsOfBag tvs_of = foldrBag (unionVarSet . tvs_of) emptyVarSet +tyCoFVsOfBag :: (a -> FV) -> Bag a -> FV +tyCoFVsOfBag tvs_of = foldrBag (unionFV . tvs_of) emptyFV -------------------------- dropDerivedSimples :: Cts -> Cts diff --git a/compiler/typecheck/TcSMonad.hs b/compiler/typecheck/TcSMonad.hs index ad86f7f..afd199f 100644 --- a/compiler/typecheck/TcSMonad.hs +++ b/compiler/typecheck/TcSMonad.hs @@ -93,6 +93,7 @@ module TcSMonad ( TcLevel, isTouchableMetaTyVarTcS, isFilledMetaTyVar_maybe, isFilledMetaTyVar, zonkTyCoVarsAndFV, zonkTcType, zonkTcTypes, zonkTcTyVar, zonkCo, + zonkTyCoVarsAndFVList, zonkSimples, zonkWC, -- References @@ -2756,6 +2757,9 @@ isFilledMetaTyVar tv = wrapTcS (TcM.isFilledMetaTyVar tv) zonkTyCoVarsAndFV :: TcTyCoVarSet -> TcS TcTyCoVarSet zonkTyCoVarsAndFV tvs = wrapTcS (TcM.zonkTyCoVarsAndFV tvs) +zonkTyCoVarsAndFVList :: [TcTyCoVar] -> TcS [TcTyCoVar] +zonkTyCoVarsAndFVList tvs = wrapTcS (TcM.zonkTyCoVarsAndFVList tvs) + zonkCo :: Coercion -> TcS Coercion zonkCo = wrapTcS . TcM.zonkCo diff --git a/compiler/typecheck/TcSimplify.hs b/compiler/typecheck/TcSimplify.hs index e22a5f6..39923cf 100644 --- a/compiler/typecheck/TcSimplify.hs +++ b/compiler/typecheck/TcSimplify.hs @@ -130,9 +130,8 @@ simpl_top wanteds | isEmptyWC wc = return wc | otherwise - = do { free_tvs <- TcS.zonkTyCoVarsAndFV (tyCoVarsOfWC wc) - ; let meta_tvs = varSetElems $ - filterVarSet (isTyVar <&&> isMetaTyVar) free_tvs + = do { free_tvs <- TcS.zonkTyCoVarsAndFVList (tyCoVarsOfWCList wc) + ; let meta_tvs = filter (isTyVar <&&> isMetaTyVar) free_tvs -- zonkTyCoVarsAndFV: the wc_first_go is not yet zonked -- filter isMetaTyVar: we might have runtime-skolems in GHCi, -- and we definitely don't want to try to assign to those! From git at git.haskell.org Mon Jul 18 17:57:58 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 18 Jul 2016 17:57:58 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Make absentError not depend on uniques (06ca161) Message-ID: <20160718175758.0600A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/06ca16125d9ea1bbb5d8c8f8c2e13c6d6217420c/ghc >--------------------------------------------------------------- commit 06ca16125d9ea1bbb5d8c8f8c2e13c6d6217420c Author: Bartosz Nitka Date: Thu May 12 05:42:21 2016 -0700 Make absentError not depend on uniques As explained in the comment it will cause changes in inlining if we don't suppress them. Test Plan: ./validate Reviewers: bgamari, austin, simonpj, goldfire, simonmar Reviewed By: simonmar Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2203 GHC Trac Issues: #4012 >--------------------------------------------------------------- 06ca16125d9ea1bbb5d8c8f8c2e13c6d6217420c compiler/stranal/WwLib.hs | 9 ++++++++- 1 file changed, 8 insertions(+), 1 deletion(-) diff --git a/compiler/stranal/WwLib.hs b/compiler/stranal/WwLib.hs index 1472ead..09bc204 100644 --- a/compiler/stranal/WwLib.hs +++ b/compiler/stranal/WwLib.hs @@ -757,7 +757,14 @@ mk_absent_let dflags arg where arg_ty = idType arg abs_rhs = mkRuntimeErrorApp aBSENT_ERROR_ID arg_ty msg - msg = showSDoc dflags (ppr arg <+> ppr (idType arg)) + msg = showSDoc (gopt_set dflags Opt_SuppressUniques) + (ppr arg <+> ppr (idType arg)) + -- We need to suppress uniques here because otherwise they'd + -- end up in the generated code as strings. This is bad for + -- determinism, because with different uniques the strings + -- will have different lengths and hence different costs for + -- the inliner leading to different inlining. + -- See also Note [Unique Determinism] in Unique mk_seq_case :: Id -> CoreExpr -> CoreExpr mk_seq_case arg body = Case (Var arg) (sanitiseCaseBndr arg) (exprType body) [(DEFAULT, [], body)] From git at git.haskell.org Mon Jul 18 17:58:00 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 18 Jul 2016 17:58:00 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Kill non-deterministic foldUFM in TrieMap and TcAppMap (6e94424) Message-ID: <20160718175800.A9BA03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/6e94424e015e9a3765a08a75e07463f559141987/ghc >--------------------------------------------------------------- commit 6e94424e015e9a3765a08a75e07463f559141987 Author: Bartosz Nitka Date: Wed May 4 09:22:37 2016 -0700 Kill non-deterministic foldUFM in TrieMap and TcAppMap Summary: foldUFM introduces unnecessary non-determinism that actually leads to different generated code as explained in Note [TrieMap determinism]. As we're switching from UniqFM to UniqDFM here you might be concerned about performance. There's nothing that ./validate detects. nofib reports no change in Compile Allocations, but Compile Time got better on some tests and worse on some, yielding this summary: -1 s.d. ----- -3.8% +1 s.d. ----- +5.4% Average ----- +0.7% This is not a fair comparison as the order of Uniques changes what GHC is actually doing. One benefit from making this deterministic is also that it will make the performance results more stable. Full nofib results: P108 Test Plan: ./validate, nofib Reviewers: goldfire, simonpj, simonmar, austin, bgamari Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2169 GHC Trac Issues: #4012 >--------------------------------------------------------------- 6e94424e015e9a3765a08a75e07463f559141987 compiler/basicTypes/NameEnv.hs | 24 ++++ compiler/basicTypes/VarEnv.hs | 8 ++ compiler/coreSyn/TrieMap.hs | 132 ++++++++++++++++----- compiler/typecheck/TcSMonad.hs | 28 +++-- .../tests/ghc-api/apirecomp001/apirecomp001.stderr | 16 +-- .../indexed-types/should_compile/T3017.stderr | 2 +- testsuite/tests/parser/should_compile/T2245.stderr | 8 +- .../should_compile/ExtraConstraints1.stderr | 6 +- .../should_compile/ExtraConstraints3.stderr | 32 ++--- .../WarningWildcardInstantiations.stderr | 2 +- .../InstantiatedNamedWildcardsInConstraints.stderr | 2 +- .../should_fail/WildcardInstantiations.stderr | 2 +- testsuite/tests/rebindable/rebindable6.stderr | 17 +-- .../tests/typecheck/should_compile/T10971a.stderr | 6 +- testsuite/tests/typecheck/should_fail/T5300.stderr | 4 +- testsuite/tests/typecheck/should_fail/T5853.stderr | 29 +++-- .../tests/typecheck/should_fail/tcfail171.stderr | 4 +- .../tests/typecheck/should_fail/tcfail204.stderr | 9 +- .../tests/warnings/should_compile/PluralS.stderr | 7 +- 19 files changed, 220 insertions(+), 118 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 6e94424e015e9a3765a08a75e07463f559141987 From git at git.haskell.org Mon Jul 18 17:58:03 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 18 Jul 2016 17:58:03 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Kill varSetElems in injImproveEqns (0e860a2) Message-ID: <20160718175803.541343A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/0e860a205cbb33b48c03c4bab731aa5a39dd4233/ghc >--------------------------------------------------------------- commit 0e860a205cbb33b48c03c4bab731aa5a39dd4233 Author: Bartosz Nitka Date: Thu Apr 28 05:40:39 2016 -0700 Kill varSetElems in injImproveEqns We want to remove varSetElems at the source level because it might be a source of nondeterminism. I don't think it introduces nondeterminism here, but it's easy to do the same thing deterministically for the same price. instFlexiTcS :: [TKVar] -> TcS (TCvSubst, [TcType]) instFlexiTcS currently gives the range of the produced substitution as the second element of the tuple, but it's not used anywhere right now. If it started to be used in the code I'm modifying it would cause nondeterminism problems. Test Plan: ./validate Reviewers: austin, goldfire, bgamari, simonmar, simonpj Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2149 GHC Trac Issues: #4012 >--------------------------------------------------------------- 0e860a205cbb33b48c03c4bab731aa5a39dd4233 compiler/typecheck/TcInteract.hs | 15 ++++++++++----- 1 file changed, 10 insertions(+), 5 deletions(-) diff --git a/compiler/typecheck/TcInteract.hs b/compiler/typecheck/TcInteract.hs index 39ad787..ca5d912 100644 --- a/compiler/typecheck/TcInteract.hs +++ b/compiler/typecheck/TcInteract.hs @@ -1491,7 +1491,7 @@ improve_top_fun_eqs fam_envs fam_tc args rhs_ty -> (a -> [Type]) -- get LHS of an axiom -> (a -> Type) -- get RHS of an axiom -> (a -> Maybe CoAxBranch) -- Just => apartness check required - -> [( [Type], TCvSubst, TyVarSet, Maybe CoAxBranch )] + -> [( [Type], TCvSubst, [TyVar], Maybe CoAxBranch )] -- Result: -- ( [arguments of a matching axiom] -- , RHS-unifying substitution @@ -1503,15 +1503,20 @@ improve_top_fun_eqs fam_envs fam_tc args rhs_ty , let ax_args = axiomLHS axiom , let ax_rhs = axiomRHS axiom , Just subst <- [tcUnifyTyWithTFs False ax_rhs rhs_ty] - , let tvs = tyCoVarsOfTypes ax_args + , let tvs = tyCoVarsOfTypesList ax_args notInSubst tv = not (tv `elemVarEnv` getTvSubstEnv subst) - unsubstTvs = filterVarSet (notInSubst <&&> isTyVar) tvs ] + unsubstTvs = filter (notInSubst <&&> isTyVar) tvs ] injImproveEqns :: [Bool] - -> ([Type], TCvSubst, TyCoVarSet, Maybe CoAxBranch) + -> ([Type], TCvSubst, [TyCoVar], Maybe CoAxBranch) -> TcS [Eqn] injImproveEqns inj_args (ax_args, theta, unsubstTvs, cabr) = do - (theta', _) <- instFlexiTcS (varSetElems unsubstTvs) + (theta', _) <- instFlexiTcS unsubstTvs + -- The use of deterministically ordered list for `unsubstTvs` + -- is not strictly necessary here, we only use the substitution + -- part of the result of instFlexiTcS. If we used the second + -- part of the tuple, which is the range of the substitution then + -- the order could be important. let subst = theta `unionTCvSubst` theta' return [ Pair arg (substTyUnchecked subst ax_arg) | case cabr of From git at git.haskell.org Mon Jul 18 17:58:05 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 18 Jul 2016 17:58:05 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Remove some varSetElems in dsCmdStmt (85f42e8) Message-ID: <20160718175805.EEE983A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/85f42e89c2911ebeeb12401014ad5f852860150e/ghc >--------------------------------------------------------------- commit 85f42e89c2911ebeeb12401014ad5f852860150e Author: Bartosz Nitka Date: Wed May 11 07:47:15 2016 -0700 Remove some varSetElems in dsCmdStmt varSetElems introduces unnecessary determinism and it's easy to preserve determinism here. Test Plan: ./validate Reviewers: goldfire, simonmar, austin, bgamari, simonpj Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2195 GHC Trac Issues: #4012 >--------------------------------------------------------------- 85f42e89c2911ebeeb12401014ad5f852860150e compiler/deSugar/DsArrows.hs | 8 +++++--- 1 file changed, 5 insertions(+), 3 deletions(-) diff --git a/compiler/deSugar/DsArrows.hs b/compiler/deSugar/DsArrows.hs index ea10b74..cdf839a 100644 --- a/compiler/deSugar/DsArrows.hs +++ b/compiler/deSugar/DsArrows.hs @@ -48,6 +48,7 @@ import VarSet import SrcLoc import ListSetOps( assocDefault ) import Data.List +import Util data DsCmdEnv = DsCmdEnv { arr_id, compose_id, first_id, app_id, choice_id, loop_id :: CoreExpr @@ -786,7 +787,7 @@ dsCmdStmt ids local_vars out_ids (BindStmt pat cmd _ _ _) env_ids = do (core_cmd, fv_cmd, env_ids1) <- dsfixCmd ids local_vars unitTy pat_ty cmd let pat_vars = mkVarSet (collectPatBinders pat) let - env_ids2 = varSetElems (mkVarSet out_ids `minusVarSet` pat_vars) + env_ids2 = filterOut (`elemVarSet` pat_vars) out_ids env_ty2 = mkBigCoreVarTupTy env_ids2 -- multiplexing function @@ -863,8 +864,9 @@ dsCmdStmt ids local_vars out_ids , recS_later_rets = later_rets, recS_rec_rets = rec_rets }) env_ids = do let - env2_id_set = mkVarSet out_ids `minusVarSet` mkVarSet later_ids - env2_ids = varSetElems env2_id_set + later_ids_set = mkVarSet later_ids + env2_ids = filterOut (`elemVarSet` later_ids_set) out_ids + env2_id_set = mkVarSet env2_ids env2_ty = mkBigCoreVarTupTy env2_ids -- post_loop_fn = \((later_ids),(env2_ids)) -> (out_ids) From git at git.haskell.org Mon Jul 18 17:58:08 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 18 Jul 2016 17:58:08 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Make simplifyInstanceContexts deterministic (c267680) Message-ID: <20160718175808.9E03C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/c2676803269eb90519bb11e8850b21e0d9ea0cb8/ghc >--------------------------------------------------------------- commit c2676803269eb90519bb11e8850b21e0d9ea0cb8 Author: Bartosz Nitka Date: Tue May 10 05:32:28 2016 -0700 Make simplifyInstanceContexts deterministic simplifyInstanceContexts used cmpType which is nondeterministic for canonicalising typeclass constraints in derived instances. Following changes make it deterministic as explained by the Note [Deterministic simplifyInstanceContexts]. Test Plan: ./validate Reviewers: simonmar, goldfire, simonpj, austin, bgamari Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2173 GHC Trac Issues: #4012 >--------------------------------------------------------------- c2676803269eb90519bb11e8850b21e0d9ea0cb8 compiler/basicTypes/Unique.hs | 15 ++++++++------- compiler/basicTypes/Var.hs | 14 ++++++++++++-- compiler/typecheck/TcDeriv.hs | 31 ++++++++++++++++++++++++++++--- compiler/types/Type.hs | 16 ++++++++++++++-- 4 files changed, 62 insertions(+), 14 deletions(-) diff --git a/compiler/basicTypes/Unique.hs b/compiler/basicTypes/Unique.hs index ca74373..eddf265 100644 --- a/compiler/basicTypes/Unique.hs +++ b/compiler/basicTypes/Unique.hs @@ -23,7 +23,7 @@ module Unique ( Unique, Uniquable(..), -- ** Constructors, destructors and operations on 'Unique's - hasKey, cmpByUnique, + hasKey, pprUnique, @@ -35,6 +35,7 @@ module Unique ( deriveUnique, -- Ditto newTagUnique, -- Used in CgCase initTyVarUnique, + nonDetCmpUnique, -- ** Making built-in uniques @@ -168,9 +169,6 @@ instance Uniquable FastString where instance Uniquable Int where getUnique i = mkUniqueGrimily i -cmpByUnique :: Uniquable a => a -> a -> Ordering -cmpByUnique x y = (getUnique x) `cmpUnique` (getUnique y) - {- ************************************************************************ * * @@ -204,8 +202,11 @@ eqUnique (MkUnique u1) (MkUnique u2) = u1 == u2 ltUnique (MkUnique u1) (MkUnique u2) = u1 < u2 leUnique (MkUnique u1) (MkUnique u2) = u1 <= u2 -cmpUnique :: Unique -> Unique -> Ordering -cmpUnique (MkUnique u1) (MkUnique u2) +-- Provided here to make it explicit at the call-site that it can +-- introduce non-determinism. +-- See Note [Unique Determinism] +nonDetCmpUnique :: Unique -> Unique -> Ordering +nonDetCmpUnique (MkUnique u1) (MkUnique u2) = if u1 == u2 then EQ else if u1 < u2 then LT else GT instance Eq Unique where @@ -217,7 +218,7 @@ instance Ord Unique where a <= b = leUnique a b a > b = not (leUnique a b) a >= b = not (ltUnique a b) - compare a b = cmpUnique a b + compare a b = nonDetCmpUnique a b ----------------- instance Uniquable Unique where diff --git a/compiler/basicTypes/Var.hs b/compiler/basicTypes/Var.hs index d6bd609..c70a304 100644 --- a/compiler/basicTypes/Var.hs +++ b/compiler/basicTypes/Var.hs @@ -64,7 +64,9 @@ module Var ( -- ** Modifying 'TyVar's setTyVarName, setTyVarUnique, setTyVarKind, updateTyVarKind, - updateTyVarKindM + updateTyVarKindM, + + nonDetCmpVar ) where @@ -80,6 +82,7 @@ import Util import DynFlags import Outputable +import Unique (nonDetCmpUnique) import Data.Data {- @@ -269,7 +272,14 @@ instance Ord Var where a < b = realUnique a < realUnique b a >= b = realUnique a >= realUnique b a > b = realUnique a > realUnique b - a `compare` b = varUnique a `compare` varUnique b + a `compare` b = a `nonDetCmpVar` b + +-- | Compare Vars by their Uniques. +-- This is what Ord Var does, provided here to make it explicit at the +-- call-site that it can introduce non-determinism. +-- See Note [Unique Determinism] +nonDetCmpVar :: Var -> Var -> Ordering +nonDetCmpVar a b = varUnique a `nonDetCmpUnique` varUnique b instance Data Var where -- don't traverse? diff --git a/compiler/typecheck/TcDeriv.hs b/compiler/typecheck/TcDeriv.hs index c74b450..944c513 100644 --- a/compiler/typecheck/TcDeriv.hs +++ b/compiler/typecheck/TcDeriv.hs @@ -1862,6 +1862,29 @@ this by simplifying the RHS to a form in which - the list is sorted by tyvar (major key) and then class (minor key) - no duplicates, of course +Note [Deterministic simplifyInstanceContexts] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Canonicalisation uses cmpType which is nondeterministic. Sorting +with cmpType puts the returned lists in a nondeterministic order. +If we were to return them, we'd get class constraints in +nondeterministic order. + +Consider: + + data ADT a b = Z a b deriving Eq + +The generated code could be either: + + instance (Eq a, Eq b) => Eq (Z a b) where + +Or: + + instance (Eq b, Eq a) => Eq (Z a b) where + +To prevent the order from being nondeterministic we only +canonicalize when comparing and return them in the same order as +simplifyDeriv returned them. +See also Note [cmpType nondeterminism] -} @@ -1909,8 +1932,10 @@ simplifyInstanceContexts infer_specs else iterate_deriv (n+1) new_solns } - eqSolution = eqListBy (eqListBy eqType) - + eqSolution a b = eqListBy (eqListBy eqType) (canSolution a) (canSolution b) + -- Canonicalise for comparison + -- See Note [Deterministic simplifyInstanceContexts] + canSolution = map (sortBy cmpType) ------------------------------------------------------------------ gen_soln :: DerivSpec ThetaOrigin -> TcM ThetaType gen_soln (DS { ds_loc = loc, ds_tvs = tyvars @@ -1925,7 +1950,7 @@ simplifyInstanceContexts infer_specs -- Claim: the result instance declaration is guaranteed valid -- Hence no need to call: -- checkValidInstance tyvars theta clas inst_tys - ; return (sortBy cmpType theta) } -- Canonicalise before returning the solution + ; return theta } where the_pred = mkClassPred clas inst_tys diff --git a/compiler/types/Type.hs b/compiler/types/Type.hs index b4a123b..69cf69f 100644 --- a/compiler/types/Type.hs +++ b/compiler/types/Type.hs @@ -223,6 +223,7 @@ import FastString import Pair import ListSetOps import Digraph +import Unique ( nonDetCmpUnique ) import Maybes ( orElse ) import Data.Maybe ( isJust, mapMaybe ) @@ -2098,6 +2099,16 @@ eqVarBndrs _ _ _= Nothing -- Now here comes the real worker +{- +Note [cmpType nondeterminism] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +cmpType is implemented in terms of cmpTypeX. cmpTypeX uses cmpTc which +compares TyCons by their Unique value. Using Uniques for ordering leads +to nondeterminism. We hit the same problem in the TyVarTy case, comparing +type variables is nondeterministic, note the call to nonDetCmpVar in cmpTypeX. +See Note [Unique Determinism] for more details. +-} + cmpType :: Type -> Type -> Ordering cmpType t1 t2 -- we know k1 and k2 have the same kind, because they both have kind *. @@ -2160,7 +2171,7 @@ cmpTypeX env orig_t1 orig_t2 = | Just t2' <- coreViewOneStarKind t2 = go env t1 t2' go env (TyVarTy tv1) (TyVarTy tv2) - = liftOrdering $ rnOccL env tv1 `compare` rnOccR env tv2 + = liftOrdering $ rnOccL env tv1 `nonDetCmpVar` rnOccR env tv2 go env (ForAllTy (Named tv1 _) t1) (ForAllTy (Named tv2 _) t2) = go env (tyVarKind tv1) (tyVarKind tv2) `thenCmpTy` go (rnBndr2 env tv1 tv2) t1 t2 @@ -2211,10 +2222,11 @@ cmpTypesX _ _ [] = GT -- | Compare two 'TyCon's. NB: This should /never/ see the "star synonyms", -- as recognized by Kind.isStarKindSynonymTyCon. See Note -- [Kind Constraint and kind *] in Kind. +-- See Note [cmpType nondeterminism] cmpTc :: TyCon -> TyCon -> Ordering cmpTc tc1 tc2 = ASSERT( not (isStarKindSynonymTyCon tc1) && not (isStarKindSynonymTyCon tc2) ) - u1 `compare` u2 + u1 `nonDetCmpUnique` u2 where u1 = tyConUnique tc1 u2 = tyConUnique tc2 From git at git.haskell.org Mon Jul 18 17:58:11 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 18 Jul 2016 17:58:11 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Make inert_model and inert_eqs deterministic sets (aaff852) Message-ID: <20160718175811.53B0F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/aaff8525d1689532705b4a0d57fc338cc19bb1c9/ghc >--------------------------------------------------------------- commit aaff8525d1689532705b4a0d57fc338cc19bb1c9 Author: Bartosz Nitka Date: Tue May 17 05:45:43 2016 -0700 Make inert_model and inert_eqs deterministic sets The order inert_model and intert_eqs fold affects the order that the typechecker looks at things. I've been able to experimentally confirm that the order of equalities and the order of the model matter for determinism. This is just a straigthforward replacement of nondeterministic VarEnv for deterministic DVarEnv. Test Plan: ./validate Reviewers: simonpj, goldfire, austin, bgamari, simonmar Reviewed By: simonmar Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2232 GHC Trac Issues: #4012 >--------------------------------------------------------------- aaff8525d1689532705b4a0d57fc338cc19bb1c9 compiler/basicTypes/VarEnv.hs | 28 +++++++++-- compiler/typecheck/TcFlatten.hs | 4 +- compiler/typecheck/TcInteract.hs | 2 +- compiler/typecheck/TcSMonad.hs | 58 +++++++++++----------- compiler/utils/UniqDFM.hs | 22 +++++++- .../tests/indexed-types/should_fail/T3330a.stderr | 5 +- .../tests/indexed-types/should_fail/T4174.stderr | 4 +- .../tests/indexed-types/should_fail/T4179.stderr | 6 +-- .../tests/indexed-types/should_fail/T9662.stderr | 4 +- testsuite/tests/polykinds/T9017.stderr | 4 +- testsuite/tests/typecheck/should_fail/T7869.stderr | 8 ++- 11 files changed, 93 insertions(+), 52 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc aaff8525d1689532705b4a0d57fc338cc19bb1c9 From git at git.haskell.org Mon Jul 18 17:58:14 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 18 Jul 2016 17:58:14 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Refactor free tyvars on LHS of rules (be341c8) Message-ID: <20160718175814.0C0EA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/be341c87b6e61e4f08e05a695a4df9db565c273e/ghc >--------------------------------------------------------------- commit be341c87b6e61e4f08e05a695a4df9db565c273e Author: Simon Peyton Jones Date: Fri Apr 22 10:47:14 2016 +0100 Refactor free tyvars on LHS of rules A RULE can have unbound meta-tyvars on the LHS. Consider data T a = C foo :: T a -> Int foo C = 1 {-# RULES "myrule" foo C = 1 #-} After type checking the LHS becomes (foo alpha (C alpah)) and we do not want to zap the unbound meta-tyvar 'alpha' to Any, because that limits the applicability of the rule. Instead, we want to quantify over it! Previously there was a rather clunky implementation of this quantification, buried in the zonker in TcHsSyn (zonkTvCollecting). This patch refactors it so that the zonker just turns the meta-tyvar into a skolem, and the desugarer adds the quantification. See DsBinds Note [Free tyvars on rule LHS]. As it happened, the desugarer was already doing something similar for dictionaries. See DsBinds Note [Free dictionaries on rule LHS] No change in functionality, but less cruft. >--------------------------------------------------------------- be341c87b6e61e4f08e05a695a4df9db565c273e compiler/deSugar/DsBinds.hs | 99 +++++++++++++++++++------------ compiler/typecheck/TcHsSyn.hs | 134 ++++++++++++++++++------------------------ 2 files changed, 121 insertions(+), 112 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc be341c87b6e61e4f08e05a695a4df9db565c273e From git at git.haskell.org Mon Jul 18 17:58:16 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 18 Jul 2016 17:58:16 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Kill varSetElems in tcInferPatSynDecl (4f2dc04) Message-ID: <20160718175816.ACEFC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/4f2dc04bf8dfed7ca4ae7603af21334a14b97a21/ghc >--------------------------------------------------------------- commit 4f2dc04bf8dfed7ca4ae7603af21334a14b97a21 Author: Bartosz Nitka Date: Mon May 16 03:27:53 2016 -0700 Kill varSetElems in tcInferPatSynDecl varSetElems introduces unnecessary non-determinism and while I didn't estabilish experimentally that this matters here I'm convinced that it will, because I expect pattern synonyms to end up in interface files. Test Plan: ./validate Reviewers: austin, simonmar, bgamari, mpickering, simonpj Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2206 GHC Trac Issues: #4012 >--------------------------------------------------------------- 4f2dc04bf8dfed7ca4ae7603af21334a14b97a21 compiler/typecheck/TcPatSyn.hs | 42 ++++++++++++++++++++++++++---------------- 1 file changed, 26 insertions(+), 16 deletions(-) diff --git a/compiler/typecheck/TcPatSyn.hs b/compiler/typecheck/TcPatSyn.hs index 633b8d6..3cf1a86 100644 --- a/compiler/typecheck/TcPatSyn.hs +++ b/compiler/typecheck/TcPatSyn.hs @@ -47,6 +47,7 @@ import FieldLabel import Bag import Util import ErrUtils +import FV import Control.Monad ( unless, zipWithM ) import Data.List( partition ) #if __GLASGOW_HASKELL__ < 709 @@ -219,9 +220,8 @@ tcInferPatSynDecl PSB{ psb_id = lname@(L _ name), psb_args = details, ; (qtvs, req_dicts, ev_binds) <- simplifyInfer tclvl False [] named_taus wanted - ; let (ex_vars, prov_dicts) = tcCollectEx lpat' + ; let ((ex_tvs, ex_vars), prov_dicts) = tcCollectEx lpat' univ_tvs = filter (not . (`elemVarSet` ex_vars)) qtvs - ex_tvs = varSetElems ex_vars prov_theta = map evVarPred prov_dicts req_theta = map evVarPred req_dicts @@ -948,34 +948,44 @@ nonBidirectionalErr name = failWithTc $ -- These are used in computing the type of a pattern synonym and also -- in generating matcher functions, since success continuations need -- to be passed these pattern-bound evidences. -tcCollectEx :: LPat Id -> (TyVarSet, [EvVar]) -tcCollectEx pat = go pat +tcCollectEx + :: LPat Id + -> ( ([Var], VarSet) -- Existentially-bound type variables as a + -- deterministically ordered list and a set. + -- See Note [Deterministic FV] in FV + , [EvVar] + ) +tcCollectEx pat = let (fv, evs) = go pat in (fvVarListVarSet fv, evs) where - go :: LPat Id -> (TyVarSet, [EvVar]) + go :: LPat Id -> (FV, [EvVar]) go = go1 . unLoc - go1 :: Pat Id -> (TyVarSet, [EvVar]) + go1 :: Pat Id -> (FV, [EvVar]) go1 (LazyPat p) = go p go1 (AsPat _ p) = go p go1 (ParPat p) = go p go1 (BangPat p) = go p - go1 (ListPat ps _ _) = mconcat . map go $ ps - go1 (TuplePat ps _ _) = mconcat . map go $ ps - go1 (PArrPat ps _) = mconcat . map go $ ps + go1 (ListPat ps _ _) = mergeMany . map go $ ps + go1 (TuplePat ps _ _) = mergeMany . map go $ ps + go1 (PArrPat ps _) = mergeMany . map go $ ps go1 (ViewPat _ p _) = go p - go1 con at ConPatOut{} = mappend (mkVarSet (pat_tvs con), pat_dicts con) $ + go1 con at ConPatOut{} = merge (FV.mkFVs (pat_tvs con), pat_dicts con) $ goConDetails $ pat_args con go1 (SigPatOut p _) = go p go1 (CoPat _ p _) = go1 p go1 (NPlusKPat n k _ geq subtract _) = pprPanic "TODO: NPlusKPat" $ ppr n $$ ppr k $$ ppr geq $$ ppr subtract - go1 _ = mempty + go1 _ = empty - goConDetails :: HsConPatDetails Id -> (TyVarSet, [EvVar]) - goConDetails (PrefixCon ps) = mconcat . map go $ ps - goConDetails (InfixCon p1 p2) = go p1 `mappend` go p2 + goConDetails :: HsConPatDetails Id -> (FV, [EvVar]) + goConDetails (PrefixCon ps) = mergeMany . map go $ ps + goConDetails (InfixCon p1 p2) = go p1 `merge` go p2 goConDetails (RecCon HsRecFields{ rec_flds = flds }) - = mconcat . map goRecFd $ flds + = mergeMany . map goRecFd $ flds - goRecFd :: LHsRecField Id (LPat Id) -> (TyVarSet, [EvVar]) + goRecFd :: LHsRecField Id (LPat Id) -> (FV, [EvVar]) goRecFd (L _ HsRecField{ hsRecFieldArg = p }) = go p + + merge (vs1, evs1) (vs2, evs2) = (vs1 `unionFV` vs2, evs1 ++ evs2) + mergeMany = foldr merge empty + empty = (emptyFV, []) From git at git.haskell.org Mon Jul 18 17:58:19 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 18 Jul 2016 17:58:19 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Kill varEnvElts in specImports (047cdc0) Message-ID: <20160718175819.7165F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/047cdc0ff20046cd35e25c08e9b6c65a2bffe7ce/ghc >--------------------------------------------------------------- commit 047cdc0ff20046cd35e25c08e9b6c65a2bffe7ce Author: Bartosz Nitka Date: Thu May 12 06:55:00 2016 -0700 Kill varEnvElts in specImports We need the order of specialized binds and rules to be deterministic, so we use a deterministic set here. Test Plan: ./validate Reviewers: simonmar, bgamari, austin, simonpj Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2197 GHC Trac Issues: #4012 >--------------------------------------------------------------- 047cdc0ff20046cd35e25c08e9b6c65a2bffe7ce compiler/basicTypes/VarEnv.hs | 25 +++++++++++++++++++++++-- compiler/specialise/Specialise.hs | 28 ++++++++++++++++++---------- compiler/utils/UniqDFM.hs | 32 ++++++++++++++++++++++++++++++++ 3 files changed, 73 insertions(+), 12 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 047cdc0ff20046cd35e25c08e9b6c65a2bffe7ce From git at git.haskell.org Mon Jul 18 17:58:22 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 18 Jul 2016 17:58:22 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Make accept (d2ed0f7) Message-ID: <20160718175822.38F3F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/d2ed0f71ac9ba075737f5580307c598f7174e40b/ghc >--------------------------------------------------------------- commit d2ed0f71ac9ba075737f5580307c598f7174e40b Author: Bartosz Nitka Date: Mon May 16 12:47:25 2016 -0700 Make accept Summary: Test Plan: Reviewers: Subscribers: Tasks: Blame Revision: >--------------------------------------------------------------- d2ed0f71ac9ba075737f5580307c598f7174e40b testsuite/tests/ado/ado004.stderr | 16 +- testsuite/tests/determinism/determ007/A.hs | 3 + testsuite/tests/determinism/determ007/Makefile | 13 ++ testsuite/tests/determinism/determ007/all.T | 4 + .../determ007.stdout} | 0 testsuite/tests/determinism/determ008/A.hs | 3 + testsuite/tests/determinism/determ008/Makefile | 13 ++ testsuite/tests/determinism/determ008/all.T | 4 + .../determ008.stdout} | 0 testsuite/tests/determinism/determ009/A.hs | 4 + testsuite/tests/determinism/determ009/Makefile | 13 ++ testsuite/tests/determinism/determ009/all.T | 4 + .../determ009.stdout} | 0 testsuite/tests/determinism/determ011/A.hs | 26 +++ testsuite/tests/determinism/determ011/Makefile | 13 ++ testsuite/tests/determinism/determ011/all.T | 4 + .../determ011.stdout} | 0 testsuite/tests/determinism/determ012/A.hs | 10 + testsuite/tests/determinism/determ012/Makefile | 13 ++ testsuite/tests/determinism/determ012/all.T | 4 + .../tests/determinism/determ012/determ012.stdout | 2 + testsuite/tests/determinism/determ013/A.hs | 19 ++ testsuite/tests/determinism/determ013/Makefile | 13 ++ testsuite/tests/determinism/determ013/all.T | 4 + .../tests/determinism/determ013/determ013.stdout | 2 + .../T10934.hs => determinism/determ014/A.hs} | 0 testsuite/tests/determinism/determ014/Makefile | 13 ++ testsuite/tests/determinism/determ014/all.T | 4 + .../tests/determinism/determ014/determ014.stdout | 2 + testsuite/tests/determinism/determ015/A.hs | 59 ++++++ testsuite/tests/determinism/determ015/Makefile | 13 ++ testsuite/tests/determinism/determ015/all.T | 4 + .../determ015.stdout} | 0 testsuite/tests/determinism/determ016/A.hs | 19 ++ testsuite/tests/determinism/determ016/Makefile | 13 ++ testsuite/tests/determinism/determ016/all.T | 4 + .../determ016.stdout} | 0 testsuite/tests/determinism/determ017/A.hs | 215 +++++++++++++++++++++ testsuite/tests/determinism/determ017/Makefile | 13 ++ testsuite/tests/determinism/determ017/all.T | 4 + .../determ017.stdout} | 0 .../tests/ghci.debugger/scripts/break006.stderr | 4 +- testsuite/tests/ghci/scripts/T6018ghcifail.stderr | 4 +- testsuite/tests/typecheck/should_fail/T5095.stderr | 2 +- .../typecheck/should_fail/T6018failclosed.stderr | 144 +++++++------- .../tests/typecheck/should_fail/tcfail133.stderr | 2 +- 46 files changed, 620 insertions(+), 86 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc d2ed0f71ac9ba075737f5580307c598f7174e40b From git at git.haskell.org Mon Jul 18 17:58:24 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 18 Jul 2016 17:58:24 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Serialize vParallelTyCons in a stable order (c9c0cca) Message-ID: <20160718175824.E20553A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/c9c0cca21dc5beceff6b89a84f642a5de0202242/ghc >--------------------------------------------------------------- commit c9c0cca21dc5beceff6b89a84f642a5de0202242 Author: Bartosz Nitka Date: Thu Jun 2 09:51:04 2016 -0700 Serialize vParallelTyCons in a stable order nameSetElems can introduce nondeterminism and while I haven't observed this being a problem in practice (possibly because this is dead code) there's no downside to doing this. Test Plan: ./validate Reviewers: bgamari, austin, simonpj, simonmar Reviewed By: simonmar Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2296 GHC Trac Issues: #4012 >--------------------------------------------------------------- c9c0cca21dc5beceff6b89a84f642a5de0202242 compiler/iface/MkIface.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/iface/MkIface.hs b/compiler/iface/MkIface.hs index 1a31afd..1b9570c 100644 --- a/compiler/iface/MkIface.hs +++ b/compiler/iface/MkIface.hs @@ -326,7 +326,7 @@ mkIface_ hsc_env maybe_old_fingerprint , ifaceVectInfoTyCon = [tyConName t | (t, t_v) <- nameEnvElts vTyCon, t /= t_v] , ifaceVectInfoTyConReuse = [tyConName t | (t, t_v) <- nameEnvElts vTyCon, t == t_v] , ifaceVectInfoParallelVars = [Var.varName v | v <- varSetElems vParallelVars] - , ifaceVectInfoParallelTyCons = nameSetElems vParallelTyCons + , ifaceVectInfoParallelTyCons = nameSetElemsStable vParallelTyCons } ----------------------------- From git at git.haskell.org Mon Jul 18 17:58:27 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 18 Jul 2016 17:58:27 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Kill varSetElems in tidyFreeTyCoVars (28aabfc) Message-ID: <20160718175827.941343A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/28aabfcb609cb784b72d8746a8a681c487db0e16/ghc >--------------------------------------------------------------- commit 28aabfcb609cb784b72d8746a8a681c487db0e16 Author: Bartosz Nitka Date: Wed May 18 10:36:49 2016 -0700 Kill varSetElems in tidyFreeTyCoVars I haven't observed this to have an effect on nondeterminism, but tidyOccName appears to modify the TidyOccEnv in a way dependent on the order of inputs. It's easy enough to change it to be deterministic to be on the safe side. Test Plan: ./validate Reviewers: simonmar, austin, bgamari, simonpj Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2238 GHC Trac Issues: #4012 >--------------------------------------------------------------- 28aabfcb609cb784b72d8746a8a681c487db0e16 compiler/typecheck/TcErrors.hs | 8 +- compiler/typecheck/TcRnMonad.hs | 2 +- compiler/typecheck/TcValidity.hs | 10 +- compiler/types/TyCoRep.hs | 8 +- .../tests/indexed-types/should_fail/T2693.stderr | 4 +- .../should_fail/overloadedlabelsfail01.stderr | 46 ++-- testsuite/tests/parser/should_fail/T7848.stderr | 4 +- testsuite/tests/rename/should_fail/T10618.stderr | 2 +- .../tests/typecheck/should_fail/T11355.stderr | 2 +- testsuite/tests/typecheck/should_fail/T5684.stderr | 286 ++++++++++----------- testsuite/tests/typecheck/should_fail/T7851.stderr | 4 +- .../tests/typecheck/should_fail/tcfail001.stderr | 2 +- 12 files changed, 189 insertions(+), 189 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 28aabfcb609cb784b72d8746a8a681c487db0e16 From git at git.haskell.org Mon Jul 18 17:58:31 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 18 Jul 2016 17:58:31 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Make Arrow desugaring deterministic (be3a886) Message-ID: <20160718175831.641693A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/be3a8861da376d6cf5bfa056db2f5b0d050d1dd6/ghc >--------------------------------------------------------------- commit be3a8861da376d6cf5bfa056db2f5b0d050d1dd6 Author: Bartosz Nitka Date: Tue May 24 04:44:37 2016 -0700 Make Arrow desugaring deterministic This kills two instances of varSetElems that turned out to be nondeterministic. I've tried to untangle this before, but it's a bit hard with the fixDs in the middle. Fortunately I now have a test case that proves that we need determinism here. Test Plan: ./validate, new testcase Reviewers: simonpj, simonmar, austin, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2258 GHC Trac Issues: #4012 >--------------------------------------------------------------- be3a8861da376d6cf5bfa056db2f5b0d050d1dd6 compiler/coreSyn/CoreFVs.hs | 33 ++++++++++++ compiler/deSugar/DsArrows.hs | 63 +++++++++++----------- compiler/utils/UniqDFM.hs | 7 ++- testsuite/tests/determinism/determ018/A.hs | 32 +++++++++++ .../determinism/{determ013 => determ018}/Makefile | 2 +- .../determinism/{determ009 => determ018}/all.T | 4 +- .../determ018.stdout} | 0 7 files changed, 106 insertions(+), 35 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc be3a8861da376d6cf5bfa056db2f5b0d050d1dd6 From git at git.haskell.org Mon Jul 18 17:58:34 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 18 Jul 2016 17:58:34 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Refactor validity checking for type/data instances (84ad87d) Message-ID: <20160718175834.14A763A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/84ad87d4d803cbb9f07089d7eb18e0b942ca3d05/ghc >--------------------------------------------------------------- commit 84ad87d4d803cbb9f07089d7eb18e0b942ca3d05 Author: Simon Peyton Jones Date: Fri Jan 22 16:40:55 2016 +0000 Refactor validity checking for type/data instances I found that there was some code duplication going on, so I've put more into the shared function checkValidFamPats. I did some refactoring in checkConsistentFamInst too, preparatory to #11450; the error messages change a little but no change in behaviour. >--------------------------------------------------------------- 84ad87d4d803cbb9f07089d7eb18e0b942ca3d05 compiler/typecheck/TcInstDcls.hs | 9 +- compiler/typecheck/TcTyClsDecls.hs | 2 + compiler/typecheck/TcValidity.hs | 154 ++++++++++++--------- .../indexed-types/should_fail/SimpleFail2a.stderr | 11 +- 4 files changed, 101 insertions(+), 75 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 84ad87d4d803cbb9f07089d7eb18e0b942ca3d05 From git at git.haskell.org Mon Jul 18 17:58:37 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 18 Jul 2016 17:58:37 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Add -foptimal-applicative-do (43ea95f) Message-ID: <20160718175837.37C343A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/43ea95f2d42a27bee2293ee975ecd1a7aa011e3f/ghc >--------------------------------------------------------------- commit 43ea95f2d42a27bee2293ee975ecd1a7aa011e3f Author: Simon Marlow Date: Fri Mar 4 13:06:42 2016 +0000 Add -foptimal-applicative-do Summary: The algorithm for ApplicativeDo rearrangement is based on a heuristic that runs in O(n^2). This patch adds the optimal algorithm, which is O(n^3), selected by a flag (-foptimal-applicative-do). It finds better solutions in a small number of cases (about 2% of the cases where ApplicativeDo makes a difference), but it can be very slow for large do expressions. I'm mainly adding it for experimental reasons. ToDo: user guide docs Test Plan: validate Reviewers: simonpj, bgamari, austin, niteria, erikd Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1969 >--------------------------------------------------------------- 43ea95f2d42a27bee2293ee975ecd1a7aa011e3f compiler/main/DynFlags.hs | 2 + compiler/rename/RnExpr.hs | 226 ++++++++++++++++--------- docs/users_guide/glasgow_exts.rst | 17 ++ testsuite/tests/ado/ado-optimal.hs | 59 +++++++ testsuite/tests/ado/ado-optimal.stdout | 1 + testsuite/tests/ado/ado004.hs | 9 + testsuite/tests/ado/ado004.stderr | 6 + testsuite/tests/ado/all.T | 1 + utils/mkUserGuidePart/Options/Optimizations.hs | 6 + 9 files changed, 251 insertions(+), 76 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 43ea95f2d42a27bee2293ee975ecd1a7aa011e3f From git at git.haskell.org Mon Jul 18 17:58:39 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 18 Jul 2016 17:58:39 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Add nameSetElemsStable and fix the build (375afd4) Message-ID: <20160718175839.D500D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/375afd47ade46ef07fb7f62009fd2aa3690efc28/ghc >--------------------------------------------------------------- commit 375afd47ade46ef07fb7f62009fd2aa3690efc28 Author: Bartosz Nitka Date: Thu Jun 2 10:34:57 2016 -0700 Add nameSetElemsStable and fix the build >--------------------------------------------------------------- 375afd47ade46ef07fb7f62009fd2aa3690efc28 compiler/basicTypes/NameSet.hs | 11 +++++++++++ compiler/utils/UniqFM.hs | 6 +++++- 2 files changed, 16 insertions(+), 1 deletion(-) diff --git a/compiler/basicTypes/NameSet.hs b/compiler/basicTypes/NameSet.hs index 7bca479..b764bd9 100644 --- a/compiler/basicTypes/NameSet.hs +++ b/compiler/basicTypes/NameSet.hs @@ -13,6 +13,7 @@ module NameSet ( minusNameSet, elemNameSet, nameSetElems, extendNameSet, extendNameSetList, delFromNameSet, delListFromNameSet, isEmptyNameSet, foldNameSet, filterNameSet, intersectsNameSet, intersectNameSet, + nameSetElemsStable, -- * Free variables FreeVars, @@ -33,6 +34,8 @@ module NameSet ( import Name import UniqSet +import UniqFM +import Data.List (sortBy) {- ************************************************************************ @@ -84,6 +87,14 @@ delListFromNameSet set ns = foldl delFromNameSet set ns intersectsNameSet s1 s2 = not (isEmptyNameSet (s1 `intersectNameSet` s2)) +-- | Get the elements of a NameSet with some stable ordering. +-- See Note [Deterministic UniqFM] to learn about nondeterminism +nameSetElemsStable :: NameSet -> [Name] +nameSetElemsStable ns = + sortBy stableNameCmp $ nonDetEltsUFM ns + -- It's OK to use nonDetEltsUFM here because we immediately sort + -- with stableNameCmp + {- ************************************************************************ * * diff --git a/compiler/utils/UniqFM.hs b/compiler/utils/UniqFM.hs index 0df5a2d..0056287 100644 --- a/compiler/utils/UniqFM.hs +++ b/compiler/utils/UniqFM.hs @@ -64,7 +64,7 @@ module UniqFM ( isNullUFM, lookupUFM, lookupUFM_Directly, lookupWithDefaultUFM, lookupWithDefaultUFM_Directly, - eltsUFM, keysUFM, splitUFM, + eltsUFM, keysUFM, splitUFM, nonDetEltsUFM, ufmToSet_Directly, ufmToList, ufmToIntMap, joinUFM, pprUniqFM, pprUFM, pluralUFM @@ -304,6 +304,10 @@ ufmToList (UFM m) = map (\(k, v) -> (getUnique k, v)) $ M.toList m ufmToIntMap :: UniqFM elt -> M.IntMap elt ufmToIntMap (UFM m) = m +-- See Note [Deterministic UniqFM] to learn about nondeterminism +nonDetEltsUFM :: UniqFM elt -> [elt] +nonDetEltsUFM (UFM m) = M.elems m + -- Hoopl joinUFM :: JoinFun v -> JoinFun (UniqFM v) joinUFM eltJoin l (OldFact old) (NewFact new) = foldUFM_Directly add (NoChange, old) new From git at git.haskell.org Mon Jul 18 17:58:43 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 18 Jul 2016 17:58:43 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Desugar ApplicativeDo and RecDo deterministically (aaa4e0e) Message-ID: <20160718175843.B21553A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/aaa4e0edfee30c6ee70d9743c35a9da629b62124/ghc >--------------------------------------------------------------- commit aaa4e0edfee30c6ee70d9743c35a9da629b62124 Author: Bartosz Nitka Date: Mon Jun 6 06:08:54 2016 -0700 Desugar ApplicativeDo and RecDo deterministically This fixes a problem described in Note [Deterministic ApplicativeDo and RecursiveDo desugaring]. Test Plan: ./validate + new testcase Reviewers: simonpj, bgamari, austin, simonmar Reviewed By: simonmar Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2287 GHC Trac Issues: #4012 >--------------------------------------------------------------- aaa4e0edfee30c6ee70d9743c35a9da629b62124 compiler/basicTypes/Name.hs | 4 +- compiler/basicTypes/NameSet.hs | 2 + compiler/rename/RnExpr.hs | 43 +++++++++++++--- testsuite/tests/determinism/determ019/A.hs | 57 ++++++++++++++++++++++ .../determinism/{determ013 => determ019}/Makefile | 2 +- .../determinism/{determ007 => determ019}/all.T | 4 +- .../determ019.stdout} | 0 7 files changed, 101 insertions(+), 11 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc aaa4e0edfee30c6ee70d9743c35a9da629b62124 From git at git.haskell.org Mon Jul 18 17:58:46 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 18 Jul 2016 17:58:46 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Implement deterministic CallInfoSet (d3cc329) Message-ID: <20160718175846.6904F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/d3cc329a8e81fc14041c154e58a0a1f246fed951/ghc >--------------------------------------------------------------- commit d3cc329a8e81fc14041c154e58a0a1f246fed951 Author: Bartosz Nitka Date: Mon Jun 6 04:36:21 2016 -0700 Implement deterministic CallInfoSet We need CallInfoSet to be deterministic because it determines the order that the binds get generated. Currently it's not deterministic because it's keyed on `CallKey = [Maybe Type]` and `Ord CallKey` is implemented with `cmpType` which is nondeterministic. See Note [CallInfoSet determinism] for more details. Test Plan: ./validate Reviewers: simonpj, bgamari, austin, simonmar Reviewed By: simonmar Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2242 GHC Trac Issues: #4012 >--------------------------------------------------------------- d3cc329a8e81fc14041c154e58a0a1f246fed951 compiler/specialise/Specialise.hs | 111 +++++++++++++++++++++++++------------- 1 file changed, 74 insertions(+), 37 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc d3cc329a8e81fc14041c154e58a0a1f246fed951 From git at git.haskell.org Mon Jul 18 17:58:49 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 18 Jul 2016 17:58:49 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Use DVarSet in Vectorise.Exp (2d3dc76) Message-ID: <20160718175849.1B2023A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/2d3dc76bceb93297bc0d67852c079e85ad04a156/ghc >--------------------------------------------------------------- commit 2d3dc76bceb93297bc0d67852c079e85ad04a156 Author: Bartosz Nitka Date: Tue Jun 7 06:28:51 2016 -0700 Use DVarSet in Vectorise.Exp I believe this part of code is a bit unused. That's probably why it never became a problem in my testing. I'm changing to deterministic sets here to be safer. Test Plan: ./validate Reviewers: simonmar, austin, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2312 GHC Trac Issues: #4012 >--------------------------------------------------------------- 2d3dc76bceb93297bc0d67852c079e85ad04a156 compiler/vectorise/Vectorise/Exp.hs | 53 ++++++++++++++++++------------------- 1 file changed, 26 insertions(+), 27 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 2d3dc76bceb93297bc0d67852c079e85ad04a156 From git at git.haskell.org Mon Jul 18 17:58:51 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 18 Jul 2016 17:58:51 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Use UniqFM for SigOf (e8e8f8b) Message-ID: <20160718175851.BB8DB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/e8e8f8bdb6f851db02fa3112fd15bd5de13a9ad7/ghc >--------------------------------------------------------------- commit e8e8f8bdb6f851db02fa3112fd15bd5de13a9ad7 Author: Bartosz Nitka Date: Mon Jun 13 07:35:32 2016 -0700 Use UniqFM for SigOf Summary: The Ord instance for ModuleName is currently implemented in terms of Uniques causing potential determinism problems. I plan to change it to use the actual FastStrings and in preparation for that I'm switching to UniqFM where it's possible (you need *one* Unique per key, and you can't get the keys back), so that the performance doesn't suffer. Test Plan: ./validate Reviewers: simonmar, austin, ezyang, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2320 GHC Trac Issues: #4012 >--------------------------------------------------------------- e8e8f8bdb6f851db02fa3112fd15bd5de13a9ad7 compiler/main/DynFlags.hs | 9 +++++---- 1 file changed, 5 insertions(+), 4 deletions(-) diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index f6598b9..0a944b7 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -164,6 +164,7 @@ import CmdLineParser import Constants import Panic import Util +import UniqFM import Maybes import MonadUtils import qualified Pretty @@ -629,10 +630,10 @@ instance Show SafeHaskellMode where instance Outputable SafeHaskellMode where ppr = text . show -type SigOf = Map ModuleName Module +type SigOf = ModuleNameEnv Module getSigOf :: DynFlags -> ModuleName -> Maybe Module -getSigOf dflags n = Map.lookup n (sigOf dflags) +getSigOf dflags n = lookupUFM (sigOf dflags) n -- | Contains not only a collection of 'GeneralFlag's but also a plethora of -- information relating to the compilation of a single file or GHC session @@ -1438,7 +1439,7 @@ defaultDynFlags mySettings = ghcMode = CompManager, ghcLink = LinkBinary, hscTarget = defaultHscTarget (sTargetPlatform mySettings), - sigOf = Map.empty, + sigOf = emptyUFM, verbosity = 0, optLevel = 0, debugLevel = 0, @@ -1981,7 +1982,7 @@ parseSigOf :: String -> SigOf parseSigOf str = case filter ((=="").snd) (readP_to_S parse str) of [(r, "")] -> r _ -> throwGhcException $ CmdLineError ("Can't parse -sig-of: " ++ str) - where parse = Map.fromList <$> sepBy parseEntry (R.char ',') + where parse = listToUFM <$> sepBy parseEntry (R.char ',') parseEntry = do n <- tok $ parseModuleName -- ToDo: deprecate this 'is' syntax? From git at git.haskell.org Mon Jul 18 17:58:54 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 18 Jul 2016 17:58:54 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Make UnitIdMap a deterministic map (da8e714) Message-ID: <20160718175854.6D7A63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/da8e7142ba480058638657393c5d698cf8e147f0/ghc >--------------------------------------------------------------- commit da8e7142ba480058638657393c5d698cf8e147f0 Author: Bartosz Nitka Date: Mon Jun 6 08:54:17 2016 -0700 Make UnitIdMap a deterministic map This impacts at least the order in which version macros are generated. It's pretty hard to track what kind of nondeterminism is benign and this should have no performance impact as the number of packages should be relatively small. Test Plan: ./validate Reviewers: simonmar, austin, bgamari, ezyang Reviewed By: ezyang Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2308 GHC Trac Issues: #4012 >--------------------------------------------------------------- da8e7142ba480058638657393c5d698cf8e147f0 compiler/main/Packages.hs | 53 ++++++++++++++++++++++++----------------------- compiler/utils/UniqDFM.hs | 7 ++++++- 2 files changed, 33 insertions(+), 27 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc da8e7142ba480058638657393c5d698cf8e147f0 From git at git.haskell.org Mon Jul 18 17:58:57 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 18 Jul 2016 17:58:57 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Make vectInfoParallelVars a DVarSet (3f5ef15) Message-ID: <20160718175857.210CC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/3f5ef15ff996794f733cc85623ebcd80008540ef/ghc >--------------------------------------------------------------- commit 3f5ef15ff996794f733cc85623ebcd80008540ef Author: Bartosz Nitka Date: Tue Jun 7 07:19:30 2016 -0700 Make vectInfoParallelVars a DVarSet We dump it in the interface file, so we need to do it in a deterministic order. I haven't seen any problems with this during my testing, but that's probably because it's unused. Test Plan: ./validate Reviewers: simonmar, austin, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2313 GHC Trac Issues: #4012 >--------------------------------------------------------------- 3f5ef15ff996794f733cc85623ebcd80008540ef compiler/iface/MkIface.hs | 2 +- compiler/iface/TcIface.hs | 2 +- compiler/main/HscTypes.hs | 6 +++--- compiler/main/TidyPgm.hs | 11 ++++++----- compiler/vectorise/Vectorise/Env.hs | 7 ++++--- compiler/vectorise/Vectorise/Exp.hs | 4 ++-- compiler/vectorise/Vectorise/Monad.hs | 2 +- compiler/vectorise/Vectorise/Monad/Global.hs | 2 +- 8 files changed, 19 insertions(+), 17 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 3f5ef15ff996794f733cc85623ebcd80008540ef From git at git.haskell.org Mon Jul 18 17:58:59 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 18 Jul 2016 17:58:59 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Make the Ord Module independent of Unique order (2nd try) (416b3ac) Message-ID: <20160718175859.C97483A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/416b3aced6fdd6a99363f689a6bdd9234b5140d4/ghc >--------------------------------------------------------------- commit 416b3aced6fdd6a99363f689a6bdd9234b5140d4 Author: Bartosz Nitka Date: Thu Jun 9 08:50:32 2016 -0700 Make the Ord Module independent of Unique order (2nd try) The `Ord Module` instance currently uses `Unique`s for comparison. We don't want to use the `Unique` order because it can introduce nondeterminism. This switches `Ord ModuleName` and `Ord UnitId` to use lexicographic ordering making `Ord Module` deterministic transitively. I've run `nofib` and it doesn't make a measurable difference. See also Note [ModuleEnv determinism and performance]. This fixes #12191 - the regression, that the previous version of this patch had. Test Plan: ./validate run nofib: P112 Reviewers: simonmar, bgamari, austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2354 GHC Trac Issues: #4012, #12191 >--------------------------------------------------------------- 416b3aced6fdd6a99363f689a6bdd9234b5140d4 compiler/basicTypes/Module.hs | 99 +++++++++++++++------- compiler/typecheck/FamInst.hs | 35 +++++++- testsuite/tests/driver/sigof01/all.T | 2 +- .../should_fail/overloadedrecfldsfail10.stderr | 4 +- testsuite/tests/rename/should_fail/T11071.stderr | 2 +- testsuite/tests/rename/should_fail/T11071a.stderr | 32 +++---- .../tests/typecheck/should_fail/T6018fail.stderr | 4 +- 7 files changed, 122 insertions(+), 56 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 416b3aced6fdd6a99363f689a6bdd9234b5140d4 From git at git.haskell.org Mon Jul 18 17:59:02 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 18 Jul 2016 17:59:02 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Make checkFamInstConsistency less expensive (d77ca3a) Message-ID: <20160718175902.729B43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/d77ca3a2b3bcacd48251e8b7626aeadb2fea02bb/ghc >--------------------------------------------------------------- commit d77ca3a2b3bcacd48251e8b7626aeadb2fea02bb Author: Bartosz Nitka Date: Tue Jun 21 15:54:00 2016 -0700 Make checkFamInstConsistency less expensive Doing canonicalization on every comparison turned out to be very expensive. Caching the canonicalization through the smart `modulePair` constructor gives `8%` reduction in allocations on `haddock.compiler` and `8.5%` reduction in allocations on `haddock.Cabal`. Possibly other things as well, but it's really visible in Haddock. Test Plan: ./validate Reviewers: jstolarek, simonpj, austin, simonmar, bgamari Reviewed By: simonpj, simonmar Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2350 GHC Trac Issues: #12191 >--------------------------------------------------------------- d77ca3a2b3bcacd48251e8b7626aeadb2fea02bb compiler/typecheck/FamInst.hs | 32 +++++++++++++++----------------- testsuite/tests/perf/haddock/all.T | 10 ++++++++-- 2 files changed, 23 insertions(+), 19 deletions(-) diff --git a/compiler/typecheck/FamInst.hs b/compiler/typecheck/FamInst.hs index 1d9e1ce..784bc81 100644 --- a/compiler/typecheck/FamInst.hs +++ b/compiler/typecheck/FamInst.hs @@ -40,8 +40,8 @@ import Pair import Panic import VarSet import Control.Monad -import Data.Map (Map) -import qualified Data.Map as Map +import Data.Set (Set) +import qualified Data.Set as Set #if __GLASGOW_HASKELL__ < 709 import Prelude hiding ( and ) @@ -124,28 +124,25 @@ certain that the modules in our `HscTypes.dep_finsts' are consistent.) -- whose family instances need to be checked for consistency. -- data ModulePair = ModulePair Module Module + -- Invariant: first Module < second Module + -- use the smart constructor + deriving (Ord, Eq) --- canonical order of the components of a module pair --- -canon :: ModulePair -> (Module, Module) -canon (ModulePair m1 m2) | m1 < m2 = (m1, m2) - | otherwise = (m2, m1) - -instance Eq ModulePair where - mp1 == mp2 = canon mp1 == canon mp2 - -instance Ord ModulePair where - mp1 `compare` mp2 = canon mp1 `compare` canon mp2 +-- | Smart constructor that establishes the invariant +modulePair :: Module -> Module -> ModulePair +modulePair a b + | a < b = ModulePair a b + | otherwise = ModulePair b a instance Outputable ModulePair where ppr (ModulePair m1 m2) = angleBrackets (ppr m1 <> comma <+> ppr m2) -- Sets of module pairs -- -type ModulePairSet = Map ModulePair () +type ModulePairSet = Set ModulePair listToSet :: [ModulePair] -> ModulePairSet -listToSet l = Map.fromList (zip l (repeat ())) +listToSet l = Set.fromList l checkFamInstConsistency :: [Module] -> [Module] -> TcM () checkFamInstConsistency famInstMods directlyImpMods @@ -170,7 +167,8 @@ checkFamInstConsistency famInstMods directlyImpMods -- instances of okPairs are consistent ; criticalPairs = listToSet $ allPairs famInstMods -- all pairs that we need to consider - ; toCheckPairs = Map.keys $ criticalPairs `Map.difference` okPairs + ; toCheckPairs = + Set.elems $ criticalPairs `Set.difference` okPairs -- the difference gives us the pairs we need to check now } @@ -178,7 +176,7 @@ checkFamInstConsistency famInstMods directlyImpMods } where allPairs [] = [] - allPairs (m:ms) = map (ModulePair m) ms ++ allPairs ms + allPairs (m:ms) = map (modulePair m) ms ++ allPairs ms check hpt_fam_insts (ModulePair m1 m2) = do { env1 <- getFamInsts hpt_fam_insts m1 diff --git a/testsuite/tests/perf/haddock/all.T b/testsuite/tests/perf/haddock/all.T index de45ea4..6ee448f 100644 --- a/testsuite/tests/perf/haddock/all.T +++ b/testsuite/tests/perf/haddock/all.T @@ -52,7 +52,7 @@ test('haddock.base', test('haddock.Cabal', [unless(in_tree_compiler(), skip), req_haddock ,stats_num_field('bytes allocated', - [(wordsize(64), 10941742184, 5) + [(wordsize(64), 10070330520, 5) # 2012-08-14: 3255435248 (amd64/Linux) # 2012-08-29: 3324606664 (amd64/Linux, new codegen) # 2012-10-08: 3373401360 (amd64/Linux) @@ -78,6 +78,11 @@ test('haddock.Cabal', # 2015-12-22: 10519532424 (amd64/Linux) - Lots of new Semigroup instances in Cabal # 2016-03-29: 11517963232 (amd64/Linux) - not yet investigated # 2016-03-30: 10941742184 (amd64/Linux) - defer inlining of Int* Ord methods + # 2016-04-06: 11542374816 (amd64/Linux) - CSE improvements and others + # 2016-04-07: 10963514352 (amd64/Linux) - Revert to what phabricator claims + # 2016-05-22: 11805238152 (amd64/Linux) - Make Generic1 poly-kinded + # 2016-06-05: 10997887320 (amd64/Linux) - Refactor derived Generic instances to reduce allocations + # 2016-06-21: 10070330520 (amd64/Linux) - D2350: Make checkFamInstConsistency less expensive ,(platform('i386-unknown-mingw32'), 3293415576, 5) # 2012-10-30: 1733638168 (x86/Windows) @@ -99,7 +104,7 @@ test('haddock.Cabal', test('haddock.compiler', [unless(in_tree_compiler(), skip), req_haddock ,stats_num_field('bytes allocated', - [(wordsize(64), 58017214568, 10) + [(wordsize(64), 55314944264, 10) # 2012P-08-14: 26070600504 (amd64/Linux) # 2012-08-29: 26353100288 (amd64/Linux, new CG) # 2012-09-18: 26882813032 (amd64/Linux) @@ -113,6 +118,7 @@ test('haddock.compiler', # 2015-12-03: 44721228752 (amd64/Linux) slow creep upwards # 2015-12-15: 49395782136 (amd64/Linux) more creep, following kind-equalities # 2015-12-17: 58017214568 (amd64/Linux) update Haddock to master + # 2016-06-21: 55314944264 (amd64/Linux) D2350: Make checkFamInstConsistency less expensive ,(platform('i386-unknown-mingw32'), 902576468, 10) # 2012-10-30: 13773051312 (x86/Windows) From git at git.haskell.org Mon Jul 18 17:59:05 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 18 Jul 2016 17:59:05 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Refactor match to not use Unique order (c0d4e35) Message-ID: <20160718175905.17B433A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/c0d4e3514a9d1570aa631bff78ae79ccea9cc691/ghc >--------------------------------------------------------------- commit c0d4e3514a9d1570aa631bff78ae79ccea9cc691 Author: Bartosz Nitka Date: Wed Jun 29 03:27:49 2016 -0700 Refactor match to not use Unique order Unique order can introduce nondeterminism. As a step towards removing the Ord Unique instance I've refactored the code to use deterministic sets instead. Test Plan: ./validate Reviewers: simonmar, austin, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2369 GHC Trac Issues: #4012 >--------------------------------------------------------------- c0d4e3514a9d1570aa631bff78ae79ccea9cc691 compiler/deSugar/Match.hs | 32 +++++++++++++++++++++++--------- 1 file changed, 23 insertions(+), 9 deletions(-) diff --git a/compiler/deSugar/Match.hs b/compiler/deSugar/Match.hs index fc70cc6..ecbed46 100644 --- a/compiler/deSugar/Match.hs +++ b/compiler/deSugar/Match.hs @@ -46,6 +46,8 @@ import Util import Name import Outputable import BasicTypes ( isGenerated ) +import Unique +import UniqDFM import Control.Monad( when, unless ) import qualified Data.Map as Map @@ -196,9 +198,9 @@ match vars@(v:_) ty eqns -- Eqns *can* be empty match_group [] = panic "match_group" match_group eqns@((group,_) : _) = case group of - PgCon {} -> matchConFamily vars ty (subGroup [(c,e) | (PgCon c, e) <- eqns]) + PgCon {} -> matchConFamily vars ty (subGroupUniq [(c,e) | (PgCon c, e) <- eqns]) PgSyn {} -> matchPatSyn vars ty (dropGroup eqns) - PgLit {} -> matchLiterals vars ty (subGroup [(l,e) | (PgLit l, e) <- eqns]) + PgLit {} -> matchLiterals vars ty (subGroupOrd [(l,e) | (PgLit l, e) <- eqns]) PgAny -> matchVariables vars ty (dropGroup eqns) PgN {} -> matchNPats vars ty (dropGroup eqns) PgNpK {} -> matchNPlusKPats vars ty (dropGroup eqns) @@ -809,22 +811,34 @@ groupEquations dflags eqns same_gp :: (PatGroup,EquationInfo) -> (PatGroup,EquationInfo) -> Bool (pg1,_) `same_gp` (pg2,_) = pg1 `sameGroup` pg2 -subGroup :: Ord a => [(a, EquationInfo)] -> [[EquationInfo]] +subGroup :: (m -> [[EquationInfo]]) -- Map.elems + -> m -- Map.empty + -> (a -> m -> Maybe [EquationInfo]) -- Map.lookup + -> (a -> [EquationInfo] -> m -> m) -- Map.insert + -> [(a, EquationInfo)] -> [[EquationInfo]] -- Input is a particular group. The result sub-groups the -- equations by with particular constructor, literal etc they match. -- Each sub-list in the result has the same PatGroup -- See Note [Take care with pattern order] -subGroup group - = map reverse $ Map.elems $ foldl accumulate Map.empty group +-- Parameterized by map operations to allow different implementations +-- and constraints, eg. types without Ord instance. +subGroup elems empty lookup insert group + = map reverse $ elems $ foldl accumulate empty group where accumulate pg_map (pg, eqn) - = case Map.lookup pg pg_map of - Just eqns -> Map.insert pg (eqn:eqns) pg_map - Nothing -> Map.insert pg [eqn] pg_map - + = case lookup pg pg_map of + Just eqns -> insert pg (eqn:eqns) pg_map + Nothing -> insert pg [eqn] pg_map -- pg_map :: Map a [EquationInfo] -- Equations seen so far in reverse order of appearance +subGroupOrd :: Ord a => [(a, EquationInfo)] -> [[EquationInfo]] +subGroupOrd = subGroup Map.elems Map.empty Map.lookup Map.insert + +subGroupUniq :: Uniquable a => [(a, EquationInfo)] -> [[EquationInfo]] +subGroupUniq = + subGroup eltsUDFM emptyUDFM (flip lookupUDFM) (\k v m -> addToUDFM m k v) + {- Note [Pattern synonym groups] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ If we see From git at git.haskell.org Mon Jul 18 17:59:08 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 18 Jul 2016 17:59:08 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Add a new determinism test (c42aafc) Message-ID: <20160718175908.8693F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/c42aafc3c6e1da44c839b5a098ea50a165315640/ghc >--------------------------------------------------------------- commit c42aafc3c6e1da44c839b5a098ea50a165315640 Author: Bartosz Nitka Date: Thu Jun 30 06:59:02 2016 -0700 Add a new determinism test This is one of the testcases that I forgot to commit >--------------------------------------------------------------- c42aafc3c6e1da44c839b5a098ea50a165315640 testsuite/tests/determinism/determ021/A.hs | 8 ++++++++ testsuite/tests/determinism/determ021/Makefile | 11 +++++++++++ .../determinism/{determ009 => determ021}/all.T | 4 ++-- .../tests/determinism/determ021/determ021.stdout | 22 ++++++++++++++++++++++ 4 files changed, 43 insertions(+), 2 deletions(-) diff --git a/testsuite/tests/determinism/determ021/A.hs b/testsuite/tests/determinism/determ021/A.hs new file mode 100644 index 0000000..773a012 --- /dev/null +++ b/testsuite/tests/determinism/determ021/A.hs @@ -0,0 +1,8 @@ +{-# LANGUAGE ApplicativeDo #-} +{-# OPTIONS_GHC -ddump-types #-} +module A where + +test2 f = do + x <- f 3 + y <- f 4 + return (x + y) diff --git a/testsuite/tests/determinism/determ021/Makefile b/testsuite/tests/determinism/determ021/Makefile new file mode 100644 index 0000000..e88edef --- /dev/null +++ b/testsuite/tests/determinism/determ021/Makefile @@ -0,0 +1,11 @@ +TOP=../../.. +include $(TOP)/mk/boilerplate.mk +include $(TOP)/mk/test.mk + +determ021: + $(RM) A.hi A.o + '$(TEST_HC)' $(TEST_HC_OPTS) -O -dinitial-unique=0 -dunique-increment=1 A.hs + $(CP) A.hi A.normal.hi + $(RM) A.hi A.o + '$(TEST_HC)' $(TEST_HC_OPTS) -O -dinitial-unique=16777215 -dunique-increment=-1 A.hs + diff A.hi A.normal.hi diff --git a/testsuite/tests/determinism/determ009/all.T b/testsuite/tests/determinism/determ021/all.T similarity index 50% copy from testsuite/tests/determinism/determ009/all.T copy to testsuite/tests/determinism/determ021/all.T index 7cae393..35af362 100644 --- a/testsuite/tests/determinism/determ009/all.T +++ b/testsuite/tests/determinism/determ021/all.T @@ -1,4 +1,4 @@ -test('determ009', +test('determ021', extra_clean(['A.o', 'A.hi', 'A.normal.hi']), run_command, - ['$MAKE -s --no-print-directory determ009']) + ['$MAKE -s --no-print-directory determ021']) diff --git a/testsuite/tests/determinism/determ021/determ021.stdout b/testsuite/tests/determinism/determ021/determ021.stdout new file mode 100644 index 0000000..747064f --- /dev/null +++ b/testsuite/tests/determinism/determ021/determ021.stdout @@ -0,0 +1,22 @@ +[1 of 1] Compiling A ( A.hs, A.o ) +TYPE SIGNATURES + test2 :: + forall t b (f :: * -> *). + (Num b, Num t, Applicative f) => + (t -> f b) -> f b +TYPE CONSTRUCTORS +COERCION AXIOMS +Dependent modules: [] +Dependent packages: [base-4.9.0.0, ghc-prim-0.5.0.0, + integer-gmp-1.0.0.1] +[1 of 1] Compiling A ( A.hs, A.o ) +TYPE SIGNATURES + test2 :: + forall t b (f :: * -> *). + (Num b, Num t, Applicative f) => + (t -> f b) -> f b +TYPE CONSTRUCTORS +COERCION AXIOMS +Dependent modules: [] +Dependent packages: [base-4.9.0.0, ghc-prim-0.5.0.0, + integer-gmp-1.0.0.1] From git at git.haskell.org Mon Jul 18 17:59:11 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 18 Jul 2016 17:59:11 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Make accept (b420d79) Message-ID: <20160718175911.3093B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/b420d79ef287f5a551ae4e476cc639656ca10b50/ghc >--------------------------------------------------------------- commit b420d79ef287f5a551ae4e476cc639656ca10b50 Author: Bartosz Nitka Date: Wed Jul 13 12:41:45 2016 -0700 Make accept >--------------------------------------------------------------- b420d79ef287f5a551ae4e476cc639656ca10b50 testsuite/tests/ado/ado004.stderr | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/testsuite/tests/ado/ado004.stderr b/testsuite/tests/ado/ado004.stderr index 2bb2e6d..8f5a816 100644 --- a/testsuite/tests/ado/ado004.stderr +++ b/testsuite/tests/ado/ado004.stderr @@ -6,8 +6,8 @@ TYPE SIGNATURES (Num b, Num t, Applicative f) => (t -> f b) -> f b test2a :: - forall (f :: * -> *) b t. - (Num t, Num b, Functor f) => + forall t b (f :: * -> *). + (Num b, Num t, Functor f) => (t -> f b) -> f b test2b :: forall (m :: * -> *) a t. (Num t, Monad m) => (t -> a) -> m a From git at git.haskell.org Tue Jul 19 05:53:13 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 19 Jul 2016 05:53:13 +0000 (UTC) Subject: [commit: ghc] branch 'wip/lazy-instance-matching' created Message-ID: <20160719055313.7BE3E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/lazy-instance-matching Referencing: 3c2ce1d19bc79d05049f220d191676699b3d02f5 From git at git.haskell.org Tue Jul 19 05:53:16 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 19 Jul 2016 05:53:16 +0000 (UTC) Subject: [commit: ghc] wip/lazy-instance-matching: TcInteract: Add braces to matchClassInst trace output (1757368) Message-ID: <20160719055316.39DC93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/lazy-instance-matching Link : http://ghc.haskell.org/trac/ghc/changeset/175736873679a2ae1c2e98b9f2a3f54197e2177c/ghc >--------------------------------------------------------------- commit 175736873679a2ae1c2e98b9f2a3f54197e2177c Author: Ben Gamari Date: Mon Jul 18 20:17:24 2016 +0200 TcInteract: Add braces to matchClassInst trace output This allows you to easily move to the result in a well-equipped editor. >--------------------------------------------------------------- 175736873679a2ae1c2e98b9f2a3f54197e2177c compiler/typecheck/TcInteract.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/typecheck/TcInteract.hs b/compiler/typecheck/TcInteract.hs index f659b22..298bbb2 100644 --- a/compiler/typecheck/TcInteract.hs +++ b/compiler/typecheck/TcInteract.hs @@ -1791,9 +1791,9 @@ matchClassInst dflags inerts clas tys loc pred = mkClassPred clas tys matchClassInst dflags _ clas tys loc - = do { traceTcS "matchClassInst" $ vcat [ text "pred =" <+> ppr (mkClassPred clas tys) ] + = do { traceTcS "matchClassInst" $ text "pred =" <+> ppr (mkClassPred clas tys) <+> char '{' ; res <- match_class_inst dflags clas tys loc - ; traceTcS "matchClassInst result" $ ppr res + ; traceTcS "} matchClassInst result" $ ppr res ; return res } match_class_inst :: DynFlags -> Class -> [Type] -> CtLoc -> TcS LookupInstResult From git at git.haskell.org Tue Jul 19 05:53:18 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 19 Jul 2016 05:53:18 +0000 (UTC) Subject: [commit: ghc] wip/lazy-instance-matching: IfaceEnv: Only parse OccNames in GHC.Tuple (adf69e4) Message-ID: <20160719055318.F08BA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/lazy-instance-matching Link : http://ghc.haskell.org/trac/ghc/changeset/adf69e43302f7a19b75d0b2ad9d08ef375cf51b8/ghc >--------------------------------------------------------------- commit adf69e43302f7a19b75d0b2ad9d08ef375cf51b8 Author: Ben Gamari Date: Mon Jul 18 21:56:42 2016 +0200 IfaceEnv: Only parse OccNames in GHC.Tuple >--------------------------------------------------------------- adf69e43302f7a19b75d0b2ad9d08ef375cf51b8 compiler/iface/IfaceEnv.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/iface/IfaceEnv.hs b/compiler/iface/IfaceEnv.hs index ff2f648..75acb68 100644 --- a/compiler/iface/IfaceEnv.hs +++ b/compiler/iface/IfaceEnv.hs @@ -33,7 +33,7 @@ import Module import FastString import FastStringEnv import IfaceType -import PrelNames ( gHC_TYPES, gHC_PRIM, gHC_TUPLE ) +import PrelNames ( gHC_TUPLE ) import UniqSupply import SrcLoc import Util @@ -214,7 +214,7 @@ are two reasons why we might look up an Orig RdrName for built-in syntax, lookupOrigNameCache :: OrigNameCache -> Module -> OccName -> Maybe Name lookupOrigNameCache nc mod occ - | mod == gHC_TYPES || mod == gHC_PRIM || mod == gHC_TUPLE + | mod == gHC_TUPLE , Just name <- isBuiltInOcc_maybe occ = -- See Note [Known-key names], 3(c) in PrelNames -- Special case for tuples; there are too many From git at git.haskell.org Tue Jul 19 05:53:21 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 19 Jul 2016 05:53:21 +0000 (UTC) Subject: [commit: ghc] wip/lazy-instance-matching: InstEnv: Ensure that instance visibility check is lazy (3c2ce1d) Message-ID: <20160719055321.A0A1D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/lazy-instance-matching Link : http://ghc.haskell.org/trac/ghc/changeset/3c2ce1d19bc79d05049f220d191676699b3d02f5/ghc >--------------------------------------------------------------- commit 3c2ce1d19bc79d05049f220d191676699b3d02f5 Author: Ben Gamari Date: Tue Jul 19 07:39:56 2016 +0200 InstEnv: Ensure that instance visibility check is lazy Previously instIsVisible had completely broken the laziness of lookupInstEnv' since it would examine is_dfun_name to check the name of the defining module (to know whether it is an interactive module). This resulted in the visibility check drawing in an interface file unnecessarily. >--------------------------------------------------------------- 3c2ce1d19bc79d05049f220d191676699b3d02f5 compiler/iface/TcIface.hs | 2 +- compiler/types/InstEnv.hs | 27 ++++++++++++++++++--------- 2 files changed, 19 insertions(+), 10 deletions(-) diff --git a/compiler/iface/TcIface.hs b/compiler/iface/TcIface.hs index f366c51..a551c96 100644 --- a/compiler/iface/TcIface.hs +++ b/compiler/iface/TcIface.hs @@ -657,7 +657,7 @@ tcIfaceInst (IfaceClsInst { ifDFun = dfun_occ, ifOFlag = oflag = do { dfun <- forkM (text "Dict fun" <+> ppr dfun_occ) $ tcIfaceExtId dfun_occ ; let mb_tcs' = map (fmap ifaceTyConName) mb_tcs - ; return (mkImportedInstance cls mb_tcs' dfun oflag orph) } + ; return (mkImportedInstance cls mb_tcs' dfun_occ dfun oflag orph) } tcIfaceFamInst :: IfaceFamInst -> IfL FamInst tcIfaceFamInst (IfaceFamInst { ifFamInstFam = fam, ifFamInstTys = mb_tcs diff --git a/compiler/types/InstEnv.hs b/compiler/types/InstEnv.hs index a8b5f0f..e87d732 100644 --- a/compiler/types/InstEnv.hs +++ b/compiler/types/InstEnv.hs @@ -61,6 +61,12 @@ data ClsInst is_cls_nm :: Name -- Class name , is_tcs :: [Maybe Name] -- Top of type args + -- We use this for the visibility check, instIsVisible. Note how + -- we cannot use the Module attached to is_dfun, since doing so + -- would mean we would potentially pull in an entire interface + -- file unnecessarily. This was the cause of #12367. + , is_dfun_name :: Name -- Defining module + -- Used for "proper matching"; see Note [Proper-match fields] , is_tvs :: [TyVar] -- Fresh template tyvars for full match -- See Note [Template tyvars are fresh] @@ -226,9 +232,10 @@ mkLocalInstance :: DFunId -> OverlapFlag mkLocalInstance dfun oflag tvs cls tys = ClsInst { is_flag = oflag, is_dfun = dfun , is_tvs = tvs + , is_dfun_name = dfun_name , is_cls = cls, is_cls_nm = cls_name , is_tys = tys, is_tcs = roughMatchTcs tys - , is_orphan = orph + , is_orphan = pprTrace "mkLocalInstance" empty orph } where cls_name = className cls @@ -257,21 +264,23 @@ mkLocalInstance dfun oflag tvs cls tys choose_one nss = chooseOrphanAnchor (unionNameSets nss) -mkImportedInstance :: Name - -> [Maybe Name] - -> DFunId - -> OverlapFlag - -> IsOrphan +mkImportedInstance :: Name -- ^ the name of the class + -> [Maybe Name] -- ^ the types which the class was applied to + -> Name -- ^ the 'Name' of the dictionary binding + -> DFunId -- ^ the 'Id' of the dictionary. + -> OverlapFlag -- ^ may this instance overlap? + -> IsOrphan -- ^ is this instance an orphan? -> ClsInst -- Used for imported instances, where we get the rough-match stuff -- from the interface file -- The bound tyvars of the dfun are guaranteed fresh, because -- the dfun has been typechecked out of the same interface file -mkImportedInstance cls_nm mb_tcs dfun oflag orphan +mkImportedInstance cls_nm mb_tcs dfun_name dfun oflag orphan = ClsInst { is_flag = oflag, is_dfun = dfun , is_tvs = tvs, is_tys = tys + , is_dfun_name = dfun_name , is_cls_nm = cls_nm, is_cls = cls, is_tcs = mb_tcs - , is_orphan = orphan } + , is_orphan = pprTrace "mkImportedInstance" empty orphan } where (tvs, _, cls, tys) = tcSplitDFunTy (idType dfun) @@ -397,7 +406,7 @@ instIsVisible vis_mods ispec | IsOrphan <- is_orphan ispec = mod `elemModuleSet` vis_mods | otherwise = True where - mod = nameModule (idName (is_dfun ispec)) + mod = nameModule $ is_dfun_name ispec classInstances :: InstEnvs -> Class -> [ClsInst] classInstances (InstEnvs { ie_global = pkg_ie, ie_local = home_ie, ie_visible = vis_mods }) cls From git at git.haskell.org Tue Jul 19 05:57:39 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 19 Jul 2016 05:57:39 +0000 (UTC) Subject: [commit: ghc] wip/lazy-instance-matching: InstEnv: Ensure that instance visibility check is lazy (73d1a9f) Message-ID: <20160719055739.C62EB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/lazy-instance-matching Link : http://ghc.haskell.org/trac/ghc/changeset/73d1a9f5c853c2aad88c7d70cce7e742555ac094/ghc >--------------------------------------------------------------- commit 73d1a9f5c853c2aad88c7d70cce7e742555ac094 Author: Ben Gamari Date: Tue Jul 19 07:39:56 2016 +0200 InstEnv: Ensure that instance visibility check is lazy Previously instIsVisible had completely broken the laziness of lookupInstEnv' since it would examine is_dfun_name to check the name of the defining module (to know whether it is an interactive module). This resulted in the visibility check drawing in an interface file unnecessarily. >--------------------------------------------------------------- 73d1a9f5c853c2aad88c7d70cce7e742555ac094 compiler/iface/TcIface.hs | 2 +- compiler/types/InstEnv.hs | 23 ++++++++++++++++------- 2 files changed, 17 insertions(+), 8 deletions(-) diff --git a/compiler/iface/TcIface.hs b/compiler/iface/TcIface.hs index f366c51..a551c96 100644 --- a/compiler/iface/TcIface.hs +++ b/compiler/iface/TcIface.hs @@ -657,7 +657,7 @@ tcIfaceInst (IfaceClsInst { ifDFun = dfun_occ, ifOFlag = oflag = do { dfun <- forkM (text "Dict fun" <+> ppr dfun_occ) $ tcIfaceExtId dfun_occ ; let mb_tcs' = map (fmap ifaceTyConName) mb_tcs - ; return (mkImportedInstance cls mb_tcs' dfun oflag orph) } + ; return (mkImportedInstance cls mb_tcs' dfun_occ dfun oflag orph) } tcIfaceFamInst :: IfaceFamInst -> IfL FamInst tcIfaceFamInst (IfaceFamInst { ifFamInstFam = fam, ifFamInstTys = mb_tcs diff --git a/compiler/types/InstEnv.hs b/compiler/types/InstEnv.hs index a8b5f0f..40865eb 100644 --- a/compiler/types/InstEnv.hs +++ b/compiler/types/InstEnv.hs @@ -61,6 +61,12 @@ data ClsInst is_cls_nm :: Name -- Class name , is_tcs :: [Maybe Name] -- Top of type args + -- We use this for the visibility check, instIsVisible. Note how + -- we cannot use the Module attached to is_dfun, since doing so + -- would mean we would potentially pull in an entire interface + -- file unnecessarily. This was the cause of #12367. + , is_dfun_name :: Name -- Defining module + -- Used for "proper matching"; see Note [Proper-match fields] , is_tvs :: [TyVar] -- Fresh template tyvars for full match -- See Note [Template tyvars are fresh] @@ -226,6 +232,7 @@ mkLocalInstance :: DFunId -> OverlapFlag mkLocalInstance dfun oflag tvs cls tys = ClsInst { is_flag = oflag, is_dfun = dfun , is_tvs = tvs + , is_dfun_name = dfun_name , is_cls = cls, is_cls_nm = cls_name , is_tys = tys, is_tcs = roughMatchTcs tys , is_orphan = orph @@ -257,19 +264,21 @@ mkLocalInstance dfun oflag tvs cls tys choose_one nss = chooseOrphanAnchor (unionNameSets nss) -mkImportedInstance :: Name - -> [Maybe Name] - -> DFunId - -> OverlapFlag - -> IsOrphan +mkImportedInstance :: Name -- ^ the name of the class + -> [Maybe Name] -- ^ the types which the class was applied to + -> Name -- ^ the 'Name' of the dictionary binding + -> DFunId -- ^ the 'Id' of the dictionary. + -> OverlapFlag -- ^ may this instance overlap? + -> IsOrphan -- ^ is this instance an orphan? -> ClsInst -- Used for imported instances, where we get the rough-match stuff -- from the interface file -- The bound tyvars of the dfun are guaranteed fresh, because -- the dfun has been typechecked out of the same interface file -mkImportedInstance cls_nm mb_tcs dfun oflag orphan +mkImportedInstance cls_nm mb_tcs dfun_name dfun oflag orphan = ClsInst { is_flag = oflag, is_dfun = dfun , is_tvs = tvs, is_tys = tys + , is_dfun_name = dfun_name , is_cls_nm = cls_nm, is_cls = cls, is_tcs = mb_tcs , is_orphan = orphan } where @@ -397,7 +406,7 @@ instIsVisible vis_mods ispec | IsOrphan <- is_orphan ispec = mod `elemModuleSet` vis_mods | otherwise = True where - mod = nameModule (idName (is_dfun ispec)) + mod = nameModule $ is_dfun_name ispec classInstances :: InstEnvs -> Class -> [ClsInst] classInstances (InstEnvs { ie_global = pkg_ie, ie_local = home_ie, ie_visible = vis_mods }) cls From git at git.haskell.org Tue Jul 19 11:04:56 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 19 Jul 2016 11:04:56 +0000 (UTC) Subject: [commit: ghc] wip/lazy-instance-matching: TcInteract: Add braces to matchClassInst trace output (3822b65) Message-ID: <20160719110456.D68D83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/lazy-instance-matching Link : http://ghc.haskell.org/trac/ghc/changeset/3822b65f851e1454838a4f4f65a6cc5140d39be8/ghc >--------------------------------------------------------------- commit 3822b65f851e1454838a4f4f65a6cc5140d39be8 Author: Ben Gamari Date: Mon Jul 18 20:17:24 2016 +0200 TcInteract: Add braces to matchClassInst trace output This allows you to easily move to the result in a well-equipped editor. >--------------------------------------------------------------- 3822b65f851e1454838a4f4f65a6cc5140d39be8 compiler/typecheck/TcInteract.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/typecheck/TcInteract.hs b/compiler/typecheck/TcInteract.hs index f659b22..298bbb2 100644 --- a/compiler/typecheck/TcInteract.hs +++ b/compiler/typecheck/TcInteract.hs @@ -1791,9 +1791,9 @@ matchClassInst dflags inerts clas tys loc pred = mkClassPred clas tys matchClassInst dflags _ clas tys loc - = do { traceTcS "matchClassInst" $ vcat [ text "pred =" <+> ppr (mkClassPred clas tys) ] + = do { traceTcS "matchClassInst" $ text "pred =" <+> ppr (mkClassPred clas tys) <+> char '{' ; res <- match_class_inst dflags clas tys loc - ; traceTcS "matchClassInst result" $ ppr res + ; traceTcS "} matchClassInst result" $ ppr res ; return res } match_class_inst :: DynFlags -> Class -> [Type] -> CtLoc -> TcS LookupInstResult From git at git.haskell.org Tue Jul 19 11:04:59 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 19 Jul 2016 11:04:59 +0000 (UTC) Subject: [commit: ghc] wip/lazy-instance-matching: InstEnv: Ensure that instance visibility check is lazy (fe94e90) Message-ID: <20160719110459.8B7513A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/lazy-instance-matching Link : http://ghc.haskell.org/trac/ghc/changeset/fe94e90944161e3938c9a755fd78875cb05377c7/ghc >--------------------------------------------------------------- commit fe94e90944161e3938c9a755fd78875cb05377c7 Author: Ben Gamari Date: Tue Jul 19 07:39:56 2016 +0200 InstEnv: Ensure that instance visibility check is lazy Previously instIsVisible had completely broken the laziness of lookupInstEnv' since it would examine is_dfun_name to check the name of the defining module (to know whether it is an interactive module). This resulted in the visibility check drawing in an interface file unnecessarily. >--------------------------------------------------------------- fe94e90944161e3938c9a755fd78875cb05377c7 compiler/iface/TcIface.hs | 8 ++-- compiler/types/InstEnv.hs | 97 ++++++++++++++++++++++++++++++++--------------- 2 files changed, 71 insertions(+), 34 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc fe94e90944161e3938c9a755fd78875cb05377c7 From git at git.haskell.org Tue Jul 19 11:05:01 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 19 Jul 2016 11:05:01 +0000 (UTC) Subject: [commit: ghc] wip/lazy-instance-matching's head updated: InstEnv: Ensure that instance visibility check is lazy (fe94e90) Message-ID: <20160719110501.CAF6C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/lazy-instance-matching' now includes: d213ab3 Fix misspellings of the word "instance" in comments 3fa3fe8 Make DeriveFunctor work with unboxed tuples 514c4a4 Fix Template Haskell reification of unboxed tuple types 1fc41d3 Make okConIdOcc recognize unboxed tuples 3822b65 TcInteract: Add braces to matchClassInst trace output fe94e90 InstEnv: Ensure that instance visibility check is lazy From git at git.haskell.org Tue Jul 19 16:07:39 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 19 Jul 2016 16:07:39 +0000 (UTC) Subject: [commit: ghc] master: Fix PDF build for the User's Guide. (0df3f4c) Message-ID: <20160719160739.65A073A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0df3f4cdd1dfff42461e3f5c3962f1ecd7c90652/ghc >--------------------------------------------------------------- commit 0df3f4cdd1dfff42461e3f5c3962f1ecd7c90652 Author: Gabor Pali Date: Tue Jul 19 18:05:53 2016 +0200 Fix PDF build for the User's Guide. >--------------------------------------------------------------- 0df3f4cdd1dfff42461e3f5c3962f1ecd7c90652 docs/users_guide/8.2.1-notes.rst | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/docs/users_guide/8.2.1-notes.rst b/docs/users_guide/8.2.1-notes.rst index 2ae804d..1d302ff 100644 --- a/docs/users_guide/8.2.1-notes.rst +++ b/docs/users_guide/8.2.1-notes.rst @@ -49,7 +49,8 @@ Template Haskell current declaration group when used as in .. code-block:: none - f x = $(addModFinalizer (reify 'x >>= runIO . print) >> [| x |]) + + f x = $(addModFinalizer (reify 'x >>= runIO . print) >> [| x |]) Runtime system ~~~~~~~~~~~~~~ From git at git.haskell.org Wed Jul 20 09:34:38 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 20 Jul 2016 09:34:38 +0000 (UTC) Subject: [commit: ghc] master: Support SCC pragmas in declaration context (98b2c50) Message-ID: <20160720093438.6944D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/98b2c5088a6f1a3b40c6eedc69d9204ba53690d3/ghc >--------------------------------------------------------------- commit 98b2c5088a6f1a3b40c6eedc69d9204ba53690d3 Author: Ömer Sinan Ağacan Date: Wed Jul 20 09:33:43 2016 +0000 Support SCC pragmas in declaration context Not having SCCs at the top level is becoming annoying real quick. For simplest cases, it's possible to do this transformation: f x y = ... => f = {-# SCC f #-} \x y -> ... However, it doesn't work when there's a `where` clause: f x y = where t = ... => f = {-# SCC f #-} \x y -> where t = ... Or when we have a "equation style" definition: f (C1 ...) = ... f (C2 ...) = ... f (C3 ...) = ... ... (usual solution is to rename `f` to `f'` and define a new `f` with a `SCC`) This patch implements support for SCC annotations in declaration contexts. This is now a valid program: f x y = ... where g z = ... {-# SCC g #-} {-# SCC f #-} Test Plan: This passes slow validate (no new failures added). Reviewers: goldfire, mpickering, austin, bgamari, simonmar Reviewed By: bgamari, simonmar Subscribers: simonmar, thomie, mpickering Differential Revision: https://phabricator.haskell.org/D2407 >--------------------------------------------------------------- 98b2c5088a6f1a3b40c6eedc69d9204ba53690d3 compiler/deSugar/DsMeta.hs | 4 +-- compiler/hsSyn/HsBinds.hs | 24 +++++++++++++- compiler/parser/Parser.y | 38 +++++++++++++++------- compiler/rename/RnBinds.hs | 9 +++++ compiler/typecheck/TcBinds.hs | 23 ++++++++++++- compiler/typecheck/TcSigs.hs | 3 +- docs/users_guide/8.2.1-notes.rst | 4 +++ docs/users_guide/profiling.rst | 21 ++++++++++-- testsuite/config/ghc | 2 ++ testsuite/tests/profiling/should_run/all.T | 5 +++ .../tests/profiling/should_run/toplevel_scc_1.hs | 23 +++++++++++++ .../should_run/toplevel_scc_1.prof.sample | 30 +++++++++++++++++ .../profiling/should_run/toplevel_scc_1.stdin | 1 + .../profiling/should_run/toplevel_scc_1.stdout | 1 + 14 files changed, 170 insertions(+), 18 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 98b2c5088a6f1a3b40c6eedc69d9204ba53690d3 From git at git.haskell.org Wed Jul 20 13:17:00 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 20 Jul 2016 13:17:00 +0000 (UTC) Subject: [commit: ghc] master: Make Data.{Bifoldable, Bitraversable} -XSafe (e46b768) Message-ID: <20160720131700.078423A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e46b76816c67ca8651aaf2c119632ff1bdb3766f/ghc >--------------------------------------------------------------- commit e46b76816c67ca8651aaf2c119632ff1bdb3766f Author: Ryan Scott Date: Wed Jul 20 09:15:56 2016 -0400 Make Data.{Bifoldable,Bitraversable} -XSafe Test Plan: Previously, `Data.{Bifoldable,Bitraversable}` were being inferred as `Unsafe` due to a transitive `Data.Coerce` import from `Data.Functor.Utils`. This rectifies this unfortunate mistake. Reviewers: austin, hvr, bgamari Reviewed By: bgamari Subscribers: thomie, phadej Differential Revision: https://phabricator.haskell.org/D2412 >--------------------------------------------------------------- e46b76816c67ca8651aaf2c119632ff1bdb3766f libraries/base/Data/Bifoldable.hs | 1 + libraries/base/Data/Bitraversable.hs | 2 ++ libraries/base/Data/Functor/Utils.hs | 1 + 3 files changed, 4 insertions(+) diff --git a/libraries/base/Data/Bifoldable.hs b/libraries/base/Data/Bifoldable.hs index 11a1c25..9006e61 100644 --- a/libraries/base/Data/Bifoldable.hs +++ b/libraries/base/Data/Bifoldable.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Safe #-} {-# LANGUAGE ScopedTypeVariables #-} ----------------------------------------------------------------------------- diff --git a/libraries/base/Data/Bitraversable.hs b/libraries/base/Data/Bitraversable.hs index 42e9635..f185044 100644 --- a/libraries/base/Data/Bitraversable.hs +++ b/libraries/base/Data/Bitraversable.hs @@ -1,3 +1,5 @@ +{-# LANGUAGE Safe #-} + ----------------------------------------------------------------------------- -- | -- Module : Data.Bitraversable diff --git a/libraries/base/Data/Functor/Utils.hs b/libraries/base/Data/Functor/Utils.hs index e24d235..79b3418 100644 --- a/libraries/base/Data/Functor/Utils.hs +++ b/libraries/base/Data/Functor/Utils.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE Trustworthy #-} {-# LANGUAGE NoImplicitPrelude #-} ----------------------------------------------------------------------------- From git at git.haskell.org Wed Jul 20 13:18:05 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 20 Jul 2016 13:18:05 +0000 (UTC) Subject: [commit: ghc] master: Fix bytecode generator panic (8de6e13) Message-ID: <20160720131805.DA8AC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8de6e13f9ef784750e502955fcb38d4a7e179727/ghc >--------------------------------------------------------------- commit 8de6e13f9ef784750e502955fcb38d4a7e179727 Author: Seraphime Kirkovski Date: Wed Jul 20 09:47:23 2016 +0200 Fix bytecode generator panic This fixes #12128. The bug was introduced in 1c9fd3f1c5522372fcaf250c805b959e8090a62c. Test Plan: ./validate Reviewers: simonmar, austin, hvr, simonpj, bgamari Reviewed By: bgamari Subscribers: simonpj, thomie Differential Revision: https://phabricator.haskell.org/D2374 GHC Trac Issues: #12128 >--------------------------------------------------------------- 8de6e13f9ef784750e502955fcb38d4a7e179727 compiler/ghci/ByteCodeGen.hs | 11 +++++++++++ testsuite/tests/ghci/should_run/T12128.hs | 14 ++++++++++++++ testsuite/tests/ghci/should_run/T12128.script | 1 + testsuite/tests/ghci/should_run/all.T | 1 + 4 files changed, 27 insertions(+) diff --git a/compiler/ghci/ByteCodeGen.hs b/compiler/ghci/ByteCodeGen.hs index 0d4c64b..8839ffa 100644 --- a/compiler/ghci/ByteCodeGen.hs +++ b/compiler/ghci/ByteCodeGen.hs @@ -1327,6 +1327,12 @@ pushAtom d p e pushAtom _ _ (AnnCoercion {}) -- Coercions are zero-width things, = return (nilOL, 0) -- treated just like a variable V +-- See Note [Empty case alternatives] in coreSyn/CoreSyn.hs +-- and Note [Bottoming expressions] in coreSyn/CoreUtils.hs: +-- The scrutinee of an empty case evaluates to bottom +pushAtom d p (AnnCase (_, a) _ _ []) -- trac #12128 + = pushAtom d p a + pushAtom d p (AnnVar v) | UnaryRep rep_ty <- repType (idType v) , V <- typeArgRep rep_ty @@ -1627,6 +1633,11 @@ atomPrimRep :: AnnExpr' Id ann -> PrimRep atomPrimRep e | Just e' <- bcView e = atomPrimRep e' atomPrimRep (AnnVar v) = bcIdPrimRep v atomPrimRep (AnnLit l) = typePrimRep (literalType l) + +-- Trac #12128: +-- A case expresssion can be an atom because empty cases evaluate to bottom. +-- See Note [Empty case alternatives] in coreSyn/CoreSyn.hs +atomPrimRep (AnnCase _ _ ty _) = ASSERT(typePrimRep ty == PtrRep) PtrRep atomPrimRep (AnnCoercion {}) = VoidRep atomPrimRep other = pprPanic "atomPrimRep" (ppr (deAnnotate' other)) diff --git a/testsuite/tests/ghci/should_run/T12128.hs b/testsuite/tests/ghci/should_run/T12128.hs new file mode 100644 index 0000000..0194910 --- /dev/null +++ b/testsuite/tests/ghci/should_run/T12128.hs @@ -0,0 +1,14 @@ +{- + This code produces an empty case statement, which + panics the bytecode generator after trac #11155. +-} + +module ShouldCompile where + +import GHC.TypeLits (Symbol) +import Unsafe.Coerce + +instance Read Symbol where + readsPrec = unsafeCoerce (readsPrec :: Int -> ReadS String) + +data Bar = TyCon !Symbol deriving (Read) diff --git a/testsuite/tests/ghci/should_run/T12128.script b/testsuite/tests/ghci/should_run/T12128.script new file mode 100644 index 0000000..8873ce2 --- /dev/null +++ b/testsuite/tests/ghci/should_run/T12128.script @@ -0,0 +1 @@ +:load T12128 diff --git a/testsuite/tests/ghci/should_run/all.T b/testsuite/tests/ghci/should_run/all.T index 08fe33d..f7e5018 100644 --- a/testsuite/tests/ghci/should_run/all.T +++ b/testsuite/tests/ghci/should_run/all.T @@ -24,3 +24,4 @@ test('T10145', just_ghci, ghci_script, ['T10145.script']) test('T7253', just_ghci, ghci_script, ['T7253.script']) test('T11328', just_ghci, ghci_script, ['T11328.script']) test('T11825', just_ghci, ghci_script, ['T11825.script']) +test('T12128', just_ghci, ghci_script, ['T12128.script']) From git at git.haskell.org Wed Jul 20 13:18:08 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 20 Jul 2016 13:18:08 +0000 (UTC) Subject: [commit: ghc] master: Cleanup PosixSource.h (cac3fb0) Message-ID: <20160720131808.843073A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/cac3fb06f4b282eee21159c364c4d08e8fdedce9/ghc >--------------------------------------------------------------- commit cac3fb06f4b282eee21159c364c4d08e8fdedce9 Author: Moritz Angermann Date: Wed Jul 20 09:53:45 2016 +0200 Cleanup PosixSource.h When trying to build arm64-apple-iso, the build fell over `strdup`, as the arm64-apple-ios build did not fall into `darwin_HOST_OS`, and would need `ios_HOST_OS`. This diff tries to clean up PosixSource.h, instead of layering another define on top. As we use `strnlen` in sources that include PosixSource.h, and `strnlen` is defined in POSIX.1-2008, the `_POSIX_C_SOURCE` and `_XOPEN_SOURCE` are increased accordingly. Furthermore the `_DARWIN_C_SOURCE` (required for `u_char`, etc. used in sysctl.h) define is moved into `OSThreads.h` alongside a similar ifdef for freebsd. Test Plan: Build on all supported platforms. Reviewers: rwbarton, erikd, austin, hvr, simonmar, bgamari Reviewed By: simonmar, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2375 >--------------------------------------------------------------- cac3fb06f4b282eee21159c364c4d08e8fdedce9 rts/PosixSource.h | 25 ++----------------------- rts/posix/OSThreads.c | 5 +++++ 2 files changed, 7 insertions(+), 23 deletions(-) diff --git a/rts/PosixSource.h b/rts/PosixSource.h index f4b880e..c4e328c 100644 --- a/rts/PosixSource.h +++ b/rts/PosixSource.h @@ -11,28 +11,7 @@ #include -/* We aim for C99 so we need to define following two defines in a consistent way - with what POSIX/XOPEN provide for C99. Some OSes are particularly picky about - the right versions defined here, e.g. Solaris - We also settle on lowest version of POSIX/XOPEN needed for proper C99 support - here which is POSIX.1-2001 compilation and Open Group Technical Standard, - Issue 6 (XPG6). XPG6 itself is a result of the merge of X/Open and POSIX - specification. It is also referred as IEEE Std. 1003.1-2001 or ISO/IEC - 9945:2002 or UNIX 03 and SUSv3. - Please also see trac ticket #11757 for more information about switch - to C99/C11. -*/ -#define _POSIX_C_SOURCE 200112L -#define _XOPEN_SOURCE 600 - -#define __USE_MINGW_ANSI_STDIO 1 - -#if defined(darwin_HOST_OS) -/* If we don't define this the including sysctl breaks with things like - /usr/include/bsm/audit.h:224:0: - error: syntax error before 'u_char' -*/ -#define _DARWIN_C_SOURCE 1 -#endif +#define _POSIX_C_SOURCE 200809L +#define _XOPEN_SOURCE 700 #endif /* POSIXSOURCE_H */ diff --git a/rts/posix/OSThreads.c b/rts/posix/OSThreads.c index 112a311..4010c5d 100644 --- a/rts/posix/OSThreads.c +++ b/rts/posix/OSThreads.c @@ -14,6 +14,11 @@ * because of some specific types, like u_char, u_int, etc. */ #define __BSD_VISIBLE 1 #endif +#if defined(darwin_HOST_OS) +/* Inclusion of system headers usually requires _DARWIN_C_SOURCE on Mac OS X + * because of some specific types like u_char, u_int, etc. */ +#define _DARWIN_C_SOURCE 1 +#endif #include "Rts.h" From git at git.haskell.org Wed Jul 20 13:18:11 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 20 Jul 2016 13:18:11 +0000 (UTC) Subject: [commit: ghc] master: TcInteract: Add braces to matchClassInst trace output (908f8e2) Message-ID: <20160720131811.2F0233A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/908f8e234fdbf951e763e0c47b018c6f74ae952c/ghc >--------------------------------------------------------------- commit 908f8e234fdbf951e763e0c47b018c6f74ae952c Author: Ben Gamari Date: Mon Jul 18 20:17:24 2016 +0200 TcInteract: Add braces to matchClassInst trace output This allows you to easily move to the result in a well-equipped editor. >--------------------------------------------------------------- 908f8e234fdbf951e763e0c47b018c6f74ae952c compiler/typecheck/TcInteract.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/typecheck/TcInteract.hs b/compiler/typecheck/TcInteract.hs index f659b22..298bbb2 100644 --- a/compiler/typecheck/TcInteract.hs +++ b/compiler/typecheck/TcInteract.hs @@ -1791,9 +1791,9 @@ matchClassInst dflags inerts clas tys loc pred = mkClassPred clas tys matchClassInst dflags _ clas tys loc - = do { traceTcS "matchClassInst" $ vcat [ text "pred =" <+> ppr (mkClassPred clas tys) ] + = do { traceTcS "matchClassInst" $ text "pred =" <+> ppr (mkClassPred clas tys) <+> char '{' ; res <- match_class_inst dflags clas tys loc - ; traceTcS "matchClassInst result" $ ppr res + ; traceTcS "} matchClassInst result" $ ppr res ; return res } match_class_inst :: DynFlags -> Class -> [Type] -> CtLoc -> TcS LookupInstResult From git at git.haskell.org Wed Jul 20 13:18:13 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 20 Jul 2016 13:18:13 +0000 (UTC) Subject: [commit: ghc] master: Update docs for partial type signatures (#12365) (627c767) Message-ID: <20160720131813.D23333A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/627c767b8e5587de52086d8891d7f7aabf6fa49f/ghc >--------------------------------------------------------------- commit 627c767b8e5587de52086d8891d7f7aabf6fa49f Author: Thomas Winant Date: Wed Jul 20 09:57:04 2016 +0200 Update docs for partial type signatures (#12365) * Update the sample error messages. The messages have been reworded and reformatted since GHC 7.10. * Mention `TypeApplications` in "Where can they occur?" * The name of a named wild card is no longer used in the name of a resulting type variable. Before: `_foo` => `w_foo`, now: `_foo` => `t` or `a`. Test Plan: generate the users guide Reviewers: goldfire, austin, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2413 GHC Trac Issues: #12365 >--------------------------------------------------------------- 627c767b8e5587de52086d8891d7f7aabf6fa49f docs/users_guide/glasgow_exts.rst | 79 ++++++++++++++++++++++++--------------- 1 file changed, 48 insertions(+), 31 deletions(-) diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst index 8a35899..56bf3f8 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -9522,22 +9522,25 @@ types like ``(Int -> Bool)`` or ``Maybe``. For instance, the first wildcard in the type signature ``not'`` would produce the following error message: -:: +.. code-block:: none + + Test.hs:4:17: error: + • Found type wildcard ‘_’ standing for ‘Bool’ + To use the inferred type, enable PartialTypeSignatures + • In the type signature: + not' :: Bool -> _ + • Relevant bindings include + not' :: Bool -> Bool (bound at Test.hs:5:1) - Test.hs:4:17: - Found hole ‘_’ with type: Bool - To use the inferred type, enable PartialTypeSignatures - In the type signature for ‘not'’: Bool -> _ When a wildcard is not instantiated to a monotype, it will be -generalised over, i.e. replaced by a fresh type variable (of which the -name will often start with ``w_``), e.g. +generalised over, i.e. replaced by a fresh type variable, e.g. :: foo :: _ -> _ foo x = x - -- Inferred: forall w_. w_ -> w_ + -- Inferred: forall t. t -> t filter' :: _ filter' = filter -- has type forall a. (a -> Bool) -> [a] -> [a] @@ -9571,7 +9574,7 @@ of the type signature to make sure that it unifies with something: :: somethingShowable :: Show _x => _x -> _ somethingShowable x = show x - -- Inferred type: Show w_x => w_x -> String + -- Inferred type: Show a => a -> String somethingShowable' :: Show _x => _x -> _ somethingShowable' x = show (not x) @@ -9586,7 +9589,7 @@ though syntactically similar, named wildcards can unify with monotypes as well as be generalised over (and behave as type variables). In the first example above, ``_x`` is generalised over (and is -effectively replaced by a fresh type variable ``w_x``). In the second +effectively replaced by a fresh type variable ``a``). In the second example, ``_x`` is unified with the ``Bool`` type, and as ``Bool`` implements the ``Show`` type class, the constraint ``Show Bool`` can be simplified away. @@ -9605,23 +9608,29 @@ no matching the actual type ``Bool``. .. code-block:: none - Test.hs:5:9: - Couldn't match expected type ‘_a’ with actual type ‘Bool’ + Test.hs:5:9: error: + • Couldn't match expected type ‘_a’ with actual type ‘Bool’ ‘_a’ is a rigid type variable bound by - the type signature for foo :: _a -> _a at Test.hs:4:8 - Relevant bindings include foo :: _a -> _a (bound at Test.hs:4:1) - In the expression: False - In an equation for ‘foo’: foo _ = False + the type signature for: + foo :: forall _a. _a -> _a + at Test.hs:4:8 + • In the expression: False + In an equation for ‘foo’: foo _ = False + • Relevant bindings include foo :: _a -> _a (bound at Test.hs:5:1) -Compiling this program with :ghc-flag:`-XNamedWildCards` enabled produces the -following error message reporting the inferred type of the named -wildcard ``_a``. +Compiling this program with :ghc-flag:`-XNamedWildCards` (as well as +:ghc-flag:`-XPartialTypeSignatures`) enabled produces the following error +message reporting the inferred type of the named wildcard ``_a``. .. code-block:: none - Test.hs:4:8: Warning: - Found hole ‘_a’ with type: Bool - In the type signature for ‘foo’: _a -> _a + Test.hs:4:8: warning: [-Wpartial-type-signatures] + • Found type wildcard ‘_a’ standing for ‘Bool’ + • In the type signature: + foo :: _a -> _a + • Relevant bindings include + foo :: Bool -> Bool (bound at Test.hs:5:1) + .. _extra-constraints-wildcard: @@ -9641,10 +9650,11 @@ extra-constraints wildcard is used to infer three extra constraints. -- Inferred: -- forall a. (Enum a, Eq a, Show a) => a -> String -- Error: - Test.hs:5:12: - Found hole ‘_’ with inferred constraints: (Enum a, Eq a, Show a) + Test.hs:5:12: error: + Found constraint wildcard ‘_’ standing for ‘(Show a, Eq a, Enum a)’ To use the inferred type, enable PartialTypeSignatures - In the type signature for ‘arbitCs’: _ => a -> String + In the type signature: + arbitCs :: _ => a -> String An extra-constraints wildcard shouldn't prevent the programmer from already listing the constraints he knows or wants to annotate, e.g. @@ -9657,10 +9667,11 @@ already listing the constraints he knows or wants to annotate, e.g. -- Inferred: -- forall a. (Enum a, Show a, Eq a) => a -> String -- Error: - Test.hs:9:22: - Found hole ‘_’ with inferred constraints: (Eq a, Show a) + Test.hs:9:22: error: + Found constraint wildcard ‘_’ standing for ‘()’ To use the inferred type, enable PartialTypeSignatures - In the type signature for ‘arbitCs'’: (Enum a, _) => a -> String + In the type signature: + arbitCs' :: (Enum a, _) => a -> String An extra-constraints wildcard can also lead to zero extra constraints to be inferred, e.g. @@ -9671,10 +9682,11 @@ be inferred, e.g. noCs = "noCs" -- Inferred: String -- Error: - Test.hs:13:9: - Found hole ‘_’ with inferred constraints: () + Test.hs:13:9: error: + Found constraint wildcard ‘_’ standing for ‘()’ To use the inferred type, enable PartialTypeSignatures - In the type signature for ‘noCs’: _ => String + In the type signature: + noCs :: _ => String As a single extra-constraints wildcard is enough to infer any number of constraints, only one is allowed in a type signature and it should come @@ -9702,6 +9714,11 @@ Anonymous and named wildcards *can* occur on the left hand side of a type or data instance declaration; see :ref:`type-wildcards-lhs`. +Anonymous wildcards are also allowed in visible type applications +(:ref:`visible-type-application`). If you want to specify only the second type +argument to ``wurble``, then you can say ``wurble @_ @Int`` where the first +argument is a wildcard. + In all other contexts, type wildcards are disallowed, and a named wildcard is treated as an ordinary type variable. For example: :: From git at git.haskell.org Wed Jul 20 13:18:16 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 20 Jul 2016 13:18:16 +0000 (UTC) Subject: [commit: ghc] master: Data.Either: Add fromLeft and fromRight (#12402) (a0f83a6) Message-ID: <20160720131816.7ED8E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a0f83a628cc6a00f948662f88e711c2a37bfda60/ghc >--------------------------------------------------------------- commit a0f83a628cc6a00f948662f88e711c2a37bfda60 Author: Dylan Meysmans Date: Wed Jul 20 09:54:55 2016 +0200 Data.Either: Add fromLeft and fromRight (#12402) Reviewers: austin, hvr, RyanGlScott, bgamari Reviewed By: RyanGlScott, bgamari Subscribers: RyanGlScott, thomie Differential Revision: https://phabricator.haskell.org/D2403 GHC Trac Issues: #12402 >--------------------------------------------------------------- a0f83a628cc6a00f948662f88e711c2a37bfda60 docs/users_guide/8.2.1-notes.rst | 2 ++ libraries/base/Data/Either.hs | 36 ++++++++++++++++++++++++++++++++++++ libraries/base/changelog.md | 2 ++ 3 files changed, 40 insertions(+) diff --git a/docs/users_guide/8.2.1-notes.rst b/docs/users_guide/8.2.1-notes.rst index 5f45bf1..27b49ef 100644 --- a/docs/users_guide/8.2.1-notes.rst +++ b/docs/users_guide/8.2.1-notes.rst @@ -98,6 +98,8 @@ See ``changelog.md`` in the ``base`` package for full release notes. - Version number 4.10.0.0 (was 4.9.0.0) +- ``Data.Either`` now provides ``fromLeft`` and ``fromRight`` + binary ~~~~~~ diff --git a/libraries/base/Data/Either.hs b/libraries/base/Data/Either.hs index 8bef30b..437d87c 100644 --- a/libraries/base/Data/Either.hs +++ b/libraries/base/Data/Either.hs @@ -24,6 +24,8 @@ module Data.Either ( rights, isLeft, isRight, + fromLeft, + fromRight, partitionEithers, ) where @@ -280,6 +282,40 @@ isRight :: Either a b -> Bool isRight (Left _) = False isRight (Right _) = True +-- | Return the contents of a 'Left'-value or a default value otherwise. +-- +-- @since 4.10.0.0 +-- +-- ==== __Examples__ +-- +-- Basic usage: +-- +-- >>> fromLeft 1 (Left 3) +-- 3 +-- >>> fromLeft 1 (Right "foo") +-- 1 +-- +fromLeft :: a -> Either a b -> a +fromLeft _ (Left a) = a +fromLeft a _ = a + +-- | Return the contents of a 'Right'-value or a default value otherwise. +-- +-- @since 4.10.0.0 +-- +-- ==== __Examples__ +-- +-- Basic usage: +-- +-- >>> fromRight 1 (Right 3) +-- 3 +-- >>> fromRight 1 (Left "foo") +-- 1 +-- +fromRight :: b -> Either a b -> b +fromRight _ (Right b) = b +fromRight b _ = b + -- instance for the == Boolean type-level equality operator type family EqEither a b where EqEither ('Left x) ('Left y) = x == y diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md index ecf6a82..996456f 100644 --- a/libraries/base/changelog.md +++ b/libraries/base/changelog.md @@ -14,6 +14,8 @@ * `New modules `Data.Bifoldable` and `Data.Bitraversable` (previously defined in the `bifunctors` package) (#10448) + * `Data.Either` now provides `fromLeft` and `fromRight` (#12402) + ## 4.9.0.0 *May 2016* * Bundled with GHC 8.0 From git at git.haskell.org Wed Jul 20 15:16:22 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 20 Jul 2016 15:16:22 +0000 (UTC) Subject: [commit: ghc] master: InstEnv: Ensure that instance visibility check is lazy (ed48098) Message-ID: <20160720151622.67FEE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ed4809813fa51524ae73a4475afe33018a67f87d/ghc >--------------------------------------------------------------- commit ed4809813fa51524ae73a4475afe33018a67f87d Author: Ben Gamari Date: Wed Jul 20 09:56:03 2016 +0200 InstEnv: Ensure that instance visibility check is lazy Previously instIsVisible had completely broken the laziness of lookupInstEnv' since it would examine is_dfun_name to check the name of the defining module (to know whether it is an interactive module). This resulted in the visibility check drawing in an interface file unnecessarily. This contributed to the unnecessary regression in compiler allocations reported in #12367. Test Plan: Validate, check nofib changes Reviewers: simonpj, ezyang, austin Reviewed By: ezyang Subscribers: thomie, ezyang Differential Revision: https://phabricator.haskell.org/D2411 GHC Trac Issues: #12367 >--------------------------------------------------------------- ed4809813fa51524ae73a4475afe33018a67f87d compiler/iface/TcIface.hs | 8 +- compiler/types/InstEnv.hs | 97 +++++++++++++++------- .../tests/ghci.debugger/scripts/break006.stderr | 14 ++-- testsuite/tests/perf/space_leaks/all.T | 3 +- testsuite/tests/typecheck/should_fail/T5095.stderr | 8 +- 5 files changed, 83 insertions(+), 47 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc ed4809813fa51524ae73a4475afe33018a67f87d From git at git.haskell.org Wed Jul 20 15:16:25 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 20 Jul 2016 15:16:25 +0000 (UTC) Subject: [commit: ghc] master: Clean up interaction between name cache and built-in syntax (9513fe6) Message-ID: <20160720151625.1F92E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9513fe6bdeafd35ca1a04e17b5f94732516766aa/ghc >--------------------------------------------------------------- commit 9513fe6bdeafd35ca1a04e17b5f94732516766aa Author: Ben Gamari Date: Wed Jul 20 12:34:54 2016 +0200 Clean up interaction between name cache and built-in syntax This cleans up various aspects of the handling of built-in syntax in the original name cache (hopefully resulting in a nice reduction in compiler allocations), * Remove tuple types from original name cache: There is really no reason for these to be in the name cache since we already handle them specially in interface files to ensure that we can resolve them directly to Names, avoiding extraneous name cache lookups. * Sadly it's not possible to remove all traces of tuples from the name cache, however. Namely we need to keep the tuple type representations in since otherwise they would need to be wired-in * Remove the special cases for (:), [], and (##) in isBuiltInOcc_maybe and rename it to isTupleOcc_maybe * Split lookupOrigNameCache into two variants, * lookupOrigNameCache': Merely looks up an OccName in the original name cache, making no attempt to resolve tuples * lookupOrigNameCache: Like the above but handles tuples as well. This is given the un-primed name since it does the "obvious" thing from the perspective of an API user, who knows nothing of our special treatment of tuples. Arriving at this design took a significant amount of iteration. The trail of debris leading here can be found in #11357. Thanks to ezyang and Simon for all of their help in coming to this solution. Test Plan: Validate Reviewers: goldfire, simonpj, austin Reviewed By: simonpj Subscribers: thomie, ezyang Differential Revision: https://phabricator.haskell.org/D2414 GHC Trac Issues: #11357 >--------------------------------------------------------------- 9513fe6bdeafd35ca1a04e17b5f94732516766aa compiler/iface/BinIface.hs | 5 ++- compiler/iface/IfaceEnv.hs | 40 +++++++++++++++------- compiler/prelude/PrelInfo.hs | 14 +++++++- compiler/prelude/PrelNames.hs | 3 +- compiler/prelude/TysWiredIn.hs | 74 +++++++++++++++++++++++----------------- compiler/typecheck/TcTypeable.hs | 19 +++++++++++ 6 files changed, 109 insertions(+), 46 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 9513fe6bdeafd35ca1a04e17b5f94732516766aa From git at git.haskell.org Wed Jul 20 15:28:51 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 20 Jul 2016 15:28:51 +0000 (UTC) Subject: [commit: ghc] master: testsuite: Add regression test for #12381 (a4f2b76) Message-ID: <20160720152851.883AB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a4f2b76661fa2056172b27b9883df1f488b7a0dc/ghc >--------------------------------------------------------------- commit a4f2b76661fa2056172b27b9883df1f488b7a0dc Author: Ben Gamari Date: Wed Jul 20 17:21:35 2016 +0200 testsuite: Add regression test for #12381 Test Plan: Validate Reviewers: austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2408 GHC Trac Issues: #12381, #11348 >--------------------------------------------------------------- a4f2b76661fa2056172b27b9883df1f488b7a0dc testsuite/tests/typecheck/should_compile/T12381.hs | 10 ++++++++++ testsuite/tests/typecheck/should_compile/all.T | 1 + 2 files changed, 11 insertions(+) diff --git a/testsuite/tests/typecheck/should_compile/T12381.hs b/testsuite/tests/typecheck/should_compile/T12381.hs new file mode 100644 index 0000000..9d4d731 --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T12381.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE TypeInType, TypeFamilies #-} +module Kinds where + +import GHC.Types + +type family G (a :: Type) :: Type +type instance G Int = Bool + +type family F (a :: Type) :: G a +type instance F Int = True diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index 7333ffb..995fa2a 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -531,3 +531,4 @@ test('T12067', extra_clean(['T12067a.hi', 'T12067a.o']), multimod_compile, ['T12067', '-v0']) test('T12185', normal, compile, ['']) test('T12133', normal, compile, ['']) +test('T12381', normal, compile, ['']) From git at git.haskell.org Wed Jul 20 15:28:54 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 20 Jul 2016 15:28:54 +0000 (UTC) Subject: [commit: ghc] master: Add another testcase for #12082 (93acc02) Message-ID: <20160720152854.AFB063A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/93acc02f7db7eb86967b4ec586359f408d62f75d/ghc >--------------------------------------------------------------- commit 93acc02f7db7eb86967b4ec586359f408d62f75d Author: Ben Gamari Date: Wed Jul 20 17:25:37 2016 +0200 Add another testcase for #12082 Test Plan: Validate, should pass. Reviewers: austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2399 GHC Trac Issues: #12082 >--------------------------------------------------------------- 93acc02f7db7eb86967b4ec586359f408d62f75d testsuite/tests/driver/all.T | 3 +-- testsuite/tests/typecheck/should_compile/T12082.hs | 9 +++++++++ testsuite/tests/typecheck/should_compile/all.T | 1 + 3 files changed, 11 insertions(+), 2 deletions(-) diff --git a/testsuite/tests/driver/all.T b/testsuite/tests/driver/all.T index ee59bef..ebd1b5a 100644 --- a/testsuite/tests/driver/all.T +++ b/testsuite/tests/driver/all.T @@ -491,5 +491,4 @@ test('T12135', run_command, ['$MAKE -s --no-print-directory T12135']) -test('T12192', normal, run_command, - ['mkdir foo && (cd foo && {compiler} -v0 ../T12192)']) +test('T12192', normal, run_command, ['mkdir foo && (cd foo && {compiler} -v0 ../T12192)']) \ No newline at end of file diff --git a/testsuite/tests/typecheck/should_compile/T12082.hs b/testsuite/tests/typecheck/should_compile/T12082.hs new file mode 100644 index 0000000..7aa4196 --- /dev/null +++ b/testsuite/tests/typecheck/should_compile/T12082.hs @@ -0,0 +1,9 @@ +{-# LANGUAGE RankNTypes #-} + +module T12082 where + +import Data.Typeable (Typeable) +import Control.Monad.ST (RealWorld) + +f :: forall a. (forall b. Typeable b => b -> a) -> a +f = undefined :: (RealWorld -> a) -> a diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T index 995fa2a..f107ba1 100644 --- a/testsuite/tests/typecheck/should_compile/all.T +++ b/testsuite/tests/typecheck/should_compile/all.T @@ -532,3 +532,4 @@ test('T12067', extra_clean(['T12067a.hi', 'T12067a.o']), test('T12185', normal, compile, ['']) test('T12133', normal, compile, ['']) test('T12381', normal, compile, ['']) +test('T12082', normal, compile, ['']) From git at git.haskell.org Wed Jul 20 15:35:38 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 20 Jul 2016 15:35:38 +0000 (UTC) Subject: [commit: ghc] master: Compact Regions (cf989ff) Message-ID: <20160720153538.CD5283A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/cf989ffe490c146be4ed0fd7e0c00d3ff8fe1453/ghc >--------------------------------------------------------------- commit cf989ffe490c146be4ed0fd7e0c00d3ff8fe1453 Author: Giovanni Campagna Date: Fri Jul 15 19:47:26 2016 +0100 Compact Regions This brings in initial support for compact regions, as described in the ICFP 2015 paper "Efficient Communication and Collection with Compact Normal Forms" (Edward Z. Yang et.al.) and implemented by Giovanni Campagna. Some things may change before the 8.2 release, but I (Simon M.) wanted to get the main patch committed so that we can iterate. What documentation there is is in the Data.Compact module in the new compact package. We'll need to extend and polish the documentation before the release. Test Plan: validate (new test cases included) Reviewers: ezyang, simonmar, hvr, bgamari, austin Subscribers: vikraman, Yuras, RyanGlScott, qnikst, mboes, facundominguez, rrnewton, thomie, erikd Differential Revision: https://phabricator.haskell.org/D1264 GHC Trac Issues: #11493 >--------------------------------------------------------------- cf989ffe490c146be4ed0fd7e0c00d3ff8fe1453 compiler/codeGen/StgCmmPrim.hs | 5 +- compiler/prelude/PrelNames.hs | 4 +- compiler/prelude/TysPrim.hs | 19 +- compiler/prelude/primops.txt.pp | 101 ++ ghc.mk | 1 + includes/rts/storage/Block.h | 4 + includes/rts/storage/ClosureMacros.h | 10 + includes/rts/storage/ClosureTypes.h | 3 +- includes/rts/storage/Closures.h | 46 + includes/rts/storage/GC.h | 19 + includes/stg/MiscClosures.h | 12 + libraries/compact/.gitignore | 4 + libraries/compact/Data/Compact.hs | 89 ++ libraries/compact/Data/Compact/Internal.hs | 78 ++ libraries/compact/Data/Compact/Serialized.hs | 225 ++++ libraries/compact/LICENSE | 41 + libraries/compact/README.md | 5 + libraries/{integer-simple => compact}/Setup.hs | 0 libraries/compact/compact.cabal | 47 + libraries/compact/tests/.gitignore | 21 + libraries/{base => compact}/tests/Makefile | 0 libraries/compact/tests/all.T | 6 + libraries/compact/tests/compact_append.hs | 38 + libraries/compact/tests/compact_autoexpand.hs | 27 + libraries/compact/tests/compact_loop.hs | 47 + libraries/compact/tests/compact_serialize.hs | 53 + libraries/compact/tests/compact_serialize.stderr | 1 + libraries/compact/tests/compact_simple.hs | 35 + libraries/compact/tests/compact_simple_array.hs | 60 + rts/ClosureFlags.c | 5 +- rts/LdvProfile.c | 1 + rts/PrimOps.cmm | 131 +++ rts/Printer.c | 9 +- rts/ProfHeap.c | 23 + rts/RetainerProfile.c | 1 + rts/RtsStartup.c | 1 + rts/RtsSymbols.c | 9 + rts/StgMiscClosures.cmm | 12 + rts/sm/BlockAlloc.c | 1 + rts/sm/CNF.c | 1352 ++++++++++++++++++++++ rts/sm/CNF.h | 71 ++ rts/sm/Compact.c | 1 + rts/sm/Evac.c | 130 ++- rts/sm/GC.c | 40 +- rts/sm/Sanity.c | 49 +- rts/sm/Scav.c | 9 +- rts/sm/Storage.c | 12 +- utils/deriveConstants/Main.hs | 13 +- utils/genprimopcode/Main.hs | 1 + 49 files changed, 2852 insertions(+), 20 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc cf989ffe490c146be4ed0fd7e0c00d3ff8fe1453 From git at git.haskell.org Wed Jul 20 17:03:57 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 20 Jul 2016 17:03:57 +0000 (UTC) Subject: [commit: ghc] branch 'wip/iface-type-pretty' created Message-ID: <20160720170357.0F8293A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/iface-type-pretty Referencing: 48c63554896118310579e66ec9859c9c29c6efc4 From git at git.haskell.org Wed Jul 20 17:03:59 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 20 Jul 2016 17:03:59 +0000 (UTC) Subject: [commit: ghc] wip/iface-type-pretty: Kill Type pretty-printer (846eca4) Message-ID: <20160720170359.C215B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/iface-type-pretty Link : http://ghc.haskell.org/trac/ghc/changeset/846eca4c5ad558141722443fd50ca9959f71e9d6/ghc >--------------------------------------------------------------- commit 846eca4c5ad558141722443fd50ca9959f71e9d6 Author: Ben Gamari Date: Wed Mar 2 12:43:47 2016 +0100 Kill Type pretty-printer Here we consolidate the pretty-printing logic for types in IfaceType. We need IfaceType regardless and the printer for Type can be implemented in terms of that for IfaceType. See #11660. >--------------------------------------------------------------- 846eca4c5ad558141722443fd50ca9959f71e9d6 compiler/iface/IfaceType.hs | 77 ++++++--- compiler/types/TyCoRep.hs | 399 +++----------------------------------------- 2 files changed, 78 insertions(+), 398 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 846eca4c5ad558141722443fd50ca9959f71e9d6 From git at git.haskell.org Wed Jul 20 17:04:02 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 20 Jul 2016 17:04:02 +0000 (UTC) Subject: [commit: ghc] wip/iface-type-pretty: Progress (48c6355) Message-ID: <20160720170402.BCBCE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/iface-type-pretty Link : http://ghc.haskell.org/trac/ghc/changeset/48c63554896118310579e66ec9859c9c29c6efc4/ghc >--------------------------------------------------------------- commit 48c63554896118310579e66ec9859c9c29c6efc4 Author: Ben Gamari Date: Tue May 17 23:21:10 2016 +0200 Progress >--------------------------------------------------------------- 48c63554896118310579e66ec9859c9c29c6efc4 compiler/iface/IfaceType.hs | 2 +- compiler/iface/IfaceType.hs-boot | 28 ++++++++++++++++++++++++++++ compiler/types/TyCoRep.hs | 1 + compiler/types/TyCoRep.hs-boot | 1 + 4 files changed, 31 insertions(+), 1 deletion(-) diff --git a/compiler/iface/IfaceType.hs b/compiler/iface/IfaceType.hs index 5627d91..0ea7a48 100644 --- a/compiler/iface/IfaceType.hs +++ b/compiler/iface/IfaceType.hs @@ -63,7 +63,7 @@ import Coercion import DataCon ( isTupleDataCon ) import TcType import DynFlags -import TyCoRep -- needs to convert core types to iface types +import {-# SOURCE #-}TyCoRep -- needs to convert core types to iface types import TyCon hiding ( pprPromotionQuote ) import CoAxiom import Id diff --git a/compiler/iface/IfaceType.hs-boot b/compiler/iface/IfaceType.hs-boot new file mode 100644 index 0000000..12859f6 --- /dev/null +++ b/compiler/iface/IfaceType.hs-boot @@ -0,0 +1,28 @@ +-- Exists to allow TyCoRep to import pretty-printers +module IfaceType where + +import Var (TyVar) +import {-# SOURCE #-} TyCoRep (Type, TyLit, TyBinder) +import Outputable + +data IfaceType +data IfaceTyLit +data IfaceForAllBndr +data IfaceTyConBinder +data IfaceTvBndr + +pprIfaceType, pprParendIfaceType :: IfaceType -> SDoc +pprIfaceSigmaType :: IfaceType -> SDoc +pprIfaceTyLit :: IfaceTyLit -> SDoc +pprIfaceForAll :: [IfaceForAllBndr] -> SDoc +pprIfaceTvBndr :: Bool -> IfaceTvBndr -> SDoc +pprUserIfaceForAll :: [IfaceForAllBndr] -> SDoc +pprIfaceContext :: Outputable a => [a] -> SDoc +pprIfaceContextArr :: Outputable a => [a] -> SDoc + +toIfaceType :: Type -> IfaceType +toIfaceTyLit :: TyLit -> IfaceTyLit + +zipIfaceBinders :: [TyVar] -> [TyBinder] -> [IfaceTyConBinder] + +toDegenerateBinders :: [TyBinder] -> [IfaceTyConBinder] diff --git a/compiler/types/TyCoRep.hs b/compiler/types/TyCoRep.hs index ac568cf..766bf8d 100644 --- a/compiler/types/TyCoRep.hs +++ b/compiler/types/TyCoRep.hs @@ -137,6 +137,7 @@ import {-# SOURCE #-} Type( isPredTy, isCoercionTy, mkAppTy import {-# SOURCE #-} Coercion import {-# SOURCE #-} ConLike ( ConLike(..), conLikeName ) import {-# SOURCE #-} TysWiredIn ( ptrRepLiftedTy ) +import {-# SOURCE #-} IfaceType -- friends: import Var diff --git a/compiler/types/TyCoRep.hs-boot b/compiler/types/TyCoRep.hs-boot index 0bcd9b3..ef63d2a 100644 --- a/compiler/types/TyCoRep.hs-boot +++ b/compiler/types/TyCoRep.hs-boot @@ -10,6 +10,7 @@ data Coercion data LeftOrRight data UnivCoProvenance data TCvSubst +data TyLit mkForAllTys :: [TyBinder] -> Type -> Type From git at git.haskell.org Wed Jul 20 18:35:34 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 20 Jul 2016 18:35:34 +0000 (UTC) Subject: [commit: ghc] master: Revert "Clean up interaction between name cache and built-in syntax" (83e4f49) Message-ID: <20160720183534.8EF503A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/83e4f49577665278fe08fbaafe2239553f3c448e/ghc >--------------------------------------------------------------- commit 83e4f49577665278fe08fbaafe2239553f3c448e Author: Ben Gamari Date: Wed Jul 20 19:04:10 2016 +0200 Revert "Clean up interaction between name cache and built-in syntax" This reverts commit 9513fe6bdeafd35ca1a04e17b5f94732516766aa. Sadly this broke with -DDEBUG. >--------------------------------------------------------------- 83e4f49577665278fe08fbaafe2239553f3c448e compiler/iface/BinIface.hs | 5 +---- compiler/iface/IfaceEnv.hs | 40 ++++++++++++---------------------------- compiler/prelude/PrelInfo.hs | 14 +------------- compiler/prelude/PrelNames.hs | 3 +-- compiler/prelude/TysWiredIn.hs | 22 +++++----------------- compiler/typecheck/TcTypeable.hs | 19 ------------------- 6 files changed, 20 insertions(+), 83 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 83e4f49577665278fe08fbaafe2239553f3c448e From git at git.haskell.org Thu Jul 21 08:12:27 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 21 Jul 2016 08:12:27 +0000 (UTC) Subject: [commit: ghc] master: Implement unboxed sum primitive type (714bebf) Message-ID: <20160721081227.AF0C83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/714bebff44076061d0a719c4eda2cfd213b7ac3d/ghc >--------------------------------------------------------------- commit 714bebff44076061d0a719c4eda2cfd213b7ac3d Author: Ömer Sinan Ağacan Date: Thu Jul 21 08:07:41 2016 +0000 Implement unboxed sum primitive type Summary: This patch implements primitive unboxed sum types, as described in https://ghc.haskell.org/trac/ghc/wiki/UnpackedSumTypes. Main changes are: - Add new syntax for unboxed sums types, terms and patterns. Hidden behind `-XUnboxedSums`. - Add unlifted unboxed sum type constructors and data constructors, extend type and pattern checkers and desugarer. - Add new RuntimeRep for unboxed sums. - Extend unarise pass to translate unboxed sums to unboxed tuples right before code generation. - Add `StgRubbishArg` to `StgArg`, and a new type `CmmArg` for better code generation when sum values are involved. - Add user manual section for unboxed sums. Some other changes: - Generalize `UbxTupleRep` to `MultiRep` and `UbxTupAlt` to `MultiValAlt` to be able to use those with both sums and tuples. - Don't use `tyConPrimRep` in `isVoidTy`: `tyConPrimRep` is really wrong, given an `Any` `TyCon`, there's no way to tell what its kind is, but `kindPrimRep` and in turn `tyConPrimRep` returns `PtrRep`. - Fix some bugs on the way: #12375. Not included in this patch: - Update Haddock for new the new unboxed sum syntax. - `TemplateHaskell` support is left as future work. For reviewers: - Front-end code is mostly trivial and adapted from unboxed tuple code for type checking, pattern checking, renaming, desugaring etc. - Main translation routines are in `RepType` and `UnariseStg`. Documentation in `UnariseStg` should be enough for understanding what's going on. Credits: - Johan Tibell wrote the initial front-end and interface file extensions. - Simon Peyton Jones reviewed this patch many times, wrote some code, and helped with debugging. Reviewers: bgamari, alanz, goldfire, RyanGlScott, simonpj, austin, simonmar, hvr, erikd Reviewed By: simonpj Subscribers: Iceland_jack, ggreif, ezyang, RyanGlScott, goldfire, thomie, mpickering Differential Revision: https://phabricator.haskell.org/D2259 >--------------------------------------------------------------- 714bebff44076061d0a719c4eda2cfd213b7ac3d compiler/basicTypes/BasicTypes.hs | 28 +- compiler/basicTypes/DataCon.hs | 12 +- compiler/basicTypes/Id.hs | 7 +- compiler/basicTypes/IdInfo.hs | 2 +- compiler/basicTypes/Unique.hs | 9 + compiler/cmm/CLabel.hs | 4 +- compiler/cmm/CmmExpr.hs | 12 +- compiler/cmm/CmmLayoutStack.hs | 2 +- compiler/cmm/CmmLive.hs | 4 +- compiler/cmm/CmmParse.y | 8 +- compiler/cmm/CmmUtils.hs | 22 +- compiler/cmm/MkGraph.hs | 74 +- compiler/cmm/PprCmmExpr.hs | 9 + compiler/codeGen/StgCmm.hs | 8 +- compiler/codeGen/StgCmmBind.hs | 6 +- compiler/codeGen/StgCmmClosure.hs | 5 +- compiler/codeGen/StgCmmCon.hs | 10 +- compiler/codeGen/StgCmmEnv.hs | 37 +- compiler/codeGen/StgCmmExpr.hs | 30 +- compiler/codeGen/StgCmmForeign.hs | 7 +- compiler/codeGen/StgCmmHeap.hs | 20 +- compiler/codeGen/StgCmmLayout.hs | 28 +- compiler/codeGen/StgCmmMonad.hs | 19 +- compiler/codeGen/StgCmmPrim.hs | 25 +- compiler/codeGen/StgCmmUtils.hs | 35 +- compiler/coreSyn/CoreArity.hs | 3 + compiler/coreSyn/CoreLint.hs | 12 +- compiler/deSugar/Check.hs | 5 + compiler/deSugar/Coverage.hs | 3 + compiler/deSugar/DsArrows.hs | 1 + compiler/deSugar/DsExpr.hs | 7 + compiler/deSugar/DsForeign.hs | 1 + compiler/deSugar/Match.hs | 7 + compiler/ghc.cabal.in | 1 + compiler/ghc.mk | 1 + compiler/ghci/ByteCodeGen.hs | 148 ++-- compiler/ghci/ByteCodeItbls.hs | 4 +- compiler/ghci/RtClosureInspect.hs | 33 +- compiler/hsSyn/HsExpr.hs | 11 + compiler/hsSyn/HsPat.hs | 19 +- compiler/hsSyn/HsTypes.hs | 7 + compiler/hsSyn/HsUtils.hs | 1 + compiler/iface/BinIface.hs | 139 +++- compiler/iface/MkIface.hs | 1 + compiler/main/Constants.hs | 3 + compiler/main/DynFlags.hs | 1 + compiler/main/InteractiveEval.hs | 3 +- compiler/parser/Lexer.x | 11 +- compiler/parser/Parser.y | 41 +- compiler/parser/RdrHsSyn.hs | 29 +- compiler/prelude/PrelNames.hs | 9 +- compiler/prelude/PrimOp.hs | 5 +- compiler/prelude/TysWiredIn.hs | 121 ++- compiler/prelude/TysWiredIn.hs-boot | 2 + compiler/profiling/SCCfinal.hs | 8 +- compiler/rename/RnExpr.hs | 4 + compiler/rename/RnPat.hs | 5 + compiler/rename/RnTypes.hs | 8 + compiler/simplStg/RepType.hs | 369 +++++++++ compiler/simplStg/SimplStg.hs | 3 + compiler/simplStg/StgStats.hs | 2 +- compiler/simplStg/UnariseStg.hs | 850 ++++++++++++++++----- compiler/stgSyn/CoreToStg.hs | 28 +- compiler/stgSyn/StgLint.hs | 32 +- compiler/stgSyn/StgSyn.hs | 45 +- compiler/stranal/WwLib.hs | 1 + compiler/typecheck/TcExpr.hs | 9 + compiler/typecheck/TcHsSyn.hs | 23 +- compiler/typecheck/TcHsType.hs | 11 +- compiler/typecheck/TcPat.hs | 13 + compiler/typecheck/TcPatSyn.hs | 5 + compiler/typecheck/TcRnTypes.hs | 1 + compiler/typecheck/TcType.hs | 25 +- compiler/types/TyCoRep.hs | 13 +- compiler/types/TyCon.hs | 76 +- compiler/types/Type.hs | 136 +--- compiler/types/Type.hs-boot | 1 - compiler/utils/Outputable.hs | 8 + compiler/vectorise/Vectorise/Builtins/Base.hs | 2 +- compiler/vectorise/Vectorise/Type/TyConDecl.hs | 6 + docs/users_guide/glasgow_exts.rst | 77 ++ includes/stg/MiscClosures.h | 1 + .../ghc-boot-th/GHC/LanguageExtensions/Type.hs | 1 + libraries/ghc-prim/GHC/Types.hs | 1 + rts/StgMiscClosures.cmm | 3 + testsuite/tests/driver/T4437.hs | 3 +- testsuite/tests/unboxedsums/Makefile | 10 + testsuite/tests/unboxedsums/T12375.hs | 17 + testsuite/tests/unboxedsums/T12375.stdout | 1 + testsuite/tests/unboxedsums/all.T | 25 + testsuite/tests/unboxedsums/empty_sum.hs | 20 + testsuite/tests/unboxedsums/empty_sum.stdout | 3 + testsuite/tests/unboxedsums/ffi1.hs | 11 + testsuite/tests/unboxedsums/ffi1.stderr | 23 + testsuite/tests/unboxedsums/module/Lib.hs | 16 + testsuite/tests/unboxedsums/module/Main.hs | 11 + testsuite/tests/unboxedsums/module/Makefile | 16 + testsuite/tests/unboxedsums/module/all.T | 4 + testsuite/tests/unboxedsums/module/sum_mod.stdout | 3 + testsuite/tests/unboxedsums/sum_rr.hs | 8 + testsuite/tests/unboxedsums/sum_rr.stderr | 7 + testsuite/tests/unboxedsums/thunk.hs | 8 + testsuite/tests/unboxedsums/thunk.stdout | 1 + testsuite/tests/unboxedsums/unarise.hs | 17 + .../cgrun052.stdout => unboxedsums/unarise.stdout} | 0 testsuite/tests/unboxedsums/unboxedsums1.hs | 81 ++ testsuite/tests/unboxedsums/unboxedsums1.stdout | 14 + testsuite/tests/unboxedsums/unboxedsums10.hs | 15 + testsuite/tests/unboxedsums/unboxedsums10.stdout | 2 + testsuite/tests/unboxedsums/unboxedsums11.hs | 15 + testsuite/tests/unboxedsums/unboxedsums11.stdout | 2 + testsuite/tests/unboxedsums/unboxedsums2.hs | 34 + testsuite/tests/unboxedsums/unboxedsums2.stdin | 2 + testsuite/tests/unboxedsums/unboxedsums2.stdout | 4 + testsuite/tests/unboxedsums/unboxedsums3.hs | 33 + testsuite/tests/unboxedsums/unboxedsums3.stdout | 6 + testsuite/tests/unboxedsums/unboxedsums4.hs | 3 + testsuite/tests/unboxedsums/unboxedsums4.stderr | 2 + testsuite/tests/unboxedsums/unboxedsums5.hs | 12 + testsuite/tests/unboxedsums/unboxedsums6.hs | 35 + testsuite/tests/unboxedsums/unboxedsums6.stdout | 2 + testsuite/tests/unboxedsums/unboxedsums7.hs | 24 + testsuite/tests/unboxedsums/unboxedsums7.stdout | 1 + testsuite/tests/unboxedsums/unboxedsums8.hs | 37 + testsuite/tests/unboxedsums/unboxedsums8.stdout | 3 + testsuite/tests/unboxedsums/unboxedsums9.hs | 26 + testsuite/tests/unboxedsums/unboxedsums9.stdout | 4 + utils/mkUserGuidePart/Options/Language.hs | 6 + 128 files changed, 2685 insertions(+), 701 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 714bebff44076061d0a719c4eda2cfd213b7ac3d From git at git.haskell.org Thu Jul 21 08:54:26 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 21 Jul 2016 08:54:26 +0000 (UTC) Subject: [commit: ghc] master: Comments + tiny refactor of isNullarySrcDataCon (9c54185) Message-ID: <20160721085426.15CC83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9c54185b26922d88e516942aad946f05f707d7ce/ghc >--------------------------------------------------------------- commit 9c54185b26922d88e516942aad946f05f707d7ce Author: Simon Peyton Jones Date: Wed Jul 20 15:28:37 2016 +0100 Comments + tiny refactor of isNullarySrcDataCon >--------------------------------------------------------------- 9c54185b26922d88e516942aad946f05f707d7ce compiler/basicTypes/DataCon.hs | 18 ++++++++++++++---- 1 file changed, 14 insertions(+), 4 deletions(-) diff --git a/compiler/basicTypes/DataCon.hs b/compiler/basicTypes/DataCon.hs index 2ab29aa..7fcc5fb 100644 --- a/compiler/basicTypes/DataCon.hs +++ b/compiler/basicTypes/DataCon.hs @@ -382,10 +382,10 @@ data DataCon -- Constructor representation dcRep :: DataConRep, - -- Cached - -- dcRepArity == length dataConRepArgTys + -- Cached; see Note [DataCon arities] + -- INVARIANT: dcRepArity == length dataConRepArgTys + -- INVARIANT: dcSourceArity == length dcOrigArgTys dcRepArity :: Arity, - -- dcSourceArity == length dcOrigArgTys dcSourceArity :: Arity, -- Result type of constructor is T t1..tn @@ -427,6 +427,14 @@ Why do we need the TyVarBinders, rather than just the TyVars? So that we can construct the right type for the DataCon with its foralls attributed the correce visiblity. That in turn governs whether you can use visible type application at a call of the data constructor. + +Note [DataCon arities] +~~~~~~~~~~~~~~~~~~~~~~ +dcSourceArity does not take constraints into account, +but dcRepArity does. For example: + MkT :: Ord a => a -> T a + dcSourceArity = 1 + dcRepArity = 2 -} data DataConRep @@ -979,10 +987,12 @@ dataConRepArity :: DataCon -> Arity dataConRepArity (MkData { dcRepArity = arity }) = arity -- | Return whether there are any argument types for this 'DataCon's original source type +-- See Note [DataCon arities] isNullarySrcDataCon :: DataCon -> Bool -isNullarySrcDataCon dc = null (dcOrigArgTys dc) +isNullarySrcDataCon dc = dataConSourceArity dc == 0 -- | Return whether there are any argument types for this 'DataCon's runtime representation type +-- See Note [DataCon arities] isNullaryRepDataCon :: DataCon -> Bool isNullaryRepDataCon dc = dataConRepArity dc == 0 From git at git.haskell.org Thu Jul 21 08:54:28 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 21 Jul 2016 08:54:28 +0000 (UTC) Subject: [commit: ghc] master: Comments re ApThunks + small refactor in mkRhsClosure (8d4760f) Message-ID: <20160721085428.BC5B13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8d4760fb7b20682cb5e470b24801301cfbbdce3b/ghc >--------------------------------------------------------------- commit 8d4760fb7b20682cb5e470b24801301cfbbdce3b Author: Simon Peyton Jones Date: Wed Jul 20 15:29:44 2016 +0100 Comments re ApThunks + small refactor in mkRhsClosure >--------------------------------------------------------------- 8d4760fb7b20682cb5e470b24801301cfbbdce3b compiler/codeGen/StgCmmBind.hs | 36 +++++++++++++++++++++--------------- 1 file changed, 21 insertions(+), 15 deletions(-) diff --git a/compiler/codeGen/StgCmmBind.hs b/compiler/codeGen/StgCmmBind.hs index e8fd8f8..f8fdb89 100644 --- a/compiler/codeGen/StgCmmBind.hs +++ b/compiler/codeGen/StgCmmBind.hs @@ -299,24 +299,30 @@ mkRhsClosure dflags bndr _cc _bi [] -- No args; a thunk (StgApp fun_id args) - | args `lengthIs` (arity-1) - && all (isGcPtrRep . idPrimRep . unsafe_stripNV) fvs - && isUpdatable upd_flag - && arity <= mAX_SPEC_AP_SIZE dflags - && not (gopt Opt_SccProfilingOn dflags) - -- not when profiling: we don't want to - -- lose information about this particular - -- thunk (e.g. its type) (#949) - - -- Ha! an Ap thunk + -- We are looking for an "ApThunk"; see data con ApThunk in StgCmmClosure + -- of form (x1 x2 .... xn), where all the xi are locals (not top-level) + -- So the xi will all be free variables + | args `lengthIs` (n_fvs-1) -- This happens only if the fun_id and + -- args are all distinct local variables + -- The "-1" is for fun_id + -- Missed opportunity: (f x x) is not detected + , all (isGcPtrRep . idPrimRep . unsafe_stripNV) fvs + , isUpdatable upd_flag + , n_fvs <= mAX_SPEC_AP_SIZE dflags + , not (gopt Opt_SccProfilingOn dflags) + -- not when profiling: we don't want to + -- lose information about this particular + -- thunk (e.g. its type) (#949) + + -- Ha! an Ap thunk = cgRhsStdThunk bndr lf_info payload where - lf_info = mkApLFInfo bndr upd_flag arity - -- the payload has to be in the correct order, hence we can't - -- just use the fvs. - payload = StgVarArg fun_id : args - arity = length fvs + n_fvs = length fvs + lf_info = mkApLFInfo bndr upd_flag n_fvs + -- the payload has to be in the correct order, hence we can't + -- just use the fvs. + payload = StgVarArg fun_id : args ---------- Default case ------------------ mkRhsClosure dflags bndr cc _ fvs upd_flag args body From git at git.haskell.org Thu Jul 21 08:54:31 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 21 Jul 2016 08:54:31 +0000 (UTC) Subject: [commit: ghc] master: Comments only (a09c0e3) Message-ID: <20160721085431.6F40B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a09c0e3e68c96882a1fb392c9dbeea84056bf32f/ghc >--------------------------------------------------------------- commit a09c0e3e68c96882a1fb392c9dbeea84056bf32f Author: Simon Peyton Jones Date: Wed Jul 20 15:28:10 2016 +0100 Comments only >--------------------------------------------------------------- a09c0e3e68c96882a1fb392c9dbeea84056bf32f compiler/coreSyn/MkCore.hs | 4 +- compiler/prelude/TysPrim.hs | 127 ++++++++++++++++++++++++++++------------- compiler/prelude/TysWiredIn.hs | 28 ++++++--- 3 files changed, 109 insertions(+), 50 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc a09c0e3e68c96882a1fb392c9dbeea84056bf32f From git at git.haskell.org Thu Jul 21 12:27:29 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 21 Jul 2016 12:27:29 +0000 (UTC) Subject: [commit: ghc] master: Bump Haddock submodule (6a4dc89) Message-ID: <20160721122729.7DA283A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6a4dc891fa7a8024d8f9f03b98ad675ff5fcbd91/ghc >--------------------------------------------------------------- commit 6a4dc891fa7a8024d8f9f03b98ad675ff5fcbd91 Author: Ömer Sinan Ağacan Date: Thu Jul 21 12:26:44 2016 +0000 Bump Haddock submodule >--------------------------------------------------------------- 6a4dc891fa7a8024d8f9f03b98ad675ff5fcbd91 utils/haddock | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/utils/haddock b/utils/haddock index 008e61d..cdc81a1 160000 --- a/utils/haddock +++ b/utils/haddock @@ -1 +1 @@ -Subproject commit 008e61d0c4b10713751c2a1de4958acc75367396 +Subproject commit cdc81a1b73bd4d1b330a32870d4369e1a2af3610 From git at git.haskell.org Thu Jul 21 14:56:00 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 21 Jul 2016 14:56:00 +0000 (UTC) Subject: [commit: ghc] wip/12368: DmdAnal: Add a final, safe iteration (7b266c9) Message-ID: <20160721145600.5223B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/12368 Link : http://ghc.haskell.org/trac/ghc/changeset/7b266c9193760ae57b45de8c952da665948638b9/ghc >--------------------------------------------------------------- commit 7b266c9193760ae57b45de8c952da665948638b9 Author: Joachim Breitner Date: Thu Jul 7 11:23:48 2016 +0200 DmdAnal: Add a final, safe iteration this fixes #12368. It also refactors dmdFix a bit, removes some redundancies (such as passing around an strictness signature right next to an id, when that id is guaranteed to have been annotated with that strictness signature). Differential Revision: https://phabricator.haskell.org/D2392 >--------------------------------------------------------------- 7b266c9193760ae57b45de8c952da665948638b9 compiler/stranal/DmdAnal.hs | 169 +++++++++++++++++-------------- testsuite/tests/stranal/should_run/all.T | 2 +- 2 files changed, 92 insertions(+), 79 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 7b266c9193760ae57b45de8c952da665948638b9 From git at git.haskell.org Thu Jul 21 14:56:02 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 21 Jul 2016 14:56:02 +0000 (UTC) Subject: [commit: ghc] wip/12368's head updated: DmdAnal: Add a final, safe iteration (7b266c9) Message-ID: <20160721145602.E202D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/12368' now includes: 979baec --without-libcharset disables the use of libcharset bedd620 Style changes for UniqFM 6ed7c47 Document some codegen nondeterminism 9858552 Use deterministic maps for FamInstEnv 34085b5 Correct the message displayed for syntax error (#12146) 64bce8c Add Note [FamInstEnv determinism] 6e280c2 Utils: Fix `lengthIs` and `lengthExceeds` for negative args 0481324 Use UniqDFM for InstEnv b8cd94d GHC.Stack.CCS: Fix typo in Haddocks 91fd87e FastString: Reduce allocations of concatFS 15751f2 FastString: Add IsString instance c4a9dca FastString: Supply mconcat implementation fc53d36 OccName: Implement startsWithUnderscore in terms of headFS eb3d659 OccName: Avoid re-encoding derived OccNames 4f21a51 Kill eltsUFM in classifyTyCons 6c7c193 DsExpr: Remove usage of concatFS in fingerprintName 0177c85 Testsuite: expose TEST_CC (path to gcc) f53d761 TysWiredIn: Use UniqFM lookup for built-in OccNames 9a3df1f check-api-annotations utility loads by filename 17d0b84 Add -package-env to the flags reference 372dbc4 Pretty: delete really old changelog 45d8f4e Demand analyser: Implement LetUp rule (#12370) 18ac80f tidyType: Rename variables of nested forall at once cd0750e tidyOccNames: Rename variables fairly 37aeff6 Added type family dependency to Data.Type.Bool.Not b35e01c Bring comments in TcGenGenerics up to date a9bc547 Log heap profiler samples to event log ffe4660 IfaceEnv: Only check for built-in OccNames if mod is GHC.Types 24f5f36 Binary: Use ByteString's copy in getBS 0f0cdb6 Bugfix for bug 11632: `readLitChar` should consume null characters 1ba79fa CodeGen: Way to dump cmm only once (#11717) 89a8be7 Pretty: remove a harmful $! (#12227) 5df92f6 hp2ps: fix invalid PostScript for names with parentheses d213ab3 Fix misspellings of the word "instance" in comments 3fa3fe8 Make DeriveFunctor work with unboxed tuples 514c4a4 Fix Template Haskell reification of unboxed tuple types 1fc41d3 Make okConIdOcc recognize unboxed tuples 0df3f4c Fix PDF build for the User's Guide. 98b2c50 Support SCC pragmas in declaration context e46b768 Make Data.{Bifoldable,Bitraversable} -XSafe 908f8e2 TcInteract: Add braces to matchClassInst trace output 8de6e13 Fix bytecode generator panic cac3fb0 Cleanup PosixSource.h a0f83a6 Data.Either: Add fromLeft and fromRight (#12402) 627c767 Update docs for partial type signatures (#12365) ed48098 InstEnv: Ensure that instance visibility check is lazy 9513fe6 Clean up interaction between name cache and built-in syntax a4f2b76 testsuite: Add regression test for #12381 93acc02 Add another testcase for #12082 cf989ff Compact Regions 83e4f49 Revert "Clean up interaction between name cache and built-in syntax" 714bebf Implement unboxed sum primitive type a09c0e3 Comments only 9c54185 Comments + tiny refactor of isNullarySrcDataCon 8d4760f Comments re ApThunks + small refactor in mkRhsClosure 6a4dc89 Bump Haddock submodule 7b266c9 DmdAnal: Add a final, safe iteration From git at git.haskell.org Thu Jul 21 15:39:03 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 21 Jul 2016 15:39:03 +0000 (UTC) Subject: [commit: ghc] wip/12368: DmdAnal: Add a final, safe iteration (269bb42) Message-ID: <20160721153903.D872A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/12368 Link : http://ghc.haskell.org/trac/ghc/changeset/269bb421b64ff7e1c83d553d9337632482a13129/ghc >--------------------------------------------------------------- commit 269bb421b64ff7e1c83d553d9337632482a13129 Author: Joachim Breitner Date: Thu Jul 7 11:23:48 2016 +0200 DmdAnal: Add a final, safe iteration this fixes #12368. It also refactors dmdFix a bit, removes some redundancies (such as passing around an strictness signature right next to an id, when that id is guaranteed to have been annotated with that strictness signature). Differential Revision: https://phabricator.haskell.org/D2392 >--------------------------------------------------------------- 269bb421b64ff7e1c83d553d9337632482a13129 compiler/stranal/DmdAnal.hs | 169 +++++++++++++++++-------------- testsuite/tests/stranal/should_run/all.T | 2 +- 2 files changed, 92 insertions(+), 79 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 269bb421b64ff7e1c83d553d9337632482a13129 From git at git.haskell.org Thu Jul 21 15:45:32 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 21 Jul 2016 15:45:32 +0000 (UTC) Subject: [commit: ghc] wip/12368: DmdAnal: Testcase about splitFVs and dmdFix abortion (6d98600) Message-ID: <20160721154532.679CA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/12368 Link : http://ghc.haskell.org/trac/ghc/changeset/6d98600446d0a2e391ef93510df49fbba8cea84b/ghc >--------------------------------------------------------------- commit 6d98600446d0a2e391ef93510df49fbba8cea84b Author: Joachim Breitner Date: Thu Jul 21 17:44:25 2016 +0200 DmdAnal: Testcase about splitFVs and dmdFix abortion Any variable with useful information (strict or used-once) will not be included in lazy_fv (according to splitFVs). If we now also remove them from the strictness signatures, their uses are not recorded anywhere – and then probably considered absent. >--------------------------------------------------------------- 6d98600446d0a2e391ef93510df49fbba8cea84b testsuite/tests/stranal/should_run/T12368a.hs | 27 +++++++++++++++++++++++ testsuite/tests/stranal/should_run/T12368a.stderr | 3 +++ testsuite/tests/stranal/should_run/all.T | 1 + 3 files changed, 31 insertions(+) diff --git a/testsuite/tests/stranal/should_run/T12368a.hs b/testsuite/tests/stranal/should_run/T12368a.hs new file mode 100644 index 0000000..738e8ef --- /dev/null +++ b/testsuite/tests/stranal/should_run/T12368a.hs @@ -0,0 +1,27 @@ +-- Needs to be a product type +data Stream = S Int Stream + +-- a is wrongly recorded abstent if the non-lazy-fv from foo are thrown away. +bar :: Int -> Int -> Stream -> Int +bar a n s = foo n s + where + -- Non terminating local rec, strict in a + foo :: Int -> Stream -> Int + foo 0 (S n s) = a + foo i (S n s) = a `seq` n + foo (i-1) s +{-# NOINLINE bar #-} + + +baz :: Int -> Int -> Int +baz 0 not_absent = 0 +baz 1 not_absent = baz 2 not_absent +baz x not_absent = bar not_absent 1000 arg + where + arg = S 1 arg + +bamf x = baz x (error "This is good!") +{-# NOINLINE bamf #-} + + +main :: IO () +main = bamf 10 `seq` return () diff --git a/testsuite/tests/stranal/should_run/T12368a.stderr b/testsuite/tests/stranal/should_run/T12368a.stderr new file mode 100644 index 0000000..98246d3 --- /dev/null +++ b/testsuite/tests/stranal/should_run/T12368a.stderr @@ -0,0 +1,3 @@ +T12368a: This is good! +CallStack (from HasCallStack): + error, called at T12368a.hs:22:17 in main:Main diff --git a/testsuite/tests/stranal/should_run/all.T b/testsuite/tests/stranal/should_run/all.T index 5b976f1..fb678b4 100644 --- a/testsuite/tests/stranal/should_run/all.T +++ b/testsuite/tests/stranal/should_run/all.T @@ -13,3 +13,4 @@ test('T10218', normal, compile_and_run, ['']) test('T11076', normal, multimod_compile_and_run, ['T11076.hs', 'T11076_prim.cmm']) test('T11555a', normal, compile_and_run, ['']) test('T12368', exit_code(1), compile_and_run, ['']) +test('T12368a', [expect_broken(12368), exit_code(1)], compile_and_run, ['']) From git at git.haskell.org Thu Jul 21 20:00:17 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 21 Jul 2016 20:00:17 +0000 (UTC) Subject: [commit: ghc] master: Fix and document Unique generation for sum TyCon and DataCons (8265c78) Message-ID: <20160721200017.5C8533A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8265c783dc26cb72e74a8fe89101049bb94c6db5/ghc >--------------------------------------------------------------- commit 8265c783dc26cb72e74a8fe89101049bb94c6db5 Author: Ömer Sinan Ağacan Date: Thu Jul 21 19:59:05 2016 +0000 Fix and document Unique generation for sum TyCon and DataCons Test Plan: validate Reviewers: bgamari, austin Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2420 >--------------------------------------------------------------- 8265c783dc26cb72e74a8fe89101049bb94c6db5 compiler/basicTypes/Unique.hs | 28 ++++++++++++++++++---- compiler/prelude/TysWiredIn.hs | 19 +++++++++++---- testsuite/tests/unboxedsums/all.T | 5 ++++ .../tests/unboxedsums/unboxedsums_unit_tests.hs | 26 ++++++++++++++++++++ 4 files changed, 70 insertions(+), 8 deletions(-) diff --git a/compiler/basicTypes/Unique.hs b/compiler/basicTypes/Unique.hs index 800198b..545ea9f 100644 --- a/compiler/basicTypes/Unique.hs +++ b/compiler/basicTypes/Unique.hs @@ -329,11 +329,9 @@ mkAlphaTyVarUnique :: Int -> Unique mkPreludeClassUnique :: Int -> Unique mkPreludeTyConUnique :: Int -> Unique mkTupleTyConUnique :: Boxity -> Arity -> Unique -mkSumTyConUnique :: Arity -> Unique mkCTupleTyConUnique :: Arity -> Unique mkPreludeDataConUnique :: Arity -> Unique mkTupleDataConUnique :: Boxity -> Arity -> Unique -mkSumDataConUnique :: ConTagZ -> Arity -> Unique mkPrimOpIdUnique :: Int -> Unique mkPreludeMiscIdUnique :: Int -> Unique mkPArrDataConUnique :: Int -> Unique @@ -351,7 +349,6 @@ mkPreludeTyConUnique i = mkUnique '3' (2*i) mkTupleTyConUnique Boxed a = mkUnique '4' (2*a) mkTupleTyConUnique Unboxed a = mkUnique '5' (2*a) mkCTupleTyConUnique a = mkUnique 'k' (2*a) -mkSumTyConUnique a = mkUnique 'z' (2*a) tyConRepNameUnique :: Unique -> Unique tyConRepNameUnique u = incrUnique u @@ -372,12 +369,35 @@ tyConRepNameUnique u = incrUnique u mkPreludeDataConUnique i = mkUnique '6' (3*i) -- Must be alphabetic mkTupleDataConUnique Boxed a = mkUnique '7' (3*a) -- ditto (*may* be used in C labels) mkTupleDataConUnique Unboxed a = mkUnique '8' (3*a) + +-------------------------------------------------- +-- Sum arities start from 2. A sum of arity N has N data constructors, so it +-- occupies N+1 slots: 1 TyCon + N DataCons. +-- +-- So arity 2 sum takes uniques 0 (tycon), 1, 2 (2 data cons) +-- arity 3 sum takes uniques 3 (tycon), 4, 5, 6 (3 data cons) +-- etc. + +mkSumTyConUnique :: Arity -> Unique +mkSumTyConUnique arity = mkUnique 'z' (sumUniqsOccupied arity) + +mkSumDataConUnique :: ConTagZ -> Arity -> Unique mkSumDataConUnique alt arity | alt >= arity = panic ("mkSumDataConUnique: " ++ show alt ++ " >= " ++ show arity) | otherwise - = mkUnique 'z' (2 * alt * arity) + = mkUnique 'z' (sumUniqsOccupied arity + alt + 1 {- skip the tycon -}) + +-- How many unique slots occupied by sum types (including constructors) up to +-- the given arity? +sumUniqsOccupied :: Arity -> Int +sumUniqsOccupied arity + = ASSERT(arity >= 2) + -- 3 + 4 + ... + arity + ((arity * (arity + 1)) `div` 2) - 3 +{-# INLINE sumUniqsOccupied #-} +-------------------------------------------------- dataConRepNameUnique, dataConWorkerUnique :: Unique -> Unique dataConWorkerUnique u = incrUnique u dataConRepNameUnique u = stepUnique u 2 diff --git a/compiler/prelude/TysWiredIn.hs b/compiler/prelude/TysWiredIn.hs index 0775d06..1028478 100644 --- a/compiler/prelude/TysWiredIn.hs +++ b/compiler/prelude/TysWiredIn.hs @@ -861,8 +861,15 @@ mkSumDataConOcc alt n = mkOccName dataName str -- | Type constructor for n-ary unboxed sum. sumTyCon :: Arity -> TyCon -sumTyCon n | n > mAX_SUM_SIZE = fst (mk_sum n) -- Build one specially -sumTyCon n = fst (unboxedSumArr ! n) +sumTyCon arity + | arity > mAX_SUM_SIZE + = fst (mk_sum arity) -- Build one specially + + | arity < 2 + = panic ("sumTyCon: Arity starts from 2. (arity: " ++ show arity ++ ")") + + | otherwise + = fst (unboxedSumArr ! arity) -- | Data constructor for i-th alternative of a n-ary unboxed sum. sumDataCon :: ConTag -- Alternative @@ -870,13 +877,17 @@ sumDataCon :: ConTag -- Alternative -> DataCon sumDataCon alt arity | alt > arity - = panic ("sumDataCon: index out of bounds: alt " + = panic ("sumDataCon: index out of bounds: alt: " ++ show alt ++ " > arity " ++ show arity) | alt <= 0 = panic ("sumDataCon: Alts start from 1. (alt: " ++ show alt ++ ", arity: " ++ show arity ++ ")") + | arity < 2 + = panic ("sumDataCon: Arity starts from 2. (alt: " ++ show alt + ++ ", arity: " ++ show arity ++ ")") + | arity > mAX_SUM_SIZE = snd (mk_sum arity) ! (alt - 1) -- Build one specially @@ -887,7 +898,7 @@ sumDataCon alt arity -- indexed by the arity of the sum and the inner array is indexed by -- the alternative. unboxedSumArr :: Array Int (TyCon, Array Int DataCon) -unboxedSumArr = listArray (0,mAX_SUM_SIZE) [mk_sum i | i <- [0..mAX_SUM_SIZE]] +unboxedSumArr = listArray (2,mAX_SUM_SIZE) [mk_sum i | i <- [2..mAX_SUM_SIZE]] -- | Create type constructor and data constructors for n-ary unboxed sum. mk_sum :: Arity -> (TyCon, Array ConTagZ DataCon) diff --git a/testsuite/tests/unboxedsums/all.T b/testsuite/tests/unboxedsums/all.T index 274045f..0b948b1 100644 --- a/testsuite/tests/unboxedsums/all.T +++ b/testsuite/tests/unboxedsums/all.T @@ -1,3 +1,8 @@ +test('unboxedsums_unit_tests', + only_ways(['normal']), + compile_and_run, + ['-package ghc']) + test('unarise', omit_ways(['ghci']), compile_and_run, ['']) test('unboxedsums1', omit_ways(['ghci']), compile_and_run, ['']) test('unboxedsums2', omit_ways(['ghci']), compile_and_run, ['']) diff --git a/testsuite/tests/unboxedsums/unboxedsums_unit_tests.hs b/testsuite/tests/unboxedsums/unboxedsums_unit_tests.hs new file mode 100644 index 0000000..d7a8d33 --- /dev/null +++ b/testsuite/tests/unboxedsums/unboxedsums_unit_tests.hs @@ -0,0 +1,26 @@ +module Main where + +import TysWiredIn +import UniqSet +import Unique + +import System.IO +import Control.Monad + +main :: IO () +main = sequence_ + [ uniq_tests ] + + +uniq_tests :: IO () +uniq_tests = do + let tycons = map sumTyCon [2 .. 20] + datacons = [ sumDataCon alt arity | arity <- [ 2 .. 20 ] + , alt <- [ 1 .. arity ] ] + + us = mkUniqSet (map getUnique tycons) + `unionUniqSets` mkUniqSet (map getUnique datacons) + + when (sizeUniqSet us /= length tycons + length datacons) $ do + hPutStrLn stderr "Sum cons/tycons have same uniques." + hFlush stderr From git at git.haskell.org Thu Jul 21 22:13:10 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 21 Jul 2016 22:13:10 +0000 (UTC) Subject: [commit: ghc] master: Correct a few mistyped words in prose/comments (e710f8f) Message-ID: <20160721221310.3FEB53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e710f8f52a66d0666ed681049e17902b3d12bb39/ghc >--------------------------------------------------------------- commit e710f8f52a66d0666ed681049e17902b3d12bb39 Author: Gabor Greif Date: Fri Jul 22 00:10:32 2016 +0200 Correct a few mistyped words in prose/comments >--------------------------------------------------------------- e710f8f52a66d0666ed681049e17902b3d12bb39 compiler/prelude/primops.txt.pp | 2 +- docs/storage-mgt/ldv.tex | 2 +- testsuite/tests/typecheck/should_compile/T10195.hs | 4 ++-- testsuite/tests/typecheck/should_compile/T3108.hs | 2 +- 4 files changed, 5 insertions(+), 5 deletions(-) diff --git a/compiler/prelude/primops.txt.pp b/compiler/prelude/primops.txt.pp index 9fd5d17..c617e94 100644 --- a/compiler/prelude/primops.txt.pp +++ b/compiler/prelude/primops.txt.pp @@ -2513,7 +2513,7 @@ primop CompactFixupPointersOp "compactFixupPointers#" GenPrimOp ------------------------------------------------------------------------ section "Unsafe pointer equality" --- (#1 Bad Guy: Alistair Reid :) +-- (#1 Bad Guy: Alastair Reid :) ------------------------------------------------------------------------ primop ReallyUnsafePtrEqualityOp "reallyUnsafePtrEquality#" GenPrimOp diff --git a/docs/storage-mgt/ldv.tex b/docs/storage-mgt/ldv.tex index 79f0f23..897b621 100644 --- a/docs/storage-mgt/ldv.tex +++ b/docs/storage-mgt/ldv.tex @@ -619,7 +619,7 @@ two options should result in nearly same profiling outputs, but the second run (without @-Sstderr@ option) spends almost twice as long in the Haskell mutator as the first run: 1) @+RTS -Sstderr -hL -RTS@; 2) @+RTS -hL -RTS at . -This is quite a subtle bug because this wierd phenomenon is not +This is quite a subtle bug because this weird phenomenon is not observed in retainer profiling, yet the implementation of @mut_user_time_during_LDV()@ is completely analogous to that of @mut_user_time_during_RP()@. The overall shapes of the resultant graphs diff --git a/testsuite/tests/typecheck/should_compile/T10195.hs b/testsuite/tests/typecheck/should_compile/T10195.hs index b1e1809..d79929b 100644 --- a/testsuite/tests/typecheck/should_compile/T10195.hs +++ b/testsuite/tests/typecheck/should_compile/T10195.hs @@ -16,7 +16,7 @@ class Bar m m' instance (BarFamily m m' ~ 'True) => Bar m m' magic :: (Bar m m') => c m zp -> Foo m zp (c m' zq) --- Wierd test case: (Bar m m') is simplifiable +-- Weird test case: (Bar m m') is simplifiable magic = undefined getDict :: a -> Dict (Num a) @@ -26,7 +26,7 @@ fromScalar = undefined foo :: (Bar m m') => c m zp -> Foo m zp (c m' zq) -> Foo m zp (c m' zq) --- Wierd test case: (Bar m m') is simplifiable +-- Weird test case: (Bar m m') is simplifiable foo b (Foo sc) = let scinv = fromScalar sc in case getDict scinv of diff --git a/testsuite/tests/typecheck/should_compile/T3108.hs b/testsuite/tests/typecheck/should_compile/T3108.hs index be1dc54..3611bbc 100644 --- a/testsuite/tests/typecheck/should_compile/T3108.hs +++ b/testsuite/tests/typecheck/should_compile/T3108.hs @@ -29,7 +29,7 @@ class C1 x instance {-# OVERLAPPING #-} (C1 x, C1 y) => C1 (x,y) instance {-# OVERLAPPING #-} C1 Bool instance {-# OVERLAPPABLE #-} (C2 x y, C1 (y,Bool)) => C1 x --- Wierd test case: (C1 (y,Bool)) is simplifiable +-- Weird test case: (C1 (y,Bool)) is simplifiable class C2 x y | x -> y instance C2 Int Int From git at git.haskell.org Thu Jul 21 22:42:41 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 21 Jul 2016 22:42:41 +0000 (UTC) Subject: [commit: ghc] master: More typos in comments (bbf36f8) Message-ID: <20160721224241.BB0A43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/bbf36f89c7ddee9ec63b12fe735cc758de4e3da2/ghc >--------------------------------------------------------------- commit bbf36f89c7ddee9ec63b12fe735cc758de4e3da2 Author: Gabor Greif Date: Fri Jul 22 00:32:28 2016 +0200 More typos in comments >--------------------------------------------------------------- bbf36f89c7ddee9ec63b12fe735cc758de4e3da2 compiler/deSugar/Desugar.hs | 2 +- compiler/deSugar/DsGRHSs.hs | 2 +- compiler/prelude/primops.txt.pp | 2 +- compiler/simplCore/CallArity.hs | 2 +- compiler/specialise/Specialise.hs | 6 +++--- 5 files changed, 7 insertions(+), 7 deletions(-) diff --git a/compiler/deSugar/Desugar.hs b/compiler/deSugar/Desugar.hs index 7ce0c6d..6a6c012 100644 --- a/compiler/deSugar/Desugar.hs +++ b/compiler/deSugar/Desugar.hs @@ -672,7 +672,7 @@ We want the user to express a rule saying roughly “mapping a coercion over a list can be replaced by a coercion”. But the cast operator of Core (▷) cannot be written in Haskell. So we use `coerce` for that (#2110). The user writes map coerce = coerce -as a RULE, and this optimizes any kind of mapped' casts aways, including `map +as a RULE, and this optimizes any kind of mapped' casts away, including `map MkNewtype`. For that we replace any forall'ed `c :: Coercible a b` value in a RULE by diff --git a/compiler/deSugar/DsGRHSs.hs b/compiler/deSugar/DsGRHSs.hs index d08bd55..0c34bc2 100644 --- a/compiler/deSugar/DsGRHSs.hs +++ b/compiler/deSugar/DsGRHSs.hs @@ -133,7 +133,7 @@ isTrueLHsExpr :: LHsExpr Id -> Maybe (CoreExpr -> DsM CoreExpr) -- * 'otherwise' Id -- * Trivial wappings of these -- The arguments to Just are any HsTicks that we have found, --- because we still want to tick then, even it they are aways evaluted. +-- because we still want to tick then, even it they are always evaluated. isTrueLHsExpr (L _ (HsVar (L _ v))) | v `hasKey` otherwiseIdKey || v `hasKey` getUnique trueDataConId = Just return diff --git a/compiler/prelude/primops.txt.pp b/compiler/prelude/primops.txt.pp index c617e94..e948610 100644 --- a/compiler/prelude/primops.txt.pp +++ b/compiler/prelude/primops.txt.pp @@ -2527,7 +2527,7 @@ primop ParOp "par#" GenPrimOp a -> Int# with -- Note that Par is lazy to avoid that the sparked thing - -- gets evaluted strictly, which it should *not* be + -- gets evaluated strictly, which it should *not* be has_side_effects = True code_size = { primOpCodeSizeForeignCall } diff --git a/compiler/simplCore/CallArity.hs b/compiler/simplCore/CallArity.hs index fda28a8..0186c67 100644 --- a/compiler/simplCore/CallArity.hs +++ b/compiler/simplCore/CallArity.hs @@ -150,7 +150,7 @@ The interesting cases of the analysis: Only one can be execuded, so Return (alt₁ ∪ alt₂ ∪...) * App e₁ e₂ (and analogously Case scrut alts), with non-trivial e₂: - We get the results from both sides, with the argument evaluted at most once. + We get the results from both sides, with the argument evaluated at most once. Additionally, anything called by e₁ can possibly be called with anything from e₂. Return: C(e₁) ∪ C(e₂) ∪ (fv e₁) × (fv e₂) diff --git a/compiler/specialise/Specialise.hs b/compiler/specialise/Specialise.hs index 644ecc7..72118aa 100644 --- a/compiler/specialise/Specialise.hs +++ b/compiler/specialise/Specialise.hs @@ -2307,12 +2307,12 @@ is used: Now give it to the simplifier and the _Lifting will be optimised away. -The benfit is that we have given the specialised "unboxed" values a -very simplep lifted semantics and then leave it up to the simplifier to +The benefit is that we have given the specialised "unboxed" values a +very simple lifted semantics and then leave it up to the simplifier to optimise it --- knowing that the overheads will be removed in nearly all cases. -In particular, the value will only be evaluted in the branches of the +In particular, the value will only be evaluated in the branches of the program which use it, rather than being forced at the point where the value is bound. For example: From git at git.haskell.org Fri Jul 22 07:46:31 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 22 Jul 2016 07:46:31 +0000 (UTC) Subject: [commit: ghc] master: Revert "Cleanup PosixSource.h" (fb34b27) Message-ID: <20160722074631.D92ED3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/fb34b27c97515d06bcc00065b352704a5ea21557/ghc >--------------------------------------------------------------- commit fb34b27c97515d06bcc00065b352704a5ea21557 Author: Ben Gamari Date: Fri Jul 22 09:45:36 2016 +0200 Revert "Cleanup PosixSource.h" This reverts commit cac3fb06f4b282eee21159c364c4d08e8fdedce9. This breaks OS X and Windows. >--------------------------------------------------------------- fb34b27c97515d06bcc00065b352704a5ea21557 rts/PosixSource.h | 25 +++++++++++++++++++++++-- rts/posix/OSThreads.c | 5 ----- 2 files changed, 23 insertions(+), 7 deletions(-) diff --git a/rts/PosixSource.h b/rts/PosixSource.h index c4e328c..f4b880e 100644 --- a/rts/PosixSource.h +++ b/rts/PosixSource.h @@ -11,7 +11,28 @@ #include -#define _POSIX_C_SOURCE 200809L -#define _XOPEN_SOURCE 700 +/* We aim for C99 so we need to define following two defines in a consistent way + with what POSIX/XOPEN provide for C99. Some OSes are particularly picky about + the right versions defined here, e.g. Solaris + We also settle on lowest version of POSIX/XOPEN needed for proper C99 support + here which is POSIX.1-2001 compilation and Open Group Technical Standard, + Issue 6 (XPG6). XPG6 itself is a result of the merge of X/Open and POSIX + specification. It is also referred as IEEE Std. 1003.1-2001 or ISO/IEC + 9945:2002 or UNIX 03 and SUSv3. + Please also see trac ticket #11757 for more information about switch + to C99/C11. +*/ +#define _POSIX_C_SOURCE 200112L +#define _XOPEN_SOURCE 600 + +#define __USE_MINGW_ANSI_STDIO 1 + +#if defined(darwin_HOST_OS) +/* If we don't define this the including sysctl breaks with things like + /usr/include/bsm/audit.h:224:0: + error: syntax error before 'u_char' +*/ +#define _DARWIN_C_SOURCE 1 +#endif #endif /* POSIXSOURCE_H */ diff --git a/rts/posix/OSThreads.c b/rts/posix/OSThreads.c index 4010c5d..112a311 100644 --- a/rts/posix/OSThreads.c +++ b/rts/posix/OSThreads.c @@ -14,11 +14,6 @@ * because of some specific types, like u_char, u_int, etc. */ #define __BSD_VISIBLE 1 #endif -#if defined(darwin_HOST_OS) -/* Inclusion of system headers usually requires _DARWIN_C_SOURCE on Mac OS X - * because of some specific types like u_char, u_int, etc. */ -#define _DARWIN_C_SOURCE 1 -#endif #include "Rts.h" From git at git.haskell.org Fri Jul 22 08:38:40 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 22 Jul 2016 08:38:40 +0000 (UTC) Subject: [commit: ghc] master: Unboxed sums: More unit tests (86b1522) Message-ID: <20160722083840.2B9293A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/86b1522c85519b43ab5c1ce09b61bd8005edfd11/ghc >--------------------------------------------------------------- commit 86b1522c85519b43ab5c1ce09b61bd8005edfd11 Author: Ömer Sinan Ağacan Date: Fri Jul 22 08:37:56 2016 +0000 Unboxed sums: More unit tests >--------------------------------------------------------------- 86b1522c85519b43ab5c1ce09b61bd8005edfd11 testsuite/tests/unboxedsums/all.T | 2 +- .../tests/unboxedsums/unboxedsums_unit_tests.hs | 69 +++++++++++++++++++--- 2 files changed, 63 insertions(+), 8 deletions(-) diff --git a/testsuite/tests/unboxedsums/all.T b/testsuite/tests/unboxedsums/all.T index 0b948b1..806f415 100644 --- a/testsuite/tests/unboxedsums/all.T +++ b/testsuite/tests/unboxedsums/all.T @@ -1,5 +1,5 @@ test('unboxedsums_unit_tests', - only_ways(['normal']), + [ only_ways(['normal']), extra_run_opts('"' + config.libdir + '"') ], compile_and_run, ['-package ghc']) diff --git a/testsuite/tests/unboxedsums/unboxedsums_unit_tests.hs b/testsuite/tests/unboxedsums/unboxedsums_unit_tests.hs index d7a8d33..5c0b929 100644 --- a/testsuite/tests/unboxedsums/unboxedsums_unit_tests.hs +++ b/testsuite/tests/unboxedsums/unboxedsums_unit_tests.hs @@ -1,17 +1,32 @@ module Main where +import BasicTypes +import GHC +import GhcMonad +import Outputable +import RepType +import TysPrim import TysWiredIn import UniqSet import Unique -import System.IO +import qualified Control.Exception as E import Control.Monad +import System.Environment (getArgs) +import System.IO -main :: IO () -main = sequence_ - [ uniq_tests ] +assert :: Bool -> String -> SDoc -> IO () +assert False tn msg = pprPanic tn msg +assert True _ _ = return () +main :: IO () +main = do + [libdir] <- getArgs + runGhc (Just libdir) $ liftIO $ do + -- need to initialize the monad to initialize static flags etc. + sequence_ [ uniq_tests, layout_tests ] +-- Make sure sum datacon/tycon uniques are really uniq uniq_tests :: IO () uniq_tests = do let tycons = map sumTyCon [2 .. 20] @@ -21,6 +36,46 @@ uniq_tests = do us = mkUniqSet (map getUnique tycons) `unionUniqSets` mkUniqSet (map getUnique datacons) - when (sizeUniqSet us /= length tycons + length datacons) $ do - hPutStrLn stderr "Sum cons/tycons have same uniques." - hFlush stderr + assert (sizeUniqSet us == length tycons + length datacons) + "uniq_tests" + (text "Sum cons/tycons have same uniques.") + +layout_tests :: IO () +layout_tests = sequence_ + [ layout1, layout2, layout3, enum_layout ] + where + assert_layout tn tys layout = + let + layout_ret = ubxSumRepType tys + in + assert (layout_ret == layout) + tn + (text "Unexpected sum layout." $$ + text "Alts: " <+> ppr tys $$ + text "Expected layout:" <+> ppr layout $$ + text "Actual layout: " <+> ppr layout_ret) + + ubxtup = mkTupleTy Unboxed + + layout1 = + assert_layout "layout1" + [ ubxtup [ intTy, intPrimTy ] + , ubxtup [ intPrimTy, intTy ] ] + [ WordSlot, PtrSlot, WordSlot ] + + layout2 = + assert_layout "layout2" + [ ubxtup [ intTy ] + , intTy ] + [ WordSlot, PtrSlot ] + + layout3 = + assert_layout "layout3" + [ ubxtup [ intTy, intPrimTy, intTy, intPrimTy ] + , ubxtup [ intPrimTy, intTy, intPrimTy, intTy ] ] + [ WordSlot, PtrSlot, PtrSlot, WordSlot, WordSlot ] + + enum_layout = + assert_layout "enum" + (replicate 10 (ubxtup [])) + [ WordSlot ] From git at git.haskell.org Fri Jul 22 09:49:35 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 22 Jul 2016 09:49:35 +0000 (UTC) Subject: [commit: ghc] master: StgCmmBind: Some minor simplifications (bfef2eb) Message-ID: <20160722094935.B80613A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/bfef2eb1898641f250a1b39fe67c18963a709534/ghc >--------------------------------------------------------------- commit bfef2eb1898641f250a1b39fe67c18963a709534 Author: Ömer Sinan Ağacan Date: Fri Jul 22 09:48:42 2016 +0000 StgCmmBind: Some minor simplifications >--------------------------------------------------------------- bfef2eb1898641f250a1b39fe67c18963a709534 compiler/codeGen/StgCmmBind.hs | 10 ++-------- 1 file changed, 2 insertions(+), 8 deletions(-) diff --git a/compiler/codeGen/StgCmmBind.hs b/compiler/codeGen/StgCmmBind.hs index f8fdb89..745fd33 100644 --- a/compiler/codeGen/StgCmmBind.hs +++ b/compiler/codeGen/StgCmmBind.hs @@ -112,8 +112,7 @@ cgTopRhsClosure dflags rec id ccs _ upd_flag args body = -- BUILD THE OBJECT, AND GENERATE INFO TABLE (IF NECESSARY) ; emitDataLits closure_label closure_rep ; let fv_details :: [(NonVoid Id, VirtualHpOffset)] - (_, _, fv_details) = mkVirtHeapOffsets dflags (isLFThunk lf_info) - (addIdReps []) + (_, _, fv_details) = mkVirtHeapOffsets dflags (isLFThunk lf_info) [] -- Don't drop the non-void args until the closure info has been made ; forkClosureBody (closureCodeBody True id closure_info ccs (nonVoidIds args) (length args) body fv_details) @@ -339,12 +338,7 @@ mkRhsClosure dflags bndr cc _ fvs upd_flag args body -- _was_ a free var of its RHS, mkClosureLFInfo thinks it *is* -- stored in the closure itself, so it will make sure that -- Node points to it... - ; let - is_elem = isIn "cgRhsClosure" - bndr_is_a_fv = (NonVoid bndr) `is_elem` fvs - reduced_fvs | bndr_is_a_fv = fvs `minusList` [NonVoid bndr] - | otherwise = fvs - + ; let reduced_fvs = filter (NonVoid bndr /=) fvs -- MAKE CLOSURE INFO FOR THIS CLOSURE ; mod_name <- getModuleName From git at git.haskell.org Fri Jul 22 11:05:13 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 22 Jul 2016 11:05:13 +0000 (UTC) Subject: [commit: ghc] branch 'wip/erikd-build' created Message-ID: <20160722110513.6D59E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/erikd-build Referencing: 5fa5e402e0a90e50711d2d6986c2a8e071bd9382 From git at git.haskell.org Fri Jul 22 11:05:16 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 22 Jul 2016 11:05:16 +0000 (UTC) Subject: [commit: ghc] wip/erikd-build: Fix the non-Linux build (5fa5e40) Message-ID: <20160722110516.1992D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/erikd-build Link : http://ghc.haskell.org/trac/ghc/changeset/5fa5e402e0a90e50711d2d6986c2a8e071bd9382/ghc >--------------------------------------------------------------- commit 5fa5e402e0a90e50711d2d6986c2a8e071bd9382 Author: Erik de Castro Lopo Date: Thu Jul 21 20:42:22 2016 +1000 Fix the non-Linux build * rts/sm/CNF.c: Drop un-needed #includes. * Fix parenthesis usage with CPP ASSERT macro. * Fix format string in debugBelch messages. >--------------------------------------------------------------- 5fa5e402e0a90e50711d2d6986c2a8e071bd9382 compiler/simplStg/UnariseStg.hs | 16 ++++++++-------- compiler/stgSyn/CoreToStg.hs | 2 +- rts/sm/CNF.c | 5 ++--- 3 files changed, 11 insertions(+), 12 deletions(-) diff --git a/compiler/simplStg/UnariseStg.hs b/compiler/simplStg/UnariseStg.hs index af2928d..24c0ce8 100644 --- a/compiler/simplStg/UnariseStg.hs +++ b/compiler/simplStg/UnariseStg.hs @@ -241,10 +241,10 @@ instance Outputable UnariseVal where -- | Extend the environment, checking the UnariseEnv invariant. extendRho :: UnariseEnv -> Id -> UnariseVal -> UnariseEnv extendRho rho x (MultiVal args) - = ASSERT (all (isNvUnaryType . stgArgType) args) + = ASSERT(all (isNvUnaryType . stgArgType) args) extendVarEnv rho x (MultiVal args) extendRho rho x (UnaryVal val) - = ASSERT (isNvUnaryType (stgArgType val)) + = ASSERT(isNvUnaryType (stgArgType val)) extendVarEnv rho x (UnaryVal val) -------------------------------------------------------------------------------- @@ -273,7 +273,7 @@ unariseRhs rho (StgRhsClosure ccs b_info fvs update_flag args expr) return (StgRhsClosure ccs b_info fvs' update_flag args1 expr') unariseRhs rho (StgRhsCon ccs con args) - = ASSERT (not (isUnboxedTupleCon con || isUnboxedSumCon con)) + = ASSERT(not (isUnboxedTupleCon con || isUnboxedSumCon con)) return (StgRhsCon ccs con (unariseConArgs rho args)) -------------------------------------------------------------------------------- @@ -356,7 +356,7 @@ unariseMulti_maybe rho dc args ty_args = Just (unariseConArgs rho args) | isUnboxedSumCon dc - , let args1 = ASSERT (isSingleton args) (unariseConArgs rho args) + , let args1 = ASSERT(isSingleton args) (unariseConArgs rho args) = Just (mkUbxSum dc ty_args args1) | otherwise @@ -374,7 +374,7 @@ elimCase rho args bndr (MultiValAlt _) [(_, bndrs, rhs)] | isUnboxedTupleBndr bndr = mapTupleIdBinders bndrs args rho1 | otherwise - = ASSERT (isUnboxedSumBndr bndr) + = ASSERT(isUnboxedSumBndr bndr) if null bndrs then rho1 else mapSumIdBinders bndrs args rho1 @@ -480,7 +480,7 @@ mapTupleIdBinders -> UnariseEnv -> UnariseEnv mapTupleIdBinders ids args0 rho0 - = ASSERT (not (any (isVoidTy . stgArgType) args0)) + = ASSERT(not (any (isVoidTy . stgArgType) args0)) let ids_unarised :: [(Id, RepType)] ids_unarised = map (\id -> (id, repType (idType id))) ids @@ -498,7 +498,7 @@ mapTupleIdBinders ids args0 rho0 | isMultiRep x_rep = extendRho rho x (MultiVal x_args) | otherwise - = ASSERT (x_args `lengthIs` 1) + = ASSERT(x_args `lengthIs` 1) extendRho rho x (UnaryVal (head x_args)) in map_ids rho' xs args' @@ -514,7 +514,7 @@ mapSumIdBinders -> UnariseEnv mapSumIdBinders [id] args rho0 - = ASSERT (not (any (isVoidTy . stgArgType) args)) + = ASSERT(not (any (isVoidTy . stgArgType) args)) let arg_slots = concatMap (repTypeSlots . repType . stgArgType) args id_slots = repTypeSlots (repType (idType id)) diff --git a/compiler/stgSyn/CoreToStg.hs b/compiler/stgSyn/CoreToStg.hs index cba139a..d130b74 100644 --- a/compiler/stgSyn/CoreToStg.hs +++ b/compiler/stgSyn/CoreToStg.hs @@ -774,7 +774,7 @@ mkStgRhs' con_updateable rhs_fvs bndr binder_info rhs | StgConApp con args _ <- unticked_rhs , not (con_updateable con args) = -- CorePrep does this right, but just to make sure - ASSERT (not (isUnboxedTupleCon con || isUnboxedSumCon con)) + ASSERT(not (isUnboxedTupleCon con || isUnboxedSumCon con)) StgRhsCon noCCS con args | otherwise = StgRhsClosure noCCS binder_info diff --git a/rts/sm/CNF.c b/rts/sm/CNF.c index 3c681c2..c55d778 100644 --- a/rts/sm/CNF.c +++ b/rts/sm/CNF.c @@ -30,7 +30,6 @@ #include #endif #include -#include /** * Note [Compact Normal Forms] @@ -977,7 +976,7 @@ spew_failing_pointer(StgWord *fixup_table, uint32_t count, StgWord address) bdescr *bd; StgWord size; - debugBelch("Failed to adjust 0x%lx. Block dump follows...\n", + debugBelch("Failed to adjust 0x%" FMT_HexWord ". Block dump follows...\n", address); for (i = 0; i < count; i++) { @@ -988,7 +987,7 @@ spew_failing_pointer(StgWord *fixup_table, uint32_t count, StgWord address) bd = Bdescr((P_)block); size = (W_)bd->free - (W_)bd->start; - debugBelch("%d: was 0x%lx-0x%lx, now 0x%lx-0x%lx\n", i, + debugBelch("%" FMT_Word32 ": was 0x%" FMT_HexWord "-0x%" FMT_HexWord ", now 0x%" FMT_HexWord "-0x%" FMT_HexWord "\n", i, key, key+size, value, value+size); } } From git at git.haskell.org Fri Jul 22 11:07:13 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 22 Jul 2016 11:07:13 +0000 (UTC) Subject: [commit: ghc] wip/erikd-build: Fix the non-Linux build (4c982cd) Message-ID: <20160722110713.CDFDD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/erikd-build Link : http://ghc.haskell.org/trac/ghc/changeset/4c982cd4b5ef265fc09fb15e009600b04bb9d77c/ghc >--------------------------------------------------------------- commit 4c982cd4b5ef265fc09fb15e009600b04bb9d77c Author: Erik de Castro Lopo Date: Thu Jul 21 20:42:22 2016 +1000 Fix the non-Linux build * rts/sm/CNF.c: Drop un-needed #includes. * Fix parenthesis usage with CPP ASSERT macro. * Fix format string in debugBelch messages. >--------------------------------------------------------------- 4c982cd4b5ef265fc09fb15e009600b04bb9d77c compiler/simplStg/UnariseStg.hs | 16 ++++++++-------- compiler/stgSyn/CoreToStg.hs | 2 +- rts/sm/CNF.c | 6 ++---- 3 files changed, 11 insertions(+), 13 deletions(-) diff --git a/compiler/simplStg/UnariseStg.hs b/compiler/simplStg/UnariseStg.hs index af2928d..24c0ce8 100644 --- a/compiler/simplStg/UnariseStg.hs +++ b/compiler/simplStg/UnariseStg.hs @@ -241,10 +241,10 @@ instance Outputable UnariseVal where -- | Extend the environment, checking the UnariseEnv invariant. extendRho :: UnariseEnv -> Id -> UnariseVal -> UnariseEnv extendRho rho x (MultiVal args) - = ASSERT (all (isNvUnaryType . stgArgType) args) + = ASSERT(all (isNvUnaryType . stgArgType) args) extendVarEnv rho x (MultiVal args) extendRho rho x (UnaryVal val) - = ASSERT (isNvUnaryType (stgArgType val)) + = ASSERT(isNvUnaryType (stgArgType val)) extendVarEnv rho x (UnaryVal val) -------------------------------------------------------------------------------- @@ -273,7 +273,7 @@ unariseRhs rho (StgRhsClosure ccs b_info fvs update_flag args expr) return (StgRhsClosure ccs b_info fvs' update_flag args1 expr') unariseRhs rho (StgRhsCon ccs con args) - = ASSERT (not (isUnboxedTupleCon con || isUnboxedSumCon con)) + = ASSERT(not (isUnboxedTupleCon con || isUnboxedSumCon con)) return (StgRhsCon ccs con (unariseConArgs rho args)) -------------------------------------------------------------------------------- @@ -356,7 +356,7 @@ unariseMulti_maybe rho dc args ty_args = Just (unariseConArgs rho args) | isUnboxedSumCon dc - , let args1 = ASSERT (isSingleton args) (unariseConArgs rho args) + , let args1 = ASSERT(isSingleton args) (unariseConArgs rho args) = Just (mkUbxSum dc ty_args args1) | otherwise @@ -374,7 +374,7 @@ elimCase rho args bndr (MultiValAlt _) [(_, bndrs, rhs)] | isUnboxedTupleBndr bndr = mapTupleIdBinders bndrs args rho1 | otherwise - = ASSERT (isUnboxedSumBndr bndr) + = ASSERT(isUnboxedSumBndr bndr) if null bndrs then rho1 else mapSumIdBinders bndrs args rho1 @@ -480,7 +480,7 @@ mapTupleIdBinders -> UnariseEnv -> UnariseEnv mapTupleIdBinders ids args0 rho0 - = ASSERT (not (any (isVoidTy . stgArgType) args0)) + = ASSERT(not (any (isVoidTy . stgArgType) args0)) let ids_unarised :: [(Id, RepType)] ids_unarised = map (\id -> (id, repType (idType id))) ids @@ -498,7 +498,7 @@ mapTupleIdBinders ids args0 rho0 | isMultiRep x_rep = extendRho rho x (MultiVal x_args) | otherwise - = ASSERT (x_args `lengthIs` 1) + = ASSERT(x_args `lengthIs` 1) extendRho rho x (UnaryVal (head x_args)) in map_ids rho' xs args' @@ -514,7 +514,7 @@ mapSumIdBinders -> UnariseEnv mapSumIdBinders [id] args rho0 - = ASSERT (not (any (isVoidTy . stgArgType) args)) + = ASSERT(not (any (isVoidTy . stgArgType) args)) let arg_slots = concatMap (repTypeSlots . repType . stgArgType) args id_slots = repTypeSlots (repType (idType id)) diff --git a/compiler/stgSyn/CoreToStg.hs b/compiler/stgSyn/CoreToStg.hs index cba139a..d130b74 100644 --- a/compiler/stgSyn/CoreToStg.hs +++ b/compiler/stgSyn/CoreToStg.hs @@ -774,7 +774,7 @@ mkStgRhs' con_updateable rhs_fvs bndr binder_info rhs | StgConApp con args _ <- unticked_rhs , not (con_updateable con args) = -- CorePrep does this right, but just to make sure - ASSERT (not (isUnboxedTupleCon con || isUnboxedSumCon con)) + ASSERT(not (isUnboxedTupleCon con || isUnboxedSumCon con)) StgRhsCon noCCS con args | otherwise = StgRhsClosure noCCS binder_info diff --git a/rts/sm/CNF.c b/rts/sm/CNF.c index 3c681c2..9aeb36f 100644 --- a/rts/sm/CNF.c +++ b/rts/sm/CNF.c @@ -29,8 +29,6 @@ #ifdef HAVE_LIMITS_H #include #endif -#include -#include /** * Note [Compact Normal Forms] @@ -977,7 +975,7 @@ spew_failing_pointer(StgWord *fixup_table, uint32_t count, StgWord address) bdescr *bd; StgWord size; - debugBelch("Failed to adjust 0x%lx. Block dump follows...\n", + debugBelch("Failed to adjust 0x%" FMT_HexWord ". Block dump follows...\n", address); for (i = 0; i < count; i++) { @@ -988,7 +986,7 @@ spew_failing_pointer(StgWord *fixup_table, uint32_t count, StgWord address) bd = Bdescr((P_)block); size = (W_)bd->free - (W_)bd->start; - debugBelch("%d: was 0x%lx-0x%lx, now 0x%lx-0x%lx\n", i, + debugBelch("%" FMT_Word32 ": was 0x%" FMT_HexWord "-0x%" FMT_HexWord ", now 0x%" FMT_HexWord "-0x%" FMT_HexWord "\n", i, key, key+size, value, value+size); } } From git at git.haskell.org Fri Jul 22 11:46:13 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 22 Jul 2016 11:46:13 +0000 (UTC) Subject: [commit: ghc] wip/erikd-build: Fix the non-Linux build (0f6c935) Message-ID: <20160722114613.DB2B93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/erikd-build Link : http://ghc.haskell.org/trac/ghc/changeset/0f6c93506008f85fbfbba9199ec86cbe7f637033/ghc >--------------------------------------------------------------- commit 0f6c93506008f85fbfbba9199ec86cbe7f637033 Author: Erik de Castro Lopo Date: Thu Jul 21 20:42:22 2016 +1000 Fix the non-Linux build The recent Compact Regions commit (cf989ffe49) builds fine on Linux but doesn't build on OS X r Windows. * rts/sm/CNF.c: Drop un-needed #includes. * Fix parenthesis usage with CPP ASSERT macro. * Fix format string in debugBelch messages. * Use stg_max instead. >--------------------------------------------------------------- 0f6c93506008f85fbfbba9199ec86cbe7f637033 compiler/simplStg/UnariseStg.hs | 16 ++++++++-------- compiler/stgSyn/CoreToStg.hs | 2 +- rts/sm/CNF.c | 16 +++------------- 3 files changed, 12 insertions(+), 22 deletions(-) diff --git a/compiler/simplStg/UnariseStg.hs b/compiler/simplStg/UnariseStg.hs index af2928d..24c0ce8 100644 --- a/compiler/simplStg/UnariseStg.hs +++ b/compiler/simplStg/UnariseStg.hs @@ -241,10 +241,10 @@ instance Outputable UnariseVal where -- | Extend the environment, checking the UnariseEnv invariant. extendRho :: UnariseEnv -> Id -> UnariseVal -> UnariseEnv extendRho rho x (MultiVal args) - = ASSERT (all (isNvUnaryType . stgArgType) args) + = ASSERT(all (isNvUnaryType . stgArgType) args) extendVarEnv rho x (MultiVal args) extendRho rho x (UnaryVal val) - = ASSERT (isNvUnaryType (stgArgType val)) + = ASSERT(isNvUnaryType (stgArgType val)) extendVarEnv rho x (UnaryVal val) -------------------------------------------------------------------------------- @@ -273,7 +273,7 @@ unariseRhs rho (StgRhsClosure ccs b_info fvs update_flag args expr) return (StgRhsClosure ccs b_info fvs' update_flag args1 expr') unariseRhs rho (StgRhsCon ccs con args) - = ASSERT (not (isUnboxedTupleCon con || isUnboxedSumCon con)) + = ASSERT(not (isUnboxedTupleCon con || isUnboxedSumCon con)) return (StgRhsCon ccs con (unariseConArgs rho args)) -------------------------------------------------------------------------------- @@ -356,7 +356,7 @@ unariseMulti_maybe rho dc args ty_args = Just (unariseConArgs rho args) | isUnboxedSumCon dc - , let args1 = ASSERT (isSingleton args) (unariseConArgs rho args) + , let args1 = ASSERT(isSingleton args) (unariseConArgs rho args) = Just (mkUbxSum dc ty_args args1) | otherwise @@ -374,7 +374,7 @@ elimCase rho args bndr (MultiValAlt _) [(_, bndrs, rhs)] | isUnboxedTupleBndr bndr = mapTupleIdBinders bndrs args rho1 | otherwise - = ASSERT (isUnboxedSumBndr bndr) + = ASSERT(isUnboxedSumBndr bndr) if null bndrs then rho1 else mapSumIdBinders bndrs args rho1 @@ -480,7 +480,7 @@ mapTupleIdBinders -> UnariseEnv -> UnariseEnv mapTupleIdBinders ids args0 rho0 - = ASSERT (not (any (isVoidTy . stgArgType) args0)) + = ASSERT(not (any (isVoidTy . stgArgType) args0)) let ids_unarised :: [(Id, RepType)] ids_unarised = map (\id -> (id, repType (idType id))) ids @@ -498,7 +498,7 @@ mapTupleIdBinders ids args0 rho0 | isMultiRep x_rep = extendRho rho x (MultiVal x_args) | otherwise - = ASSERT (x_args `lengthIs` 1) + = ASSERT(x_args `lengthIs` 1) extendRho rho x (UnaryVal (head x_args)) in map_ids rho' xs args' @@ -514,7 +514,7 @@ mapSumIdBinders -> UnariseEnv mapSumIdBinders [id] args rho0 - = ASSERT (not (any (isVoidTy . stgArgType) args)) + = ASSERT(not (any (isVoidTy . stgArgType) args)) let arg_slots = concatMap (repTypeSlots . repType . stgArgType) args id_slots = repTypeSlots (repType (idType id)) diff --git a/compiler/stgSyn/CoreToStg.hs b/compiler/stgSyn/CoreToStg.hs index cba139a..d130b74 100644 --- a/compiler/stgSyn/CoreToStg.hs +++ b/compiler/stgSyn/CoreToStg.hs @@ -774,7 +774,7 @@ mkStgRhs' con_updateable rhs_fvs bndr binder_info rhs | StgConApp con args _ <- unticked_rhs , not (con_updateable con args) = -- CorePrep does this right, but just to make sure - ASSERT (not (isUnboxedTupleCon con || isUnboxedSumCon con)) + ASSERT(not (isUnboxedTupleCon con || isUnboxedSumCon con)) StgRhsCon noCCS con args | otherwise = StgRhsClosure noCCS binder_info diff --git a/rts/sm/CNF.c b/rts/sm/CNF.c index 3c681c2..a24697f 100644 --- a/rts/sm/CNF.c +++ b/rts/sm/CNF.c @@ -29,8 +29,6 @@ #ifdef HAVE_LIMITS_H #include #endif -#include -#include /** * Note [Compact Normal Forms] @@ -433,14 +431,6 @@ block_is_full (StgCompactNFDataBlock *block) return (bd->free + sizeW > top); } -static inline StgWord max(StgWord a, StgWord b) -{ - if (a > b) - return a; - else - return b; -} - static rtsBool allocate_loop (Capability *cap, StgCompactNFData *str, @@ -471,7 +461,7 @@ allocate_loop (Capability *cap, } } - next_size = max(str->autoBlockW * sizeof(StgWord), + next_size = stg_max(str->autoBlockW * sizeof(StgWord), BLOCK_ROUND_UP(sizeW * sizeof(StgWord))); if (next_size >= BLOCKS_PER_MBLOCK * BLOCK_SIZE) next_size = BLOCKS_PER_MBLOCK * BLOCK_SIZE; @@ -977,7 +967,7 @@ spew_failing_pointer(StgWord *fixup_table, uint32_t count, StgWord address) bdescr *bd; StgWord size; - debugBelch("Failed to adjust 0x%lx. Block dump follows...\n", + debugBelch("Failed to adjust 0x%" FMT_HexWord ". Block dump follows...\n", address); for (i = 0; i < count; i++) { @@ -988,7 +978,7 @@ spew_failing_pointer(StgWord *fixup_table, uint32_t count, StgWord address) bd = Bdescr((P_)block); size = (W_)bd->free - (W_)bd->start; - debugBelch("%d: was 0x%lx-0x%lx, now 0x%lx-0x%lx\n", i, + debugBelch("%" FMT_Word32 ": was 0x%" FMT_HexWord "-0x%" FMT_HexWord ", now 0x%" FMT_HexWord "-0x%" FMT_HexWord "\n", i, key, key+size, value, value+size); } } From git at git.haskell.org Fri Jul 22 11:55:26 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 22 Jul 2016 11:55:26 +0000 (UTC) Subject: [commit: ghc] wip/erikd-build: Fix the non-Linux build (4178c41) Message-ID: <20160722115526.864C93A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/erikd-build Link : http://ghc.haskell.org/trac/ghc/changeset/4178c4196fd39b0a4e49cc1ddf0d832d03ee3ec5/ghc >--------------------------------------------------------------- commit 4178c4196fd39b0a4e49cc1ddf0d832d03ee3ec5 Author: Erik de Castro Lopo Date: Thu Jul 21 20:42:22 2016 +1000 Fix the non-Linux build The recent Compact Regions commit (cf989ffe49) builds fine on Linux but doesn't build on OS X r Windows. * rts/sm/CNF.c: Drop un-needed #includes. * Fix parenthesis usage with CPP ASSERT macro. * Fix format string in debugBelch messages. * Use stg_max() instead hand rolled inline max() function. >--------------------------------------------------------------- 4178c4196fd39b0a4e49cc1ddf0d832d03ee3ec5 compiler/simplStg/UnariseStg.hs | 16 ++++++++-------- compiler/stgSyn/CoreToStg.hs | 2 +- rts/sm/CNF.c | 16 +++------------- 3 files changed, 12 insertions(+), 22 deletions(-) diff --git a/compiler/simplStg/UnariseStg.hs b/compiler/simplStg/UnariseStg.hs index af2928d..24c0ce8 100644 --- a/compiler/simplStg/UnariseStg.hs +++ b/compiler/simplStg/UnariseStg.hs @@ -241,10 +241,10 @@ instance Outputable UnariseVal where -- | Extend the environment, checking the UnariseEnv invariant. extendRho :: UnariseEnv -> Id -> UnariseVal -> UnariseEnv extendRho rho x (MultiVal args) - = ASSERT (all (isNvUnaryType . stgArgType) args) + = ASSERT(all (isNvUnaryType . stgArgType) args) extendVarEnv rho x (MultiVal args) extendRho rho x (UnaryVal val) - = ASSERT (isNvUnaryType (stgArgType val)) + = ASSERT(isNvUnaryType (stgArgType val)) extendVarEnv rho x (UnaryVal val) -------------------------------------------------------------------------------- @@ -273,7 +273,7 @@ unariseRhs rho (StgRhsClosure ccs b_info fvs update_flag args expr) return (StgRhsClosure ccs b_info fvs' update_flag args1 expr') unariseRhs rho (StgRhsCon ccs con args) - = ASSERT (not (isUnboxedTupleCon con || isUnboxedSumCon con)) + = ASSERT(not (isUnboxedTupleCon con || isUnboxedSumCon con)) return (StgRhsCon ccs con (unariseConArgs rho args)) -------------------------------------------------------------------------------- @@ -356,7 +356,7 @@ unariseMulti_maybe rho dc args ty_args = Just (unariseConArgs rho args) | isUnboxedSumCon dc - , let args1 = ASSERT (isSingleton args) (unariseConArgs rho args) + , let args1 = ASSERT(isSingleton args) (unariseConArgs rho args) = Just (mkUbxSum dc ty_args args1) | otherwise @@ -374,7 +374,7 @@ elimCase rho args bndr (MultiValAlt _) [(_, bndrs, rhs)] | isUnboxedTupleBndr bndr = mapTupleIdBinders bndrs args rho1 | otherwise - = ASSERT (isUnboxedSumBndr bndr) + = ASSERT(isUnboxedSumBndr bndr) if null bndrs then rho1 else mapSumIdBinders bndrs args rho1 @@ -480,7 +480,7 @@ mapTupleIdBinders -> UnariseEnv -> UnariseEnv mapTupleIdBinders ids args0 rho0 - = ASSERT (not (any (isVoidTy . stgArgType) args0)) + = ASSERT(not (any (isVoidTy . stgArgType) args0)) let ids_unarised :: [(Id, RepType)] ids_unarised = map (\id -> (id, repType (idType id))) ids @@ -498,7 +498,7 @@ mapTupleIdBinders ids args0 rho0 | isMultiRep x_rep = extendRho rho x (MultiVal x_args) | otherwise - = ASSERT (x_args `lengthIs` 1) + = ASSERT(x_args `lengthIs` 1) extendRho rho x (UnaryVal (head x_args)) in map_ids rho' xs args' @@ -514,7 +514,7 @@ mapSumIdBinders -> UnariseEnv mapSumIdBinders [id] args rho0 - = ASSERT (not (any (isVoidTy . stgArgType) args)) + = ASSERT(not (any (isVoidTy . stgArgType) args)) let arg_slots = concatMap (repTypeSlots . repType . stgArgType) args id_slots = repTypeSlots (repType (idType id)) diff --git a/compiler/stgSyn/CoreToStg.hs b/compiler/stgSyn/CoreToStg.hs index cba139a..d130b74 100644 --- a/compiler/stgSyn/CoreToStg.hs +++ b/compiler/stgSyn/CoreToStg.hs @@ -774,7 +774,7 @@ mkStgRhs' con_updateable rhs_fvs bndr binder_info rhs | StgConApp con args _ <- unticked_rhs , not (con_updateable con args) = -- CorePrep does this right, but just to make sure - ASSERT (not (isUnboxedTupleCon con || isUnboxedSumCon con)) + ASSERT(not (isUnboxedTupleCon con || isUnboxedSumCon con)) StgRhsCon noCCS con args | otherwise = StgRhsClosure noCCS binder_info diff --git a/rts/sm/CNF.c b/rts/sm/CNF.c index 3c681c2..a24697f 100644 --- a/rts/sm/CNF.c +++ b/rts/sm/CNF.c @@ -29,8 +29,6 @@ #ifdef HAVE_LIMITS_H #include #endif -#include -#include /** * Note [Compact Normal Forms] @@ -433,14 +431,6 @@ block_is_full (StgCompactNFDataBlock *block) return (bd->free + sizeW > top); } -static inline StgWord max(StgWord a, StgWord b) -{ - if (a > b) - return a; - else - return b; -} - static rtsBool allocate_loop (Capability *cap, StgCompactNFData *str, @@ -471,7 +461,7 @@ allocate_loop (Capability *cap, } } - next_size = max(str->autoBlockW * sizeof(StgWord), + next_size = stg_max(str->autoBlockW * sizeof(StgWord), BLOCK_ROUND_UP(sizeW * sizeof(StgWord))); if (next_size >= BLOCKS_PER_MBLOCK * BLOCK_SIZE) next_size = BLOCKS_PER_MBLOCK * BLOCK_SIZE; @@ -977,7 +967,7 @@ spew_failing_pointer(StgWord *fixup_table, uint32_t count, StgWord address) bdescr *bd; StgWord size; - debugBelch("Failed to adjust 0x%lx. Block dump follows...\n", + debugBelch("Failed to adjust 0x%" FMT_HexWord ". Block dump follows...\n", address); for (i = 0; i < count; i++) { @@ -988,7 +978,7 @@ spew_failing_pointer(StgWord *fixup_table, uint32_t count, StgWord address) bd = Bdescr((P_)block); size = (W_)bd->free - (W_)bd->start; - debugBelch("%d: was 0x%lx-0x%lx, now 0x%lx-0x%lx\n", i, + debugBelch("%" FMT_Word32 ": was 0x%" FMT_HexWord "-0x%" FMT_HexWord ", now 0x%" FMT_HexWord "-0x%" FMT_HexWord "\n", i, key, key+size, value, value+size); } } From git at git.haskell.org Fri Jul 22 12:27:57 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 22 Jul 2016 12:27:57 +0000 (UTC) Subject: [commit: ghc] wip/12368: DmdAnal: When aborting fixed-point-iteration, do not forget strict variables (924d210) Message-ID: <20160722122757.D85543A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/12368 Link : http://ghc.haskell.org/trac/ghc/changeset/924d2102b8ee3de3d4a93274bdb0ea3918ac5008/ghc >--------------------------------------------------------------- commit 924d2102b8ee3de3d4a93274bdb0ea3918ac5008 Author: Joachim Breitner Date: Fri Jul 22 14:24:58 2016 +0200 DmdAnal: When aborting fixed-point-iteration, do not forget strict variables When fixed-point iteration does not terminate, we conservatively delete their strictness signatures (set them to nopSig). But this loses the information on how its strict free variables are used! Lazily used variables already escape via lazy_fvs. This patch ensures that in the case of an aborted fixed-point iteration, also the strict variables are put there (with a conservative demand of topDmd). >--------------------------------------------------------------- 924d2102b8ee3de3d4a93274bdb0ea3918ac5008 compiler/basicTypes/Demand.hs | 7 ++++++- compiler/basicTypes/VarEnv.hs | 5 ++++- compiler/stranal/DmdAnal.hs | 15 +++++++++++++-- compiler/utils/UniqFM.hs | 6 ++++++ testsuite/tests/stranal/should_run/all.T | 2 +- 5 files changed, 30 insertions(+), 5 deletions(-) diff --git a/compiler/basicTypes/Demand.hs b/compiler/basicTypes/Demand.hs index 8dc7f3b..2ada6b3 100644 --- a/compiler/basicTypes/Demand.hs +++ b/compiler/basicTypes/Demand.hs @@ -36,7 +36,9 @@ module Demand ( appIsBottom, isBottomingSig, pprIfaceStrictSig, trimCPRInfo, returnsCPR_maybe, StrictSig(..), mkStrictSig, mkClosedStrictSig, nopSig, botSig, cprProdSig, - isTopSig, hasDemandEnvSig, splitStrictSig, increaseStrictSigArity, + isTopSig, hasDemandEnvSig, + splitStrictSig, strictSigDmdEnv, + increaseStrictSigArity, seqDemand, seqDemandList, seqDmdType, seqStrictSig, @@ -1682,6 +1684,9 @@ isTopSig (StrictSig ty) = isTopDmdType ty hasDemandEnvSig :: StrictSig -> Bool hasDemandEnvSig (StrictSig (DmdType env _ _)) = not (isEmptyVarEnv env) +strictSigDmdEnv :: StrictSig -> DmdEnv +strictSigDmdEnv (StrictSig (DmdType env _ _)) = env + isBottomingSig :: StrictSig -> Bool -- True if the signature diverges or throws an exception isBottomingSig (StrictSig (DmdType _ _ res)) = isBotRes res diff --git a/compiler/basicTypes/VarEnv.hs b/compiler/basicTypes/VarEnv.hs index 92b6cc7..f02a426 100644 --- a/compiler/basicTypes/VarEnv.hs +++ b/compiler/basicTypes/VarEnv.hs @@ -12,7 +12,8 @@ module VarEnv ( elemVarEnv, extendVarEnv, extendVarEnv_C, extendVarEnv_Acc, extendVarEnv_Directly, extendVarEnvList, - plusVarEnv, plusVarEnv_C, plusVarEnv_CD, alterVarEnv, + plusVarEnv, plusVarEnv_C, plusVarEnv_CD, plusVarEnvList, + alterVarEnv, delVarEnvList, delVarEnv, delVarEnv_Directly, minusVarEnv, intersectsVarEnv, lookupVarEnv, lookupVarEnv_NF, lookupWithDefaultVarEnv, @@ -422,6 +423,7 @@ extendVarEnv_C :: (a->a->a) -> VarEnv a -> Var -> a -> VarEnv a extendVarEnv_Acc :: (a->b->b) -> (a->b) -> VarEnv b -> Var -> a -> VarEnv b extendVarEnv_Directly :: VarEnv a -> Unique -> a -> VarEnv a plusVarEnv :: VarEnv a -> VarEnv a -> VarEnv a +plusVarEnvList :: [VarEnv a] -> VarEnv a extendVarEnvList :: VarEnv a -> [(Var, a)] -> VarEnv a lookupVarEnv_Directly :: VarEnv a -> Unique -> Maybe a @@ -461,6 +463,7 @@ delVarEnv = delFromUFM minusVarEnv = minusUFM intersectsVarEnv e1 e2 = not (isEmptyVarEnv (e1 `intersectUFM` e2)) plusVarEnv = plusUFM +plusVarEnvList = plusUFMList lookupVarEnv = lookupUFM filterVarEnv = filterUFM lookupWithDefaultVarEnv = lookupWithDefaultUFM diff --git a/compiler/stranal/DmdAnal.hs b/compiler/stranal/DmdAnal.hs index d6e02a9..22e1faa 100644 --- a/compiler/stranal/DmdAnal.hs +++ b/compiler/stranal/DmdAnal.hs @@ -495,8 +495,12 @@ dmdFix top_lvl env orig_pairs -- If fixed-point iteration does not yield a result we use this instead -- See Note [Safe abortion in the fixed-point iteration] abort :: (AnalEnv, DmdEnv, [(Id,CoreExpr)]) - abort = (env, lazy_fv, zapIdStrictness pairs') + abort = (env, lazy_fv', zapped_pairs) where (lazy_fv, pairs') = step True (zapIdStrictness orig_pairs) + -- Note [Lazy and unleasheable free variables] + non_lazy_fvs = plusVarEnvList $ map (strictSigDmdEnv . idStrictness . fst) pairs' + lazy_fv' = lazy_fv `plusVarEnv` mapVarEnv (const topDmd) non_lazy_fvs + zapped_pairs = zapIdStrictness pairs' -- The fixed-point varies the idStrictness field of the binders, and terminates if that -- annotation does not change any more. @@ -544,7 +548,7 @@ Fixed-point iteration may fail to terminate. But we cannot simply give up and return the environment and code unchanged! We still need to do one additional round, for two reasons: - * To get information on used free variables + * To get information on used free variables (both lazy and strict!) (see Note [Lazy and unleasheable free variables]) * To ensure that all expressions have been traversed at least once, and any left-over strictness annotations have been updated. @@ -983,6 +987,7 @@ Incidentally, here's a place where lambda-lifting h would lose the cigar --- we couldn't see the joint strictness in t/x ON THE OTHER HAND + We don't want to put *all* the fv's from the RHS into the DmdType. Because * it makes the strictness signatures, and hence slows down @@ -996,6 +1001,12 @@ absent.) To make up for this, the code that analyses the binding keeps the deman on those variable separate (usually called "lazy_fv") and adds it to the demand of the whole binding later. +What if we decide not to store a strictness signature for a binding at all, as +we do when aborting a fixed-point iteration? The we risk losing the information +that the strict variables are being used. In that case, we take all free variables +mentioned in the (unsound) strictness signature, conservatively approximate the +demand put on them (topDmd), and add that to the "lazy_fv" returned by "dmdFix". + Note [Lamba-bound unfoldings] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ diff --git a/compiler/utils/UniqFM.hs b/compiler/utils/UniqFM.hs index 244969c..be5da83 100644 --- a/compiler/utils/UniqFM.hs +++ b/compiler/utils/UniqFM.hs @@ -49,6 +49,7 @@ module UniqFM ( plusUFM, plusUFM_C, plusUFM_CD, + plusUFMList, minusUFM, intersectUFM, intersectUFM_C, @@ -71,6 +72,8 @@ module UniqFM ( import Unique ( Uniquable(..), Unique, getKey ) import Outputable +import Data.List (foldl') + import qualified Data.IntMap as M import qualified Data.IntSet as S import Data.Typeable @@ -214,6 +217,9 @@ plusUFM_CD f (UFM xm) dx (UFM ym) dy (M.map (\y -> dx `f` y)) xm ym +plusUFMList :: [UniqFM elt] -> UniqFM elt +plusUFMList = foldl' plusUFM emptyUFM + minusUFM :: UniqFM elt1 -> UniqFM elt2 -> UniqFM elt1 minusUFM (UFM x) (UFM y) = UFM (M.difference x y) diff --git a/testsuite/tests/stranal/should_run/all.T b/testsuite/tests/stranal/should_run/all.T index fb678b4..d3d4aaf 100644 --- a/testsuite/tests/stranal/should_run/all.T +++ b/testsuite/tests/stranal/should_run/all.T @@ -13,4 +13,4 @@ test('T10218', normal, compile_and_run, ['']) test('T11076', normal, multimod_compile_and_run, ['T11076.hs', 'T11076_prim.cmm']) test('T11555a', normal, compile_and_run, ['']) test('T12368', exit_code(1), compile_and_run, ['']) -test('T12368a', [expect_broken(12368), exit_code(1)], compile_and_run, ['']) +test('T12368a', exit_code(1), compile_and_run, ['']) From git at git.haskell.org Fri Jul 22 12:57:26 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 22 Jul 2016 12:57:26 +0000 (UTC) Subject: [commit: ghc] master: Add deepseq dependency and a few NFData instances (c4f3d91) Message-ID: <20160722125726.48E783A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c4f3d91b6b32a27c2e00506de532e90c595de2d1/ghc >--------------------------------------------------------------- commit c4f3d91b6b32a27c2e00506de532e90c595de2d1 Author: Simon Marlow Date: Thu Jul 21 04:32:55 2016 -0700 Add deepseq dependency and a few NFData instances I needed to rnf a data structure (CompiledByteCode) but we don't have any good deepseq infrastructure in the compiler yet. There are bits and pieces, but nothing consistent, so this is a start. We already had a dependency on deepseq indirectly via other packages (e.g. containers). Includes an update to the haddock submodule, to remove orphan NFData instances in there. Test Plan: validate Reviewers: austin, bgamari, erikd, hvr Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2418 >--------------------------------------------------------------- c4f3d91b6b32a27c2e00506de532e90c595de2d1 compiler/basicTypes/Module.hs | 12 +++++++++++- compiler/basicTypes/Name.hs | 13 +++++++++++++ compiler/basicTypes/OccName.hs | 4 ++++ compiler/basicTypes/SrcLoc.hs | 4 ++++ compiler/ghc.cabal.in | 1 + compiler/utils/FastString.hs | 5 ++++- libraries/ghci/GHCi/RemoteTypes.hs | 5 +++++ libraries/ghci/SizedSeq.hs | 4 ++++ utils/haddock | 2 +- 9 files changed, 47 insertions(+), 3 deletions(-) diff --git a/compiler/basicTypes/Module.hs b/compiler/basicTypes/Module.hs index 59ed840..b6b19d2 100644 --- a/compiler/basicTypes/Module.hs +++ b/compiler/basicTypes/Module.hs @@ -92,6 +92,7 @@ import Data.Ord import {-# SOURCE #-} Packages import GHC.PackageDb (BinaryStringRep(..), DbModuleRep(..), DbModule(..)) +import Control.DeepSeq import Data.Coerce import Data.Data import Data.Map (Map) @@ -266,6 +267,9 @@ instance Data ModuleName where gunfold _ _ = error "gunfold" dataTypeOf _ = mkNoRepType "ModuleName" +instance NFData ModuleName where + rnf x = x `seq` () + stableModuleNameCmp :: ModuleName -> ModuleName -> Ordering -- ^ Compares module names lexically, rather than by their 'Unique's stableModuleNameCmp n1 n2 = moduleNameFS n1 `compare` moduleNameFS n2 @@ -319,7 +323,7 @@ moduleNameColons = dots_to_colons . moduleNameString -- | A Module is a pair of a 'UnitId' and a 'ModuleName'. data Module = Module { moduleUnitId :: !UnitId, -- pkg-1.0 - moduleName :: !ModuleName -- A.B.C + moduleName :: !ModuleName -- A.B.C } deriving (Eq, Ord) @@ -339,6 +343,9 @@ instance Data Module where gunfold _ _ = error "gunfold" dataTypeOf _ = mkNoRepType "Module" +instance NFData Module where + rnf x = x `seq` () + -- | This gives a stable ordering, as opposed to the Ord instance which -- gives an ordering based on the 'Unique's of the components, which may -- not be stable from run to run of the compiler. @@ -404,6 +411,9 @@ instance Data UnitId where gunfold _ _ = error "gunfold" dataTypeOf _ = mkNoRepType "UnitId" +instance NFData UnitId where + rnf x = x `seq` () + stableUnitIdCmp :: UnitId -> UnitId -> Ordering -- ^ Compares package ids lexically, rather than by their 'Unique's stableUnitIdCmp p1 p2 = unitIdFS p1 `compare` unitIdFS p2 diff --git a/compiler/basicTypes/Name.hs b/compiler/basicTypes/Name.hs index b0411b9..d1b05f3 100644 --- a/compiler/basicTypes/Name.hs +++ b/compiler/basicTypes/Name.hs @@ -90,6 +90,7 @@ import DynFlags import FastString import Outputable +import Control.DeepSeq import Data.Data {- @@ -131,6 +132,18 @@ instance Outputable NameSort where ppr Internal = text "internal" ppr System = text "system" +instance NFData Name where + rnf Name{..} = rnf n_sort + +instance NFData NameSort where + rnf (External m) = rnf m + rnf (WiredIn m t b) = rnf m `seq` t `seq` b `seq` () + -- XXX this is a *lie*, we're not going to rnf the TyThing, but + -- since the TyThings for WiredIn Names are all static they can't + -- be hiding space leaks or errors. + rnf Internal = () + rnf System = () + -- | BuiltInSyntax is for things like @(:)@, @[]@ and tuples, -- which have special syntactic forms. They aren't in scope -- as such. diff --git a/compiler/basicTypes/OccName.hs b/compiler/basicTypes/OccName.hs index 8dfeb7f..3b8943f 100644 --- a/compiler/basicTypes/OccName.hs +++ b/compiler/basicTypes/OccName.hs @@ -116,6 +116,7 @@ import FastStringEnv import Outputable import Lexeme import Binary +import Control.DeepSeq import Data.List (mapAccumL) import Data.Char import Data.Data @@ -249,6 +250,9 @@ instance Data OccName where instance HasOccName OccName where occName = id +instance NFData OccName where + rnf x = x `seq` () + {- ************************************************************************ * * diff --git a/compiler/basicTypes/SrcLoc.hs b/compiler/basicTypes/SrcLoc.hs index a5df956..9c48eee 100644 --- a/compiler/basicTypes/SrcLoc.hs +++ b/compiler/basicTypes/SrcLoc.hs @@ -84,6 +84,7 @@ import Util import Outputable import FastString +import Control.DeepSeq import Data.Bits import Data.Data import Data.List @@ -238,6 +239,9 @@ data SrcSpan = deriving (Eq, Ord, Show) -- Show is used by Lexer.x, because we -- derive Show for Token +instance NFData SrcSpan where + rnf x = x `seq` () + -- | Built-in "bad" 'SrcSpan's for common sources of location uncertainty noSrcSpan, wiredInSrcSpan, interactiveSrcSpan :: SrcSpan noSrcSpan = UnhelpfulSpan (fsLit "") diff --git a/compiler/ghc.cabal.in b/compiler/ghc.cabal.in index 3042d1d..3d75dae 100644 --- a/compiler/ghc.cabal.in +++ b/compiler/ghc.cabal.in @@ -45,6 +45,7 @@ Library Exposed: False Build-Depends: base >= 4 && < 5, + deepseq >= 1.4 && < 1.5, directory >= 1 && < 1.3, process >= 1 && < 1.5, bytestring >= 0.9 && < 0.11, diff --git a/compiler/utils/FastString.hs b/compiler/utils/FastString.hs index 651719a..1496a86 100644 --- a/compiler/utils/FastString.hs +++ b/compiler/utils/FastString.hs @@ -1,6 +1,7 @@ -- (c) The University of Glasgow, 1997-2006 -{-# LANGUAGE BangPatterns, CPP, MagicHash, UnboxedTuples #-} +{-# LANGUAGE BangPatterns, CPP, MagicHash, UnboxedTuples, + GeneralizedNewtypeDeriving #-} {-# OPTIONS_GHC -O -funbox-strict-fields #-} -- We always optimise this, otherwise performance of a non-optimised -- compiler is severely affected @@ -97,6 +98,7 @@ import FastFunctions import Panic import Util +import Control.DeepSeq import Control.Monad import Data.ByteString (ByteString) import qualified Data.ByteString as BS @@ -145,6 +147,7 @@ hashByteString bs -- ----------------------------------------------------------------------------- newtype FastZString = FastZString ByteString + deriving NFData hPutFZS :: Handle -> FastZString -> IO () hPutFZS handle (FastZString bs) = BS.hPut handle bs diff --git a/libraries/ghci/GHCi/RemoteTypes.hs b/libraries/ghci/GHCi/RemoteTypes.hs index 5bc0136..3b4dee7 100644 --- a/libraries/ghci/GHCi/RemoteTypes.hs +++ b/libraries/ghci/GHCi/RemoteTypes.hs @@ -17,6 +17,7 @@ module GHCi.RemoteTypes , unsafeForeignRefToRemoteRef, finalizeForeignRef ) where +import Control.DeepSeq import Data.Word import Foreign hiding (newForeignPtr) import Foreign.Concurrent @@ -49,6 +50,7 @@ castRemotePtr (RemotePtr a) = RemotePtr a deriving instance Show (RemotePtr a) deriving instance Binary (RemotePtr a) +deriving instance NFData (RemotePtr a) -- ----------------------------------------------------------------------------- -- HValueRef @@ -91,6 +93,9 @@ freeRemoteRef (RemoteRef w) = -- | An HValueRef with a finalizer newtype ForeignRef a = ForeignRef (ForeignPtr ()) +instance NFData (ForeignRef a) where + rnf x = x `seq` () + type ForeignHValue = ForeignRef HValue -- | Create a 'ForeignRef' from a 'RemoteRef'. The finalizer diff --git a/libraries/ghci/SizedSeq.hs b/libraries/ghci/SizedSeq.hs index e5bb37c..503544a 100644 --- a/libraries/ghci/SizedSeq.hs +++ b/libraries/ghci/SizedSeq.hs @@ -8,6 +8,7 @@ module SizedSeq , sizeSS ) where +import Control.DeepSeq import Data.Binary import Data.List import GHC.Generics @@ -26,6 +27,9 @@ instance Traversable SizedSeq where instance Binary a => Binary (SizedSeq a) +instance NFData a => NFData (SizedSeq a) where + rnf (SizedSeq _ xs) = rnf xs + emptySS :: SizedSeq a emptySS = SizedSeq 0 [] diff --git a/utils/haddock b/utils/haddock index cdc81a1..a3309e7 160000 --- a/utils/haddock +++ b/utils/haddock @@ -1 +1 @@ -Subproject commit cdc81a1b73bd4d1b330a32870d4369e1a2af3610 +Subproject commit a3309e797c42dae9bccdeb17ce52fcababbaff8a From git at git.haskell.org Fri Jul 22 12:57:28 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 22 Jul 2016 12:57:28 +0000 (UTC) Subject: [commit: ghc] master: UNPACK the size field of SizedSeq (1fe5c89) Message-ID: <20160722125728.E4DA53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1fe5c8916a2bdf90ed2d9c70f900642b56650592/ghc >--------------------------------------------------------------- commit 1fe5c8916a2bdf90ed2d9c70f900642b56650592 Author: Simon Marlow Date: Thu Jul 21 05:47:47 2016 -0700 UNPACK the size field of SizedSeq >--------------------------------------------------------------- 1fe5c8916a2bdf90ed2d9c70f900642b56650592 libraries/ghci/SizedSeq.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/ghci/SizedSeq.hs b/libraries/ghci/SizedSeq.hs index 503544a..55433c2 100644 --- a/libraries/ghci/SizedSeq.hs +++ b/libraries/ghci/SizedSeq.hs @@ -13,7 +13,7 @@ import Data.Binary import Data.List import GHC.Generics -data SizedSeq a = SizedSeq !Word [a] +data SizedSeq a = SizedSeq {-# UNPACK #-} !Word [a] deriving (Generic, Show) instance Functor SizedSeq where From git at git.haskell.org Fri Jul 22 12:57:31 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 22 Jul 2016 12:57:31 +0000 (UTC) Subject: [commit: ghc] master: Squash space leaks in the result of byteCodeGen (648fd73) Message-ID: <20160722125731.8CF5C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/648fd73a7b8fbb7955edc83330e2910428e76147/ghc >--------------------------------------------------------------- commit 648fd73a7b8fbb7955edc83330e2910428e76147 Author: Simon Marlow Date: Thu Jul 21 04:51:05 2016 -0700 Squash space leaks in the result of byteCodeGen When loading a large number of modules into GHCi, we collect CompiledByteCode for every module and then link it all at the end. Space leaks in the CompiledByteCode linger until we traverse it all for linking, and possibly longer, if there are bits we don't look at. This is the nuke-it-from-orbit approach: we deepseq the whole thing after code generation. It's the only way to be sure. Test Plan: Heap profile of GHCi while loading nofib/real/anna into GHCi, this patch reduces the peak heap usage from ~100M to ~50M. Reviewers: hvr, austin, bgamari, erikd Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2419 >--------------------------------------------------------------- 648fd73a7b8fbb7955edc83330e2910428e76147 compiler/ghci/ByteCodeGen.hs | 15 ++++++++- compiler/ghci/ByteCodeTypes.hs | 73 ++++++++++++++++++++++++++++++++---------- 2 files changed, 70 insertions(+), 18 deletions(-) diff --git a/compiler/ghci/ByteCodeGen.hs b/compiler/ghci/ByteCodeGen.hs index 9c7d25a..90e2174 100644 --- a/compiler/ghci/ByteCodeGen.hs +++ b/compiler/ghci/ByteCodeGen.hs @@ -1,4 +1,5 @@ {-# LANGUAGE CPP, MagicHash, RecordWildCards #-} +{-# OPTIONS_GHC -fprof-auto-top #-} -- -- (c) The University of Glasgow 2002-2006 -- @@ -57,6 +58,7 @@ import UniqSupply import Module import Control.Arrow ( second ) +import Control.Exception import Data.Array import Data.Map (Map) import Data.IntMap (IntMap) @@ -93,10 +95,21 @@ byteCodeGen hsc_env this_mod binds tycs mb_modBreaks dumpIfSet_dyn dflags Opt_D_dump_BCOs "Proto-BCOs" (vcat (intersperse (char ' ') (map ppr proto_bcos))) - assembleBCOs hsc_env proto_bcos tycs + cbc <- assembleBCOs hsc_env proto_bcos tycs (case modBreaks of Nothing -> Nothing Just mb -> Just mb{ modBreaks_breakInfo = breakInfo }) + + -- Squash space leaks in the CompiledByteCode. This is really + -- important, because when loading a set of modules into GHCi + -- we don't touch the CompiledByteCode until the end when we + -- do linking. Forcing out the thunks here reduces space + -- usage by more than 50% when loading a large number of + -- modules. + evaluate (seqCompiledByteCode cbc) + + return cbc + where dflags = hsc_dflags hsc_env -- ----------------------------------------------------------------------------- diff --git a/compiler/ghci/ByteCodeTypes.hs b/compiler/ghci/ByteCodeTypes.hs index 99e2ba2..3537a2b 100644 --- a/compiler/ghci/ByteCodeTypes.hs +++ b/compiler/ghci/ByteCodeTypes.hs @@ -1,11 +1,11 @@ -{-# LANGUAGE MagicHash, RecordWildCards #-} +{-# LANGUAGE MagicHash, RecordWildCards, GeneralizedNewtypeDeriving #-} -- -- (c) The University of Glasgow 2002-2006 -- -- | Bytecode assembler types module ByteCodeTypes - ( CompiledByteCode(..), FFIInfo(..) + ( CompiledByteCode(..), seqCompiledByteCode, FFIInfo(..) , UnlinkedBCO(..), BCOPtr(..), BCONPtr(..) , ItblEnv, ItblPtr(..) , CgBreakInfo(..) @@ -26,6 +26,7 @@ import GHCi.BreakArray import GHCi.RemoteTypes import GHCi.FFI import GHCi.InfoTable +import Control.DeepSeq import Foreign import Data.Array @@ -48,38 +49,61 @@ data CompiledByteCode = CompiledByteCode } -- ToDo: we're not tracking strings that we malloc'd newtype FFIInfo = FFIInfo (RemotePtr C_ffi_cif) - deriving Show + deriving (Show, NFData) instance Outputable CompiledByteCode where ppr CompiledByteCode{..} = ppr bc_bcos +-- Not a real NFData instance, because ModBreaks contains some things +-- we can't rnf +seqCompiledByteCode :: CompiledByteCode -> () +seqCompiledByteCode CompiledByteCode{..} = + rnf bc_bcos `seq` + rnf (nameEnvElts bc_itbls) `seq` + rnf bc_ffis `seq` + rnf bc_strs `seq` + rnf (fmap seqModBreaks bc_breaks) + type ItblEnv = NameEnv (Name, ItblPtr) -- We need the Name in the range so we know which -- elements to filter out when unloading a module -newtype ItblPtr = ItblPtr (RemotePtr StgInfoTable) deriving Show +newtype ItblPtr = ItblPtr (RemotePtr StgInfoTable) + deriving (Show, NFData) data UnlinkedBCO = UnlinkedBCO { - unlinkedBCOName :: Name, - unlinkedBCOArity :: Int, - unlinkedBCOInstrs :: UArray Int Word16, -- insns - unlinkedBCOBitmap :: UArray Int Word, -- bitmap - unlinkedBCOLits :: (SizedSeq BCONPtr), -- non-ptrs - unlinkedBCOPtrs :: (SizedSeq BCOPtr) -- ptrs + unlinkedBCOName :: !Name, + unlinkedBCOArity :: {-# UNPACK #-} !Int, + unlinkedBCOInstrs :: !(UArray Int Word16), -- insns + unlinkedBCOBitmap :: !(UArray Int Word), -- bitmap + unlinkedBCOLits :: !(SizedSeq BCONPtr), -- non-ptrs + unlinkedBCOPtrs :: !(SizedSeq BCOPtr) -- ptrs } +instance NFData UnlinkedBCO where + rnf UnlinkedBCO{..} = + rnf unlinkedBCOLits `seq` + rnf unlinkedBCOPtrs + data BCOPtr - = BCOPtrName Name - | BCOPtrPrimOp PrimOp - | BCOPtrBCO UnlinkedBCO + = BCOPtrName !Name + | BCOPtrPrimOp !PrimOp + | BCOPtrBCO !UnlinkedBCO | BCOPtrBreakArray -- a pointer to this module's BreakArray +instance NFData BCOPtr where + rnf (BCOPtrBCO bco) = rnf bco + rnf x = x `seq` () + data BCONPtr - = BCONPtrWord Word - | BCONPtrLbl FastString - | BCONPtrItbl Name - | BCONPtrStr ByteString + = BCONPtrWord {-# UNPACK #-} !Word + | BCONPtrLbl !FastString + | BCONPtrItbl !Name + | BCONPtrStr !ByteString + +instance NFData BCONPtr where + rnf x = x `seq` () -- | Information about a breakpoint that we know at code-generation time data CgBreakInfo @@ -88,6 +112,12 @@ data CgBreakInfo , cgb_resty :: Type } +-- Not a real NFData instance because we can't rnf Id or Type +seqCgBreakInfo :: CgBreakInfo -> () +seqCgBreakInfo CgBreakInfo{..} = + rnf (map snd cgb_vars) `seq` + seqType cgb_resty + instance Outputable UnlinkedBCO where ppr (UnlinkedBCO nm _arity _insns _bitmap lits ptrs) = sep [text "BCO", ppr nm, text "with", @@ -126,6 +156,15 @@ data ModBreaks -- ^ info about each breakpoint from the bytecode generator } +seqModBreaks :: ModBreaks -> () +seqModBreaks ModBreaks{..} = + rnf modBreaks_flags `seq` + rnf modBreaks_locs `seq` + rnf modBreaks_vars `seq` + rnf modBreaks_decls `seq` + rnf modBreaks_ccs `seq` + rnf (fmap seqCgBreakInfo modBreaks_breakInfo) + -- | Construct an empty ModBreaks emptyModBreaks :: ModBreaks emptyModBreaks = ModBreaks From git at git.haskell.org Fri Jul 22 12:57:34 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 22 Jul 2016 12:57:34 +0000 (UTC) Subject: [commit: ghc] master: -fprof-auto-top (7f0f1d7) Message-ID: <20160722125734.373E43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7f0f1d7f7d798e86b3d599d61dbc5ffc71afeb52/ghc >--------------------------------------------------------------- commit 7f0f1d7f7d798e86b3d599d61dbc5ffc71afeb52 Author: Simon Marlow Date: Thu Jul 21 04:33:44 2016 -0700 -fprof-auto-top >--------------------------------------------------------------- 7f0f1d7f7d798e86b3d599d61dbc5ffc71afeb52 compiler/main/HscMain.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/compiler/main/HscMain.hs b/compiler/main/HscMain.hs index bd7f8c9..94ab42e 100644 --- a/compiler/main/HscMain.hs +++ b/compiler/main/HscMain.hs @@ -1,4 +1,5 @@ {-# LANGUAGE BangPatterns, CPP, MagicHash, NondecreasingIndentation #-} +{-# OPTIONS_GHC -fprof-auto-top #-} ------------------------------------------------------------------------------- -- From git at git.haskell.org Fri Jul 22 15:19:29 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 22 Jul 2016 15:19:29 +0000 (UTC) Subject: [commit: ghc] master: Fix the non-Linux build (d068220) Message-ID: <20160722151929.190B03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d068220f4249cce66ed5b6cc5504f79e7c8c0184/ghc >--------------------------------------------------------------- commit d068220f4249cce66ed5b6cc5504f79e7c8c0184 Author: Erik de Castro Lopo Date: Fri Jul 22 14:59:44 2016 +0200 Fix the non-Linux build Summary: The recent Compact Regions commit (cf989ffe49) builds fine on Linux but doesn't build on OS X r Windows. * rts/sm/CNF.c: Drop un-needed #includes. * Fix parenthesis usage with CPP ASSERT macro. * Fix format string in debugBelch messages. * Use stg_max() instead hand rolled inline max() function. Test Plan: Build on Linux, OS X and Windows Reviewers: gcampax, simonmar, austin, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2421 >--------------------------------------------------------------- d068220f4249cce66ed5b6cc5504f79e7c8c0184 compiler/simplStg/UnariseStg.hs | 16 ++++++++-------- compiler/stgSyn/CoreToStg.hs | 2 +- rts/sm/CNF.c | 19 +++++-------------- 3 files changed, 14 insertions(+), 23 deletions(-) diff --git a/compiler/simplStg/UnariseStg.hs b/compiler/simplStg/UnariseStg.hs index af2928d..24c0ce8 100644 --- a/compiler/simplStg/UnariseStg.hs +++ b/compiler/simplStg/UnariseStg.hs @@ -241,10 +241,10 @@ instance Outputable UnariseVal where -- | Extend the environment, checking the UnariseEnv invariant. extendRho :: UnariseEnv -> Id -> UnariseVal -> UnariseEnv extendRho rho x (MultiVal args) - = ASSERT (all (isNvUnaryType . stgArgType) args) + = ASSERT(all (isNvUnaryType . stgArgType) args) extendVarEnv rho x (MultiVal args) extendRho rho x (UnaryVal val) - = ASSERT (isNvUnaryType (stgArgType val)) + = ASSERT(isNvUnaryType (stgArgType val)) extendVarEnv rho x (UnaryVal val) -------------------------------------------------------------------------------- @@ -273,7 +273,7 @@ unariseRhs rho (StgRhsClosure ccs b_info fvs update_flag args expr) return (StgRhsClosure ccs b_info fvs' update_flag args1 expr') unariseRhs rho (StgRhsCon ccs con args) - = ASSERT (not (isUnboxedTupleCon con || isUnboxedSumCon con)) + = ASSERT(not (isUnboxedTupleCon con || isUnboxedSumCon con)) return (StgRhsCon ccs con (unariseConArgs rho args)) -------------------------------------------------------------------------------- @@ -356,7 +356,7 @@ unariseMulti_maybe rho dc args ty_args = Just (unariseConArgs rho args) | isUnboxedSumCon dc - , let args1 = ASSERT (isSingleton args) (unariseConArgs rho args) + , let args1 = ASSERT(isSingleton args) (unariseConArgs rho args) = Just (mkUbxSum dc ty_args args1) | otherwise @@ -374,7 +374,7 @@ elimCase rho args bndr (MultiValAlt _) [(_, bndrs, rhs)] | isUnboxedTupleBndr bndr = mapTupleIdBinders bndrs args rho1 | otherwise - = ASSERT (isUnboxedSumBndr bndr) + = ASSERT(isUnboxedSumBndr bndr) if null bndrs then rho1 else mapSumIdBinders bndrs args rho1 @@ -480,7 +480,7 @@ mapTupleIdBinders -> UnariseEnv -> UnariseEnv mapTupleIdBinders ids args0 rho0 - = ASSERT (not (any (isVoidTy . stgArgType) args0)) + = ASSERT(not (any (isVoidTy . stgArgType) args0)) let ids_unarised :: [(Id, RepType)] ids_unarised = map (\id -> (id, repType (idType id))) ids @@ -498,7 +498,7 @@ mapTupleIdBinders ids args0 rho0 | isMultiRep x_rep = extendRho rho x (MultiVal x_args) | otherwise - = ASSERT (x_args `lengthIs` 1) + = ASSERT(x_args `lengthIs` 1) extendRho rho x (UnaryVal (head x_args)) in map_ids rho' xs args' @@ -514,7 +514,7 @@ mapSumIdBinders -> UnariseEnv mapSumIdBinders [id] args rho0 - = ASSERT (not (any (isVoidTy . stgArgType) args)) + = ASSERT(not (any (isVoidTy . stgArgType) args)) let arg_slots = concatMap (repTypeSlots . repType . stgArgType) args id_slots = repTypeSlots (repType (idType id)) diff --git a/compiler/stgSyn/CoreToStg.hs b/compiler/stgSyn/CoreToStg.hs index cba139a..d130b74 100644 --- a/compiler/stgSyn/CoreToStg.hs +++ b/compiler/stgSyn/CoreToStg.hs @@ -774,7 +774,7 @@ mkStgRhs' con_updateable rhs_fvs bndr binder_info rhs | StgConApp con args _ <- unticked_rhs , not (con_updateable con args) = -- CorePrep does this right, but just to make sure - ASSERT (not (isUnboxedTupleCon con || isUnboxedSumCon con)) + ASSERT(not (isUnboxedTupleCon con || isUnboxedSumCon con)) StgRhsCon noCCS con args | otherwise = StgRhsClosure noCCS binder_info diff --git a/rts/sm/CNF.c b/rts/sm/CNF.c index 3c681c2..4689b46 100644 --- a/rts/sm/CNF.c +++ b/rts/sm/CNF.c @@ -29,8 +29,6 @@ #ifdef HAVE_LIMITS_H #include #endif -#include -#include /** * Note [Compact Normal Forms] @@ -433,14 +431,6 @@ block_is_full (StgCompactNFDataBlock *block) return (bd->free + sizeW > top); } -static inline StgWord max(StgWord a, StgWord b) -{ - if (a > b) - return a; - else - return b; -} - static rtsBool allocate_loop (Capability *cap, StgCompactNFData *str, @@ -471,7 +461,7 @@ allocate_loop (Capability *cap, } } - next_size = max(str->autoBlockW * sizeof(StgWord), + next_size = stg_max(str->autoBlockW * sizeof(StgWord), BLOCK_ROUND_UP(sizeW * sizeof(StgWord))); if (next_size >= BLOCKS_PER_MBLOCK * BLOCK_SIZE) next_size = BLOCKS_PER_MBLOCK * BLOCK_SIZE; @@ -977,7 +967,7 @@ spew_failing_pointer(StgWord *fixup_table, uint32_t count, StgWord address) bdescr *bd; StgWord size; - debugBelch("Failed to adjust 0x%lx. Block dump follows...\n", + debugBelch("Failed to adjust 0x%" FMT_HexWord ". Block dump follows...\n", address); for (i = 0; i < count; i++) { @@ -988,8 +978,9 @@ spew_failing_pointer(StgWord *fixup_table, uint32_t count, StgWord address) bd = Bdescr((P_)block); size = (W_)bd->free - (W_)bd->start; - debugBelch("%d: was 0x%lx-0x%lx, now 0x%lx-0x%lx\n", i, - key, key+size, value, value+size); + debugBelch("%" FMT_Word32 ": was 0x%" FMT_HexWord "-0x%" FMT_HexWord + ", now 0x%" FMT_HexWord "-0x%" FMT_HexWord "\n", i, key, + key+size, value, value+size); } } #endif From git at git.haskell.org Sun Jul 24 23:38:33 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 24 Jul 2016 23:38:33 +0000 (UTC) Subject: [commit: ghc] master: Testsuite: fix T10482a (4036c1f) Message-ID: <20160724233833.0595E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4036c1f110578f8e2813295116b79a5a06e2bf59/ghc >--------------------------------------------------------------- commit 4036c1f110578f8e2813295116b79a5a06e2bf59 Author: Thomas Miedema Date: Mon Jul 25 01:36:20 2016 +0200 Testsuite: fix T10482a >--------------------------------------------------------------- 4036c1f110578f8e2813295116b79a5a06e2bf59 testsuite/tests/stranal/should_compile/all.T | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/testsuite/tests/stranal/should_compile/all.T b/testsuite/tests/stranal/should_compile/all.T index 97c3a6f..0f57c3b 100644 --- a/testsuite/tests/stranal/should_compile/all.T +++ b/testsuite/tests/stranal/should_compile/all.T @@ -37,8 +37,10 @@ test('T8743', [ extra_clean(['T8743.o-boot', 'T8743a.hi', 'T8743a.o', 'T8743.hi- # The intent here is to check that $wfoo has type # $wfoo :: Int# -> Int# -> Int # with two unboxed args. See Trac #10482 for background -test('T10482', [ grepCoreString(r'wfoo.*Int') ], compile, ['-dppr-cols=200 -ddump-simpl']) -test('T10482a', [ grepCoreString(r'wf.*Int') ], compile, ['-dppr-cols=200 -ddump-simpl']) +# +# Set -dppr-cols to ensure output doesn't wrap +test('T10482', [ grepCoreString(r'wfoo.*Int#') ], compile, ['-dppr-cols=200 -ddump-simpl']) +test('T10482a', [ grepCoreString(r'wf.*Int#') ], compile, ['-dppr-cols=200 -ddump-simpl']) test('T9208', when(compiler_debugged(), expect_broken(9208)), compile, ['']) # T9208 fails (and should do so) if you have assertion checking on in the compiler From git at git.haskell.org Mon Jul 25 14:57:53 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 25 Jul 2016 14:57:53 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Kill some unnecessary varSetElems (7bfc8c0) Message-ID: <20160725145753.3E74F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/7bfc8c039bd4f4ac82f919e6229660013afdec42/ghc >--------------------------------------------------------------- commit 7bfc8c039bd4f4ac82f919e6229660013afdec42 Author: Bartosz Nitka Date: Fri Apr 15 04:46:21 2016 -0700 Kill some unnecessary varSetElems When you do `varSetElems (tyCoVarsOfType x)` it's equivalent to `tyCoVarsOfTypeList x`. Why? If you look at the implementation: ``` tyCoVarsOfTypeList ty = runFVList $ tyCoVarsOfTypeAcc ty tyCoVarsOfType ty = runFVSet $ tyCoVarsOfTypeAcc ty ``` they use the same helper function. The helper function returns a deterministically ordered list and a set. The only difference between the two is which part of the result they take. It is redundant to take the set and then immediately convert it to a list. This helps with determinism and we eventually want to replace the uses of `varSetElems` with functions that don't leak the values of uniques. This change gets rid of some instances that are easy to kill. I chose not to annotate every place where I got rid of `varSetElems` with a comment about non-determinism, because once we get rid of `varSetElems` it will not be possible to do the wrong thing. Test Plan: ./validate Reviewers: goldfire, austin, simonmar, bgamari, simonpj Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2115 GHC Trac Issues: #4012 (cherry picked from commit 928d74733975fe4677e2b558d031779f58a0883c) >--------------------------------------------------------------- 7bfc8c039bd4f4ac82f919e6229660013afdec42 compiler/coreSyn/CoreFVs.hs | 40 ++++++++++++++++++++++++++++++++++++---- compiler/coreSyn/CoreLint.hs | 4 ++-- compiler/deSugar/Desugar.hs | 6 ++++-- compiler/deSugar/DsArrows.hs | 2 +- compiler/deSugar/DsBinds.hs | 4 +++- compiler/main/InteractiveEval.hs | 7 +++---- compiler/main/TidyPgm.hs | 2 +- compiler/specialise/Rules.hs | 4 ++-- compiler/typecheck/TcErrors.hs | 2 +- compiler/typecheck/TcInteract.hs | 2 +- compiler/typecheck/TcSimplify.hs | 5 +++-- compiler/typecheck/TcTyDecls.hs | 4 ++-- compiler/typecheck/TcValidity.hs | 5 +++-- 13 files changed, 62 insertions(+), 25 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 7bfc8c039bd4f4ac82f919e6229660013afdec42 From git at git.haskell.org Mon Jul 25 14:57:55 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 25 Jul 2016 14:57:55 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Remove some gratitious varSetElemsWellScoped (a082cd3) Message-ID: <20160725145755.DC3CC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/a082cd3493bd53d52151c7f5faa34424f6c2f695/ghc >--------------------------------------------------------------- commit a082cd3493bd53d52151c7f5faa34424f6c2f695 Author: Bartosz Nitka Date: Fri Apr 15 04:48:45 2016 -0700 Remove some gratitious varSetElemsWellScoped Summary: `varSetElemsWellScoped` uses `varSetElems` under the hood which introduces unnecessary nondeterminism. This does the same thing, possibly cheaper, while preserving determinism. Test Plan: ./validate Reviewers: simonmar, goldfire, austin, bgamari, simonpj Reviewed By: simonpj Subscribers: thomie, RyanGlScott Differential Revision: https://phabricator.haskell.org/D2116 GHC Trac Issues: #4012 (cherry picked from commit 31e49746a5f2193e3a2161ea6e279e95b9068048) >--------------------------------------------------------------- a082cd3493bd53d52151c7f5faa34424f6c2f695 compiler/typecheck/TcClassDcl.hs | 13 ++++++------- compiler/typecheck/TcDeriv.hs | 8 ++++---- compiler/typecheck/TcGenGenerics.hs | 12 ++++++------ 3 files changed, 16 insertions(+), 17 deletions(-) diff --git a/compiler/typecheck/TcClassDcl.hs b/compiler/typecheck/TcClassDcl.hs index 602ef64..48b0e56 100644 --- a/compiler/typecheck/TcClassDcl.hs +++ b/compiler/typecheck/TcClassDcl.hs @@ -26,7 +26,7 @@ import TcBinds import TcUnify import TcHsType import TcMType -import Type ( getClassPredTys_maybe, varSetElemsWellScoped, piResultTys ) +import Type ( getClassPredTys_maybe, piResultTys ) import TcType import TcRnMonad import BuildTyCl( TcMethInfo ) @@ -41,7 +41,6 @@ import NameEnv import NameSet import Var import VarEnv -import VarSet import Outputable import SrcLoc import TyCon @@ -53,7 +52,7 @@ import BooleanFormula import Util import Control.Monad -import Data.List ( mapAccumL ) +import Data.List ( mapAccumL, partition ) {- Dictionary handling @@ -454,10 +453,10 @@ tcATDefault emit_warn loc inst_subst defined_ats (ATI fam_tc defs) = do { let (subst', pat_tys') = mapAccumL subst_tv inst_subst (tyConTyVars fam_tc) rhs' = substTyUnchecked subst' rhs_ty - tcv_set' = tyCoVarsOfTypes pat_tys' - (tv_set', cv_set') = partitionVarSet isTyVar tcv_set' - tvs' = varSetElemsWellScoped tv_set' - cvs' = varSetElemsWellScoped cv_set' + tcv' = tyCoVarsOfTypesList pat_tys' + (tv', cv') = partition isTyVar tcv' + tvs' = toposortTyVars tv' + cvs' = toposortTyVars cv' ; rep_tc_name <- newFamInstTyConName (L loc (tyConName fam_tc)) pat_tys' ; let axiom = mkSingleCoAxiom Nominal rep_tc_name tvs' cvs' fam_tc pat_tys' rhs' diff --git a/compiler/typecheck/TcDeriv.hs b/compiler/typecheck/TcDeriv.hs index 9b9a22b..03f593c 100644 --- a/compiler/typecheck/TcDeriv.hs +++ b/compiler/typecheck/TcDeriv.hs @@ -1586,7 +1586,7 @@ mkNewTypeEqn dflags overlap_mode tvs case mtheta of Just theta -> return $ GivenTheta $ DS { ds_loc = loc - , ds_name = dfun_name, ds_tvs = varSetElemsWellScoped dfun_tvs + , ds_name = dfun_name, ds_tvs = dfun_tvs , ds_cls = cls, ds_tys = inst_tys , ds_tc = rep_tycon , ds_theta = theta @@ -1594,7 +1594,7 @@ mkNewTypeEqn dflags overlap_mode tvs , ds_newtype = Just rep_inst_ty } Nothing -> return $ InferTheta $ DS { ds_loc = loc - , ds_name = dfun_name, ds_tvs = varSetElemsWellScoped dfun_tvs + , ds_name = dfun_name, ds_tvs = dfun_tvs , ds_cls = cls, ds_tys = inst_tys , ds_tc = rep_tycon , ds_theta = all_preds @@ -1689,7 +1689,7 @@ mkNewTypeEqn dflags overlap_mode tvs -- Next we figure out what superclass dictionaries to use -- See Note [Newtype deriving superclasses] above cls_tyvars = classTyVars cls - dfun_tvs = tyCoVarsOfTypes inst_tys + dfun_tvs = tyCoVarsOfTypesWellScoped inst_tys inst_ty = mkTyConApp tycon tc_args inst_tys = cls_tys ++ [inst_ty] sc_theta = mkThetaOrigin DerivOrigin TypeLevel $ @@ -1701,7 +1701,7 @@ mkNewTypeEqn dflags overlap_mode tvs -- newtype type; precisely the constraints required for the -- calls to coercible that we are going to generate. coercible_constraints = - [ let (Pair t1 t2) = mkCoerceClassMethEqn cls (varSetElemsWellScoped dfun_tvs) inst_tys rep_inst_ty meth + [ let (Pair t1 t2) = mkCoerceClassMethEqn cls dfun_tvs inst_tys rep_inst_ty meth in mkPredOrigin (DerivOriginCoerce meth t1 t2) TypeLevel (mkReprPrimEqPred t1 t2) | meth <- classMethods cls ] diff --git a/compiler/typecheck/TcGenGenerics.hs b/compiler/typecheck/TcGenGenerics.hs index 03b4d65..ebe9303 100644 --- a/compiler/typecheck/TcGenGenerics.hs +++ b/compiler/typecheck/TcGenGenerics.hs @@ -37,13 +37,13 @@ import ErrUtils( Validity(..), andValid ) import SrcLoc import Bag import VarEnv -import VarSet (elemVarSet, partitionVarSet) +import VarSet (elemVarSet) import Outputable import FastString import Util import Control.Monad (mplus) -import Data.List (zip4) +import Data.List (zip4, partition) import Data.Maybe (isJust) #include "HsVersions.h" @@ -395,10 +395,10 @@ tc_mkRepFamInsts gk tycon inst_ty mod = in_scope = mkInScopeSet (tyCoVarsOfType inst_ty) subst = mkTvSubst in_scope env repTy' = substTy subst repTy - tcv_set' = tyCoVarsOfType inst_ty - (tv_set', cv_set') = partitionVarSet isTyVar tcv_set' - tvs' = varSetElemsWellScoped tv_set' - cvs' = varSetElemsWellScoped cv_set' + tcv' = tyCoVarsOfTypeList inst_ty + (tv', cv') = partition isTyVar tcv' + tvs' = toposortTyVars tv' + cvs' = toposortTyVars cv' axiom = mkSingleCoAxiom Nominal rep_name tvs' cvs' fam_tc [inst_ty] repTy' From git at git.haskell.org Mon Jul 25 14:57:58 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 25 Jul 2016 14:57:58 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Kill unnecessary varSetElemsWellScoped in deriveTyData (b874bc9) Message-ID: <20160725145758.875733A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/b874bc9b11eb1961a04200dace1c530b6fe525ce/ghc >--------------------------------------------------------------- commit b874bc9b11eb1961a04200dace1c530b6fe525ce Author: Bartosz Nitka Date: Wed Apr 20 08:54:10 2016 -0700 Kill unnecessary varSetElemsWellScoped in deriveTyData varSetElemsWellScoped introduces unnecessary non-determinism and it's possible to do the same thing deterministically for the same price. Test Plan: ./validate Reviewers: austin, simonmar, bgamari, simonpj Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2124 GHC Trac Issues: #4012 (cherry picked from commit 687c77808b82e8cf8c77fba2c0ed2fe003c907cf) >--------------------------------------------------------------- b874bc9b11eb1961a04200dace1c530b6fe525ce compiler/typecheck/TcDeriv.hs | 9 ++++++--- 1 file changed, 6 insertions(+), 3 deletions(-) diff --git a/compiler/typecheck/TcDeriv.hs b/compiler/typecheck/TcDeriv.hs index 03f593c..39c9bfc 100644 --- a/compiler/typecheck/TcDeriv.hs +++ b/compiler/typecheck/TcDeriv.hs @@ -63,6 +63,7 @@ import Outputable import FastString import Bag import Pair +import FV (runFVList, unionFV, someVars) import qualified GHC.LanguageExtensions as LangExt import Control.Monad @@ -651,9 +652,11 @@ deriveTyData tvs tc tc_args deriv_pred mb_match = tcUnifyTy inst_ty_kind cls_arg_kind Just kind_subst = mb_match - all_tkvs = varSetElemsWellScoped $ - mkVarSet deriv_tvs `unionVarSet` - tyCoVarsOfTypes tc_args_to_keep + all_tkvs = toposortTyVars $ + runFVList $ unionFV + (tyCoVarsOfTypesAcc tc_args_to_keep) + (someVars deriv_tvs) + unmapped_tkvs = filter (`notElemTCvSubst` kind_subst) all_tkvs (subst, tkvs) = mapAccumL substTyVarBndr kind_subst unmapped_tkvs From git at git.haskell.org Mon Jul 25 14:58:01 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 25 Jul 2016 14:58:01 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Rename FV related functions (28c4a84) Message-ID: <20160725145801.443B23A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/28c4a844d7b5aac2114827f8237ba8f918588ab9/ghc >--------------------------------------------------------------- commit 28c4a844d7b5aac2114827f8237ba8f918588ab9 Author: Bartosz Nitka Date: Wed Apr 20 09:51:05 2016 -0700 Rename FV related functions This is from Simon's suggestion: * `tyCoVarsOfTypesAcc` is a terrible name for a function with a perfectly decent type `[Type] -> FV`. Maybe `tyCoFVsOfTypes`? Similarly others * `runFVList` is also terrible, but also has a decent type. Maybe just `fvVarList` (and `fvVarSet` for `runFVSet`). * `someVars` could be `mkFVs :: [Var] -> FV`. (cherry picked from commit 2e33320a24e5a7b837b4c217f95ca428cd6e5482) >--------------------------------------------------------------- 28c4a844d7b5aac2114827f8237ba8f918588ab9 compiler/coreSyn/CoreFVs.hs | 150 ++++++++++++++++++++-------------------- compiler/coreSyn/CoreSubst.hs | 2 +- compiler/simplCore/SetLevels.hs | 4 +- compiler/typecheck/TcDeriv.hs | 10 +-- compiler/typecheck/TcRnTypes.hs | 32 +++++---- compiler/typecheck/TcType.hs | 10 +-- compiler/types/Coercion.hs | 2 +- compiler/types/TyCoRep.hs | 144 ++++++++++++++++++++------------------ compiler/types/Type.hs | 2 +- compiler/utils/FV.hs | 69 +++++++++--------- 10 files changed, 220 insertions(+), 205 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 28c4a844d7b5aac2114827f8237ba8f918588ab9 From git at git.haskell.org Mon Jul 25 14:58:03 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 25 Jul 2016 14:58:03 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Remove mysterious varSetElemsWellScoped in tidyFreeTyCoVars (3a6888e) Message-ID: <20160725145803.E23173A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/3a6888e6ee523eafe5867a2891f6cfd8d63c34fa/ghc >--------------------------------------------------------------- commit 3a6888e6ee523eafe5867a2891f6cfd8d63c34fa Author: Bartosz Nitka Date: Thu Apr 21 03:49:30 2016 -0700 Remove mysterious varSetElemsWellScoped in tidyFreeTyCoVars Richard isn't sure why it's there and removing it didn't change anything. (cherry picked from commit 7c6585af9e9c83f2d87cb9728d9b8cb456e3d543) >--------------------------------------------------------------- 3a6888e6ee523eafe5867a2891f6cfd8d63c34fa compiler/types/TyCoRep.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/types/TyCoRep.hs b/compiler/types/TyCoRep.hs index fe9a746..2295cac 100644 --- a/compiler/types/TyCoRep.hs +++ b/compiler/types/TyCoRep.hs @@ -128,7 +128,7 @@ import {-# SOURCE #-} DataCon( dataConTyCon, dataConFullSig , dataConUnivTyBinders, dataConExTyBinders , DataCon, filterEqSpec ) import {-# SOURCE #-} Type( isPredTy, isCoercionTy, mkAppTy - , tyCoVarsOfTypesWellScoped, varSetElemsWellScoped + , tyCoVarsOfTypesWellScoped , partitionInvisibles, coreView, typeKind , eqType ) -- Transitively pulls in a LOT of stuff, better to break the loop @@ -3046,7 +3046,7 @@ tidyFreeTyCoVars :: TidyEnv -> TyCoVarSet -> TidyEnv -- ^ Add the free 'TyVar's to the env in tidy form, -- so that we can tidy the type they are free in tidyFreeTyCoVars (full_occ_env, var_env) tyvars - = fst (tidyOpenTyCoVars (full_occ_env, var_env) (varSetElemsWellScoped tyvars)) + = fst (tidyOpenTyCoVars (full_occ_env, var_env) (varSetElems tyvars)) --------------- tidyOpenTyCoVars :: TidyEnv -> [TyCoVar] -> (TidyEnv, [TyCoVar]) From git at git.haskell.org Mon Jul 25 14:58:06 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 25 Jul 2016 14:58:06 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Get rid of varSetElemsWellScoped in abstractFloats (085f449) Message-ID: <20160725145806.922A53A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/085f44923b163b022e3b156e732d95740be712e7/ghc >--------------------------------------------------------------- commit 085f44923b163b022e3b156e732d95740be712e7 Author: Bartosz Nitka Date: Fri Apr 22 09:47:30 2016 -0700 Get rid of varSetElemsWellScoped in abstractFloats It's possible to get rid of this use site in a local way and it introduces unneccessary nondeterminism. Test Plan: ./validate Reviewers: simonmar, goldfire, austin, bgamari, simonpj Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2122 GHC Trac Issues: #4012 (cherry picked from commit 03006f5ef2daedbbb7b0932b2c0e265f097cf2bf) >--------------------------------------------------------------- 085f44923b163b022e3b156e732d95740be712e7 compiler/coreSyn/CoreFVs.hs | 9 ++++++++- compiler/simplCore/SimplUtils.hs | 8 ++++---- compiler/types/TyCoRep.hs | 7 ++++++- compiler/types/Type.hs | 2 +- 4 files changed, 19 insertions(+), 7 deletions(-) diff --git a/compiler/coreSyn/CoreFVs.hs b/compiler/coreSyn/CoreFVs.hs index 660538c..084ed65 100644 --- a/compiler/coreSyn/CoreFVs.hs +++ b/compiler/coreSyn/CoreFVs.hs @@ -22,7 +22,7 @@ module CoreFVs ( -- * Selective free variables of expressions InterestingVarFun, exprSomeFreeVars, exprsSomeFreeVars, - exprsSomeFreeVarsList, + exprSomeFreeVarsList, exprsSomeFreeVarsList, -- * Free variables of Rules, Vars and Ids varTypeTyCoVars, @@ -155,6 +155,13 @@ exprSomeFreeVars :: InterestingVarFun -- ^ Says which 'Var's are interesting -> VarSet exprSomeFreeVars fv_cand e = fvVarSet $ filterFV fv_cand $ expr_fvs e +-- | Finds free variables in an expression selected by a predicate +-- returning a deterministically ordered list. +exprSomeFreeVarsList :: InterestingVarFun -- ^ Says which 'Var's are interesting + -> CoreExpr + -> [Var] +exprSomeFreeVarsList fv_cand e = fvVarList $ filterFV fv_cand $ expr_fvs e + -- | Finds free variables in several expressions selected by a predicate exprsSomeFreeVars :: InterestingVarFun -- Says which 'Var's are interesting -> [CoreExpr] diff --git a/compiler/simplCore/SimplUtils.hs b/compiler/simplCore/SimplUtils.hs index 266a051..a3eb357 100644 --- a/compiler/simplCore/SimplUtils.hs +++ b/compiler/simplCore/SimplUtils.hs @@ -1573,10 +1573,10 @@ abstractFloats main_tvs body_env body rhs' = CoreSubst.substExpr (text "abstract_floats2") subst rhs -- tvs_here: see Note [Which type variables to abstract over] - tvs_here = varSetElemsWellScoped $ - intersectVarSet main_tv_set $ - closeOverKinds $ - exprSomeFreeVars isTyVar rhs' + tvs_here = toposortTyVars $ + filter (`elemVarSet` main_tv_set) $ + closeOverKindsList $ + exprSomeFreeVarsList isTyVar rhs' abstract subst (Rec prs) = do { (poly_ids, poly_apps) <- mapAndUnzipM (mk_poly tvs_here) ids diff --git a/compiler/types/TyCoRep.hs b/compiler/types/TyCoRep.hs index 2295cac..7054ed5 100644 --- a/compiler/types/TyCoRep.hs +++ b/compiler/types/TyCoRep.hs @@ -64,7 +64,7 @@ module TyCoRep ( tyCoVarsOfType, tyCoVarsOfTypeDSet, tyCoVarsOfTypes, tyCoVarsOfTypesDSet, tyCoFVsBndr, tyCoFVsOfType, tyCoVarsOfTypeList, tyCoFVsOfTypes, tyCoVarsOfTypesList, - closeOverKindsDSet, closeOverKindsFV, + closeOverKindsDSet, closeOverKindsFV, closeOverKindsList, coVarsOfType, coVarsOfTypes, coVarsOfCo, coVarsOfCos, tyCoVarsOfCo, tyCoVarsOfCos, @@ -1405,6 +1405,11 @@ closeOverKindsFV tvs = mapUnionFV (tyCoFVsOfType . tyVarKind) tvs `unionFV` mkFVs tvs -- | Add the kind variables free in the kinds of the tyvars in the given set. +-- Returns a deterministically ordered list. +closeOverKindsList :: [TyVar] -> [TyVar] +closeOverKindsList tvs = fvVarList $ closeOverKindsFV tvs + +-- | Add the kind variables free in the kinds of the tyvars in the given set. -- Returns a deterministic set. closeOverKindsDSet :: DTyVarSet -> DTyVarSet closeOverKindsDSet = fvDVarSet . closeOverKindsFV . dVarSetElems diff --git a/compiler/types/Type.hs b/compiler/types/Type.hs index 774db35..36cdf06 100644 --- a/compiler/types/Type.hs +++ b/compiler/types/Type.hs @@ -120,7 +120,7 @@ module Type ( tyCoVarsOfType, tyCoVarsOfTypes, tyCoFVsOfType, tyCoVarsOfTypeDSet, coVarsOfType, - coVarsOfTypes, closeOverKinds, + coVarsOfTypes, closeOverKinds, closeOverKindsList, splitDepVarsOfType, splitDepVarsOfTypes, splitVisVarsOfType, splitVisVarsOfTypes, expandTypeSynonyms, From git at git.haskell.org Mon Jul 25 14:58:09 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 25 Jul 2016 14:58:09 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Refactor computing dependent type vars (9f00629) Message-ID: <20160725145809.4F88C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/9f0062957cf88bf627e397d64f24698b83cbff3b/ghc >--------------------------------------------------------------- commit 9f0062957cf88bf627e397d64f24698b83cbff3b Author: Simon Peyton Jones Date: Mon Apr 18 15:01:13 2016 +0100 Refactor computing dependent type vars There should be no change in behaviour here * Move splitDepVarsOfType(s) from Type to TcType * Define data type TcType.TcDepVars, document what it means, and use it where appropriate, notably in splitDepVarsOfType(s) * Use it in TcMType.quantifyTyVars and friends (cherry picked from commit 17eb2419c42c70d7436b6b8cff0cef705353bb4e) >--------------------------------------------------------------- 9f0062957cf88bf627e397d64f24698b83cbff3b compiler/typecheck/TcHsType.hs | 29 ++++++------ compiler/typecheck/TcMType.hs | 56 ++++++++++++----------- compiler/typecheck/TcPatSyn.hs | 22 ++++----- compiler/typecheck/TcSimplify.hs | 33 +++++++------- compiler/typecheck/TcType.hs | 96 ++++++++++++++++++++++++++++++++++++++++ compiler/types/Type.hs | 42 ------------------ 6 files changed, 165 insertions(+), 113 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 9f0062957cf88bf627e397d64f24698b83cbff3b From git at git.haskell.org Mon Jul 25 14:58:11 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 25 Jul 2016 14:58:11 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Fix two buglets in 17eb241 noticed by Richard (7c216d2) Message-ID: <20160725145811.EE97D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/7c216d2ab84bd5f8140952cba0a48cedfab13f7e/ghc >--------------------------------------------------------------- commit 7c216d2ab84bd5f8140952cba0a48cedfab13f7e Author: Simon Peyton Jones Date: Wed Apr 20 15:56:44 2016 +0100 Fix two buglets in 17eb241 noticed by Richard These are corner cases in 17eb241 Refactor computing dependent type vars and I couldn't even come up with a test case * In TcSimplify.simplifyInfer, in the promotion step, be sure to promote kind variables as well as type variables. * In TcType.spiltDepVarsOfTypes, the CoercionTy case, be sure to get the free coercion variables too. (cherry picked from commit 61191deee82d315a9279f11615e379d7c231dc51) >--------------------------------------------------------------- 7c216d2ab84bd5f8140952cba0a48cedfab13f7e compiler/typecheck/TcSimplify.hs | 29 +++++++++++++++-------------- compiler/typecheck/TcType.hs | 7 +------ 2 files changed, 16 insertions(+), 20 deletions(-) diff --git a/compiler/typecheck/TcSimplify.hs b/compiler/typecheck/TcSimplify.hs index 70de14c..853976c 100644 --- a/compiler/typecheck/TcSimplify.hs +++ b/compiler/typecheck/TcSimplify.hs @@ -604,10 +604,10 @@ simplifyInfer rhs_tclvl apply_mr sigs name_taus wanteds -- Decide what type variables and constraints to quantify ; zonked_taus <- mapM (TcM.zonkTcType . snd) name_taus - ; let zonked_tau_tkvs = splitDepVarsOfTypes zonked_taus + ; let zonked_tau_dvs = splitDepVarsOfTypes zonked_taus ; (qtvs, bound_theta) <- decideQuantification apply_mr sigs name_taus - quant_pred_candidates zonked_tau_tkvs + quant_pred_candidates zonked_tau_dvs -- Promote any type variables that are free in the inferred type -- of the function: @@ -621,24 +621,25 @@ simplifyInfer rhs_tclvl apply_mr sigs name_taus wanteds -- we don't quantify over beta (since it is fixed by envt) -- so we must promote it! The inferred type is just -- f :: beta -> beta - ; zonked_tau_tvs <- TcM.zonkTyCoVarsAndFV (dv_tvs zonked_tau_tkvs) + ; zonked_tau_tkvs <- TcM.zonkTyCoVarsAndFV $ + dv_kvs zonked_tau_dvs `unionVarSet` dv_tvs zonked_tau_dvs -- decideQuantification turned some meta tyvars into -- quantified skolems, so we have to zonk again - ; let phi_tvs = tyCoVarsOfTypes bound_theta - `unionVarSet` zonked_tau_tvs + ; let phi_tkvs = tyCoVarsOfTypes bound_theta -- Already zonked + `unionVarSet` zonked_tau_tkvs + promote_tkvs = closeOverKinds phi_tkvs `delVarSetList` qtvs - promote_tvs = closeOverKinds phi_tvs `delVarSetList` qtvs - ; MASSERT2( closeOverKinds promote_tvs `subVarSet` promote_tvs - , ppr phi_tvs $$ - ppr (closeOverKinds phi_tvs) $$ - ppr promote_tvs $$ - ppr (closeOverKinds promote_tvs) ) + ; MASSERT2( closeOverKinds promote_tkvs `subVarSet` promote_tkvs + , ppr phi_tkvs $$ + ppr (closeOverKinds phi_tkvs) $$ + ppr promote_tkvs $$ + ppr (closeOverKinds promote_tkvs) ) -- we really don't want a type to be promoted when its kind isn't! -- promoteTyVar ignores coercion variables ; outer_tclvl <- TcM.getTcLevel - ; mapM_ (promoteTyVar outer_tclvl) (varSetElems promote_tvs) + ; mapM_ (promoteTyVar outer_tclvl) (varSetElems promote_tkvs) -- Emit an implication constraint for the -- remaining constraints from the RHS @@ -664,8 +665,8 @@ simplifyInfer rhs_tclvl apply_mr sigs name_taus wanteds ; traceTc "} simplifyInfer/produced residual implication for quantification" $ vcat [ text "quant_pred_candidates =" <+> ppr quant_pred_candidates , text "zonked_taus" <+> ppr zonked_taus - , text "zonked_tau_tvs=" <+> ppr zonked_tau_tvs - , text "promote_tvs=" <+> ppr promote_tvs + , text "zonked_tau_dvs=" <+> ppr zonked_tau_dvs + , text "promote_tvs=" <+> ppr promote_tkvs , text "bound_theta =" <+> ppr bound_theta , text "qtvs =" <+> ppr qtvs , text "implic =" <+> ppr implic ] diff --git a/compiler/typecheck/TcType.hs b/compiler/typecheck/TcType.hs index 4f7d861..1e3f72b 100644 --- a/compiler/typecheck/TcType.hs +++ b/compiler/typecheck/TcType.hs @@ -931,12 +931,7 @@ split_dep_vars = go go (LitTy {}) = mempty go (CastTy ty co) = go ty `mappend` Pair (tyCoVarsOfCo co) emptyVarSet - go (CoercionTy co) = go_co co - - go_co co = let Pair ty1 ty2 = coercionKind co in - -- co :: ty1 ~ ty2 - go ty1 `mappend` go ty2 - + go (CoercionTy co) = Pair (tyCoVarsOfCo co) emptyVarSet isTouchableOrFmv ctxt_tclvl tv = ASSERT2( isTcTyVar tv, ppr tv ) From git at git.haskell.org Mon Jul 25 14:58:14 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 25 Jul 2016 14:58:14 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Make benign non-determinism in pretty-printing more obvious (cc02156) Message-ID: <20160725145814.98B133A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/cc02156b859159eff7d86043f67826c17f2bd170/ghc >--------------------------------------------------------------- commit cc02156b859159eff7d86043f67826c17f2bd170 Author: Bartosz Nitka Date: Mon Apr 18 07:32:03 2016 -0700 Make benign non-determinism in pretty-printing more obvious This change takes us one step closer to being able to remove `varSetElemsWellScoped`. The end goal is to make every source of non-determinism obvious at the source level, so that when we achieve determinism it doesn't get broken accidentally. Test Plan: compile GHC Reviewers: simonmar, goldfire, simonpj, austin, bgamari Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2123 GHC Trac Issues: #4012 (cherry picked from commit 0f96686b10fd36d479a54c71a6e1753193e85347) >--------------------------------------------------------------- cc02156b859159eff7d86043f67826c17f2bd170 compiler/basicTypes/VarSet.hs | 21 ++++++++++++++++++++- compiler/typecheck/FamInst.hs | 4 ++-- compiler/typecheck/FunDeps.hs | 6 +++--- compiler/utils/UniqFM.hs | 20 +++++++++++++++++++- 4 files changed, 44 insertions(+), 7 deletions(-) diff --git a/compiler/basicTypes/VarSet.hs b/compiler/basicTypes/VarSet.hs index 1cd9e21..8ece555 100644 --- a/compiler/basicTypes/VarSet.hs +++ b/compiler/basicTypes/VarSet.hs @@ -21,6 +21,7 @@ module VarSet ( lookupVarSet, lookupVarSetByName, mapVarSet, sizeVarSet, seqVarSet, elemVarSetByKey, partitionVarSet, + pluralVarSet, pprVarSet, -- * Deterministic Var set types DVarSet, DIdSet, DTyVarSet, DTyCoVarSet, @@ -45,8 +46,9 @@ import Unique import Name ( Name ) import UniqSet import UniqDSet -import UniqFM( disjointUFM ) +import UniqFM( disjointUFM, pluralUFM, pprUFM ) import UniqDFM( disjointUDFM ) +import Outputable (SDoc) -- | A non-deterministic set of variables. -- See Note [Deterministic UniqFM] in UniqDFM for explanation why it's not @@ -169,6 +171,23 @@ transCloVarSet fn seeds seqVarSet :: VarSet -> () seqVarSet s = sizeVarSet s `seq` () +-- | Determines the pluralisation suffix appropriate for the length of a set +-- in the same way that plural from Outputable does for lists. +pluralVarSet :: VarSet -> SDoc +pluralVarSet = pluralUFM + +-- | Pretty-print a non-deterministic set. +-- The order of variables is non-deterministic and for pretty-printing that +-- shouldn't be a problem. +-- Having this function helps contain the non-determinism created with +-- varSetElems. +pprVarSet :: ([Var] -> SDoc) -- ^ The pretty printing function to use on the + -- elements + -> VarSet -- ^ The things to be pretty printed + -> SDoc -- ^ 'SDoc' where the things have been pretty + -- printed +pprVarSet = pprUFM + -- Deterministic VarSet -- See Note [Deterministic UniqFM] in UniqDFM for explanation why we need -- DVarSet. diff --git a/compiler/typecheck/FamInst.hs b/compiler/typecheck/FamInst.hs index 2ff256d..1d9e1ce 100644 --- a/compiler/typecheck/FamInst.hs +++ b/compiler/typecheck/FamInst.hs @@ -562,12 +562,12 @@ unusedInjectiveVarsErr (Pair invis_vars vis_vars) errorBuilder tyfamEqn = errorBuilder (injectivityErrorHerald True $$ msg) [tyfamEqn] where - tvs = varSetElemsWellScoped (invis_vars `unionVarSet` vis_vars) + tvs = invis_vars `unionVarSet` vis_vars has_types = not $ isEmptyVarSet vis_vars has_kinds = not $ isEmptyVarSet invis_vars doc = sep [ what <+> text "variable" <> - plural tvs <+> pprQuotedList tvs + pluralVarSet tvs <+> pprVarSet (pprQuotedList . toposortTyVars) tvs , text "cannot be inferred from the right-hand side." ] what = case (has_types, has_kinds) of (True, True) -> text "Type and kind" diff --git a/compiler/typecheck/FunDeps.hs b/compiler/typecheck/FunDeps.hs index 87fb4ff..776a9f1 100644 --- a/compiler/typecheck/FunDeps.hs +++ b/compiler/typecheck/FunDeps.hs @@ -387,7 +387,7 @@ checkInstCoverage be_liberal clas theta inst_taus liberal_undet_tvs = (`minusVarSet` closed_ls_tvs) <$> rs_tvs conserv_undet_tvs = (`minusVarSet` ls_tvs) <$> rs_tvs - undet_list = varSetElemsWellScoped (fold undetermined_tvs) + undet_set = fold undetermined_tvs msg = vcat [ -- text "ls_tvs" <+> ppr ls_tvs -- , text "closed ls_tvs" <+> ppr (closeOverKinds ls_tvs) @@ -407,8 +407,8 @@ checkInstCoverage be_liberal clas theta inst_taus else text "do not jointly") <+> text "determine rhs type"<>plural rs <+> pprQuotedList rs ] - , text "Un-determined variable" <> plural undet_list <> colon - <+> pprWithCommas ppr undet_list + , text "Un-determined variable" <> pluralVarSet undet_set <> colon + <+> pprVarSet (pprWithCommas ppr) undet_set , ppWhen (isEmptyVarSet $ pSnd undetermined_tvs) $ text "(Use -fprint-explicit-kinds to see the kind variables in the types)" , ppWhen (not be_liberal && diff --git a/compiler/utils/UniqFM.hs b/compiler/utils/UniqFM.hs index e261df7..4a5f14f 100644 --- a/compiler/utils/UniqFM.hs +++ b/compiler/utils/UniqFM.hs @@ -67,7 +67,7 @@ module UniqFM ( eltsUFM, keysUFM, splitUFM, ufmToSet_Directly, ufmToList, - joinUFM, pprUniqFM + joinUFM, pprUniqFM, pprUFM, pluralUFM ) where import Unique ( Uniquable(..), Unique, getKey ) @@ -327,3 +327,21 @@ pprUniqFM ppr_elt ufm = brackets $ fsep $ punctuate comma $ [ ppr uq <+> text ":->" <+> ppr_elt elt | (uq, elt) <- ufmToList ufm ] + +-- | Pretty-print a non-deterministic set. +-- The order of variables is non-deterministic and for pretty-printing that +-- shouldn't be a problem. +-- Having this function helps contain the non-determinism created with +-- eltsUFM. +pprUFM :: ([a] -> SDoc) -- ^ The pretty printing function to use on the elements + -> UniqFM a -- ^ The things to be pretty printed + -> SDoc -- ^ 'SDoc' where the things have been pretty + -- printed +pprUFM pp ufm = pp (eltsUFM ufm) + +-- | Determines the pluralisation suffix appropriate for the length of a set +-- in the same way that plural from Outputable does for lists. +pluralUFM :: UniqFM a -> SDoc +pluralUFM ufm + | sizeUFM ufm == 1 = empty + | otherwise = char 's' From git at git.haskell.org Mon Jul 25 14:58:17 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 25 Jul 2016 14:58:17 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Kill varSetElemsWellScoped in quantifyTyVars (f775c44) Message-ID: <20160725145817.51B3B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/f775c44ac6f22c828ed7afa60a14be08943bdef9/ghc >--------------------------------------------------------------- commit f775c44ac6f22c828ed7afa60a14be08943bdef9 Author: Bartosz Nitka Date: Tue Apr 26 05:58:24 2016 -0700 Kill varSetElemsWellScoped in quantifyTyVars varSetElemsWellScoped introduces unnecessary non-determinism in inferred type signatures. Removing this instance required changing the representation of TcDepVars to use deterministic sets. This is the last occurence of varSetElemsWellScoped, allowing me to finally remove it. Test Plan: ./validate I will update the expected outputs when commiting, some reordering of type variables in types is expected. Reviewers: goldfire, simonpj, austin, bgamari Reviewed By: simonpj Subscribers: thomie, simonmar Differential Revision: https://phabricator.haskell.org/D2135 GHC Trac Issues: #4012 (cherry picked from commit c9bcaf3165586ac214fa694e61c55eb45eb131ab) >--------------------------------------------------------------- f775c44ac6f22c828ed7afa60a14be08943bdef9 compiler/basicTypes/VarSet.hs | 11 +++- compiler/typecheck/TcHsType.hs | 2 +- compiler/typecheck/TcMType.hs | 44 +++++++++---- compiler/typecheck/TcSimplify.hs | 39 ++++++++++-- compiler/typecheck/TcType.hs | 46 +++++++++----- compiler/types/Type.hs | 13 ++-- compiler/types/Type.hs-boot | 4 +- compiler/utils/UniqDFM.hs | 16 ++++- compiler/utils/UniqDSet.hs | 8 ++- compiler/utils/UniqFM.hs | 5 +- .../tests/dependent/should_fail/T11334b.stderr | 6 +- testsuite/tests/driver/werror.stderr | 2 +- testsuite/tests/gadt/gadt13.stderr | 12 ++-- testsuite/tests/gadt/gadt7.stderr | 18 +++--- .../tests/ghci.debugger/scripts/break026.stdout | 20 +++--- testsuite/tests/ghci/scripts/T11524a.stdout | 2 +- testsuite/tests/ghci/scripts/T7587.stdout | 2 +- testsuite/tests/ghci/scripts/T7730.stdout | 4 +- testsuite/tests/ghci/scripts/T7939.stdout | 4 +- testsuite/tests/ghci/scripts/T8776.stdout | 2 +- .../indexed-types/should_compile/T3017.stderr | 2 +- .../indexed-types/should_compile/T8889.stderr | 2 +- .../tests/indexed-types/should_fail/T7354.stderr | 8 +-- .../tests/indexed-types/should_fail/T8518.stderr | 8 +-- testsuite/tests/module/mod71.stderr | 10 +-- testsuite/tests/module/mod72.stderr | 2 +- .../tests/parser/should_compile/read014.stderr | 2 +- .../tests/parser/should_fail/readFail003.stderr | 6 +- .../should_compile/ExtraConstraints3.stderr | 72 +++++++++++----------- .../partial-sigs/should_compile/NamedTyVar.stderr | 4 +- .../partial-sigs/should_compile/SkipMany.stderr | 2 +- .../partial-sigs/should_compile/T10438.stderr | 4 +- .../should_compile/UncurryNamed.stderr | 2 +- .../WarningWildcardInstantiations.stderr | 30 ++++----- .../tests/partial-sigs/should_fail/T10045.stderr | 12 ++-- .../should_fail/WildcardInstantiations.stderr | 28 ++++----- .../tests/patsyn/should_compile/T11213.stderr | 2 +- testsuite/tests/polykinds/T7438.stderr | 16 ++--- testsuite/tests/polykinds/T7524.stderr | 2 +- testsuite/tests/rename/should_fail/T2993.stderr | 2 +- .../tests/typecheck/should_compile/T10971a.stderr | 2 +- .../tests/typecheck/should_compile/tc141.stderr | 6 +- .../tests/typecheck/should_compile/tc168.stderr | 2 +- .../tests/typecheck/should_compile/tc231.stderr | 2 +- testsuite/tests/typecheck/should_fail/T5853.stderr | 24 ++++---- .../tests/typecheck/should_fail/T6018fail.stderr | 6 +- testsuite/tests/typecheck/should_fail/T7453.stderr | 18 +++--- testsuite/tests/typecheck/should_fail/T7734.stderr | 12 ++-- testsuite/tests/typecheck/should_fail/T8142.stderr | 2 +- testsuite/tests/typecheck/should_fail/T9109.stderr | 12 ++-- .../tests/typecheck/should_fail/tcfail004.stderr | 6 +- .../tests/typecheck/should_fail/tcfail033.stderr | 8 +-- .../tests/typecheck/should_fail/tcfail049.stderr | 2 +- .../tests/typecheck/should_fail/tcfail050.stderr | 2 +- .../tests/typecheck/should_fail/tcfail140.stderr | 4 +- .../tests/typecheck/should_fail/tcfail198.stderr | 8 +-- 56 files changed, 345 insertions(+), 247 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc f775c44ac6f22c828ed7afa60a14be08943bdef9 From git at git.haskell.org Mon Jul 25 14:58:19 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 25 Jul 2016 14:58:19 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Kill varSetElems in TcErrors (d0f95cf) Message-ID: <20160725145819.EB3023A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/d0f95cf9dfd94feac94a0382f0f2972c6e54d666/ghc >--------------------------------------------------------------- commit d0f95cf9dfd94feac94a0382f0f2972c6e54d666 Author: Bartosz Nitka Date: Tue Apr 26 08:47:21 2016 -0700 Kill varSetElems in TcErrors The uses of varSetElems in these places are unnecessary and while it doesn't intruduce non-determinism in the ABI the plan is to get rid of all varSetElems to get some compile time guarantees. Test Plan: ./validate Reviewers: austin, simonmar, bgamari, goldfire, simonpj Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2141 GHC Trac Issues: #4012 (cherry picked from commit 2dc5b92e070132114ea1a37f5bd82ab905ff7889) >--------------------------------------------------------------- d0f95cf9dfd94feac94a0382f0f2972c6e54d666 compiler/typecheck/TcErrors.hs | 14 ++++----- .../tests/dependent/should_fail/T11407.stderr | 2 +- .../tests/indexed-types/should_fail/T2693.stderr | 8 ++--- testsuite/tests/typecheck/should_fail/T4921.stderr | 34 +++++++++++----------- 4 files changed, 29 insertions(+), 29 deletions(-) diff --git a/compiler/typecheck/TcErrors.hs b/compiler/typecheck/TcErrors.hs index 1418a2b..96c5530 100644 --- a/compiler/typecheck/TcErrors.hs +++ b/compiler/typecheck/TcErrors.hs @@ -52,6 +52,7 @@ import StaticFlags ( opt_PprStyle_Debug ) import ListSetOps ( equivClasses ) import Maybes import qualified GHC.LanguageExtensions as LangExt +import FV ( fvVarList, unionFV ) import Control.Monad ( when ) import Data.List ( partition, mapAccumL, nub, sortBy ) @@ -175,7 +176,7 @@ report_unsolved mb_binds_var err_as_warn type_errors expr_holes type_holes wante free_tvs = tyCoVarsOfWC wanted ; traceTc "reportUnsolved (after zonking and tidying):" $ - vcat [ pprTvBndrs (varSetElems free_tvs) + vcat [ pprVarSet pprTvBndrs free_tvs , ppr wanted ] ; warn_redundant <- woptM Opt_WarnRedundantConstraints @@ -1333,8 +1334,8 @@ mkTyVarEqErr dflags ctxt report ct oriented tv1 ty2 interesting_tyvars = filter (not . isEmptyVarSet . tyCoVarsOfType . tyVarKind) $ filter isTyVar $ - varSetElems $ - tyCoVarsOfType ty1 `unionVarSet` tyCoVarsOfType ty2 + fvVarList $ + tyCoFVsOfType ty1 `unionFV` tyCoFVsOfType ty2 extra3 = relevant_bindings $ ppWhen (not (null interesting_tyvars)) $ hang (text "Type variable kinds:") 2 $ @@ -2419,10 +2420,9 @@ getAmbigTkvs :: Ct -> ([Var],[Var]) getAmbigTkvs ct = partition (`elemVarSet` dep_tkv_set) ambig_tkvs where - tkv_set = tyCoVarsOfCt ct - ambig_tkv_set = filterVarSet isAmbiguousTyVar tkv_set - dep_tkv_set = tyCoVarsOfTypes (map tyVarKind (varSetElems tkv_set)) - ambig_tkvs = varSetElems ambig_tkv_set + tkvs = tyCoVarsOfCtList ct + ambig_tkvs = filter isAmbiguousTyVar tkvs + dep_tkv_set = tyCoVarsOfTypes (map tyVarKind tkvs) getSkolemInfo :: [Implication] -> TcTyVar -> ([TcTyVar], SkolemInfo) -- Get the skolem info for a type variable diff --git a/testsuite/tests/dependent/should_fail/T11407.stderr b/testsuite/tests/dependent/should_fail/T11407.stderr index b5d95bf..b07aa2b 100644 --- a/testsuite/tests/dependent/should_fail/T11407.stderr +++ b/testsuite/tests/dependent/should_fail/T11407.stderr @@ -4,5 +4,5 @@ T11407.hs:10:40: error: • In the second argument of ‘UhOh’, namely ‘(a :: x a)’ In the data instance declaration for ‘UhOh’ • Type variable kinds: - a :: k0 x :: k0 -> * + a :: k0 diff --git a/testsuite/tests/indexed-types/should_fail/T2693.stderr b/testsuite/tests/indexed-types/should_fail/T2693.stderr index 0c00711..a0ac4ea 100644 --- a/testsuite/tests/indexed-types/should_fail/T2693.stderr +++ b/testsuite/tests/indexed-types/should_fail/T2693.stderr @@ -1,7 +1,7 @@ T2693.hs:12:15: error: • Couldn't match expected type ‘(a8, b1)’ with actual type ‘TFn a6’ - The type variables ‘b1’, ‘a6’, ‘a8’ are ambiguous + The type variables ‘a6’, ‘a8’, ‘b1’ are ambiguous • In the first argument of ‘fst’, namely ‘x’ In the first argument of ‘(+)’, namely ‘fst x’ In the expression: fst x + fst x @@ -9,7 +9,7 @@ T2693.hs:12:15: error: T2693.hs:12:23: error: • Couldn't match expected type ‘(a8, b2)’ with actual type ‘TFn a7’ - The type variables ‘b2’, ‘a7’, ‘a8’ are ambiguous + The type variables ‘a7’, ‘a8’, ‘b2’ are ambiguous • In the first argument of ‘fst’, namely ‘x’ In the second argument of ‘(+)’, namely ‘fst x’ In the expression: fst x + fst x @@ -17,7 +17,7 @@ T2693.hs:12:23: error: T2693.hs:19:15: error: • Couldn't match expected type ‘(a5, b0)’ with actual type ‘TFn a2’ - The type variables ‘b0’, ‘a2’, ‘a5’ are ambiguous + The type variables ‘a2’, ‘a5’, ‘b0’ are ambiguous • In the first argument of ‘fst’, namely ‘x’ In the first argument of ‘(+)’, namely ‘fst x’ In the expression: fst x + snd x @@ -25,7 +25,7 @@ T2693.hs:19:15: error: T2693.hs:19:23: error: • Couldn't match expected type ‘(a3, a5)’ with actual type ‘TFn a4’ - The type variables ‘a3’, ‘a4’, ‘a5’ are ambiguous + The type variables ‘a4’, ‘a3’, ‘a5’ are ambiguous • In the first argument of ‘snd’, namely ‘x’ In the second argument of ‘(+)’, namely ‘snd x’ In the expression: fst x + snd x diff --git a/testsuite/tests/typecheck/should_fail/T4921.stderr b/testsuite/tests/typecheck/should_fail/T4921.stderr index 42d5a8a..8eff919 100644 --- a/testsuite/tests/typecheck/should_fail/T4921.stderr +++ b/testsuite/tests/typecheck/should_fail/T4921.stderr @@ -1,21 +1,21 @@ T4921.hs:10:9: error: - Ambiguous type variables ‘b1’, ‘a0’ arising from a use of ‘f’ - prevents the constraint ‘(C a0 b1)’ from being solved. - Relevant bindings include x :: a0 (bound at T4921.hs:10:1) - Probable fix: use a type annotation to specify what ‘b1’, ‘a0’ should be. - These potential instance exist: - instance C Int Char -- Defined at T4921.hs:7:10 - In the first argument of ‘fst’, namely ‘f’ - In the expression: fst f - In an equation for ‘x’: x = fst f + • Ambiguous type variables ‘a0’, ‘b1’ arising from a use of ‘f’ + prevents the constraint ‘(C a0 b1)’ from being solved. + Relevant bindings include x :: a0 (bound at T4921.hs:10:1) + Probable fix: use a type annotation to specify what ‘a0’, ‘b1’ should be. + These potential instance exist: + instance C Int Char -- Defined at T4921.hs:7:10 + • In the first argument of ‘fst’, namely ‘f’ + In the expression: fst f + In an equation for ‘x’: x = fst f T4921.hs:12:9: error: - Ambiguous type variable ‘b0’ arising from a use of ‘f’ - prevents the constraint ‘(C Int b0)’ from being solved. - Probable fix: use a type annotation to specify what ‘b0’ should be. - These potential instance exist: - instance C Int Char -- Defined at T4921.hs:7:10 - In the first argument of ‘fst’, namely ‘f’ - In the expression: fst f :: Int - In an equation for ‘y’: y = fst f :: Int + • Ambiguous type variable ‘b0’ arising from a use of ‘f’ + prevents the constraint ‘(C Int b0)’ from being solved. + Probable fix: use a type annotation to specify what ‘b0’ should be. + These potential instance exist: + instance C Int Char -- Defined at T4921.hs:7:10 + • In the first argument of ‘fst’, namely ‘f’ + In the expression: fst f :: Int + In an equation for ‘y’: y = fst f :: Int From git at git.haskell.org Mon Jul 25 14:58:22 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 25 Jul 2016 14:58:22 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Kill varSetElems try_tyvar_defaulting (e41984c) Message-ID: <20160725145822.963C33A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/e41984ce1be2dfaf708c7b34b1b0f93fc241402b/ghc >--------------------------------------------------------------- commit e41984ce1be2dfaf708c7b34b1b0f93fc241402b Author: Bartosz Nitka Date: Tue Apr 26 09:51:26 2016 -0700 Kill varSetElems try_tyvar_defaulting `varSetElems` introduces unnecessary nondeterminism and we can do the same thing deterministically for the same price. Test Plan: ./validate Reviewers: goldfire, austin, simonmar, bgamari, simonpj Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2143 GHC Trac Issues: #4012 (cherry picked from commit 94320e1d34d14017cc9b38226ea78205a0a76a2b) >--------------------------------------------------------------- e41984ce1be2dfaf708c7b34b1b0f93fc241402b compiler/typecheck/TcMType.hs | 7 +++++++ compiler/typecheck/TcRnTypes.hs | 37 +++++++++++++++++++++++++++---------- compiler/typecheck/TcSMonad.hs | 4 ++++ compiler/typecheck/TcSimplify.hs | 5 ++--- 4 files changed, 40 insertions(+), 13 deletions(-) diff --git a/compiler/typecheck/TcMType.hs b/compiler/typecheck/TcMType.hs index 5fefa2b..5fa0bc9 100644 --- a/compiler/typecheck/TcMType.hs +++ b/compiler/typecheck/TcMType.hs @@ -68,6 +68,7 @@ module TcMType ( tidyEvVar, tidyCt, tidySkolemInfo, skolemiseUnboundMetaTyVar, zonkTcTyVar, zonkTcTyVars, zonkTyCoVarsAndFV, zonkTcTypeAndFV, + zonkTyCoVarsAndFVList, zonkTcTypeAndSplitDepVars, zonkTcTypesAndSplitDepVars, zonkQuantifiedTyVar, zonkQuantifiedTyVarOrType, quantifyTyVars, quantifyZonkedTyVars, @@ -1202,6 +1203,12 @@ zonkTyCoVar tv | isTcTyVar tv = zonkTcTyVar tv zonkTyCoVarsAndFV :: TyCoVarSet -> TcM TyCoVarSet zonkTyCoVarsAndFV tycovars = tyCoVarsOfTypes <$> mapM zonkTyCoVar (varSetElems tycovars) +-- Takes a list of TyCoVars, zonks them and returns a +-- deterministically ordered list of their free variables. +zonkTyCoVarsAndFVList :: [TyCoVar] -> TcM [TyCoVar] +zonkTyCoVarsAndFVList tycovars = + tyCoVarsOfTypesList <$> mapM zonkTyCoVar tycovars + -- Takes a deterministic set of TyCoVars, zonks them and returns a -- deterministic set of their free variables. -- See Note [quantifyTyVars determinism]. diff --git a/compiler/typecheck/TcRnTypes.hs b/compiler/typecheck/TcRnTypes.hs index dccfd40..4755f8d 100644 --- a/compiler/typecheck/TcRnTypes.hs +++ b/compiler/typecheck/TcRnTypes.hs @@ -85,6 +85,7 @@ module TcRnTypes( andWC, unionsWC, mkSimpleWC, mkImplicWC, addInsols, addSimples, addImplics, tyCoVarsOfWC, dropDerivedWC, dropDerivedSimples, dropDerivedInsols, + tyCoVarsOfWCList, isDroppableDerivedLoc, insolubleImplic, arisesFromGivens, @@ -1608,22 +1609,38 @@ tyCoVarsOfCtsList = fvVarList . tyCoFVsOfCts tyCoFVsOfCts :: Cts -> FV tyCoFVsOfCts = foldrBag (unionFV . tyCoFVsOfCt) emptyFV +-- | Returns free variables of WantedConstraints as a non-deterministic +-- set. See Note [Deterministic FV] in FV. tyCoVarsOfWC :: WantedConstraints -> TyCoVarSet -- Only called on *zonked* things, hence no need to worry about flatten-skolems -tyCoVarsOfWC (WC { wc_simple = simple, wc_impl = implic, wc_insol = insol }) - = tyCoVarsOfCts simple `unionVarSet` - tyCoVarsOfBag tyCoVarsOfImplic implic `unionVarSet` - tyCoVarsOfCts insol +tyCoVarsOfWC = fvVarSet . tyCoFVsOfWC + +-- | Returns free variables of WantedConstraints as a deterministically +-- ordered list. See Note [Deterministic FV] in FV. +tyCoVarsOfWCList :: WantedConstraints -> [TyCoVar] +-- Only called on *zonked* things, hence no need to worry about flatten-skolems +tyCoVarsOfWCList = fvVarList . tyCoFVsOfWC -tyCoVarsOfImplic :: Implication -> TyCoVarSet +-- | Returns free variables of WantedConstraints as a composable FV +-- computation. See Note [Deterministic FV] in FV. +tyCoFVsOfWC :: WantedConstraints -> FV +-- Only called on *zonked* things, hence no need to worry about flatten-skolems +tyCoFVsOfWC (WC { wc_simple = simple, wc_impl = implic, wc_insol = insol }) + = tyCoFVsOfCts simple `unionFV` + tyCoFVsOfBag tyCoFVsOfImplic implic `unionFV` + tyCoFVsOfCts insol + +-- | Returns free variables of Implication as a composable FV computation. +-- See Note [Deterministic FV] in FV. +tyCoFVsOfImplic :: Implication -> FV -- Only called on *zonked* things, hence no need to worry about flatten-skolems -tyCoVarsOfImplic (Implic { ic_skols = skols +tyCoFVsOfImplic (Implic { ic_skols = skols , ic_given = givens, ic_wanted = wanted }) - = (tyCoVarsOfWC wanted `unionVarSet` tyCoVarsOfTypes (map evVarPred givens)) - `delVarSetList` skols + = FV.delFVs (mkVarSet skols) + (tyCoFVsOfWC wanted `unionFV` tyCoFVsOfTypes (map evVarPred givens)) -tyCoVarsOfBag :: (a -> TyCoVarSet) -> Bag a -> TyCoVarSet -tyCoVarsOfBag tvs_of = foldrBag (unionVarSet . tvs_of) emptyVarSet +tyCoFVsOfBag :: (a -> FV) -> Bag a -> FV +tyCoFVsOfBag tvs_of = foldrBag (unionFV . tvs_of) emptyFV -------------------------- dropDerivedSimples :: Cts -> Cts diff --git a/compiler/typecheck/TcSMonad.hs b/compiler/typecheck/TcSMonad.hs index ad86f7f..afd199f 100644 --- a/compiler/typecheck/TcSMonad.hs +++ b/compiler/typecheck/TcSMonad.hs @@ -93,6 +93,7 @@ module TcSMonad ( TcLevel, isTouchableMetaTyVarTcS, isFilledMetaTyVar_maybe, isFilledMetaTyVar, zonkTyCoVarsAndFV, zonkTcType, zonkTcTypes, zonkTcTyVar, zonkCo, + zonkTyCoVarsAndFVList, zonkSimples, zonkWC, -- References @@ -2756,6 +2757,9 @@ isFilledMetaTyVar tv = wrapTcS (TcM.isFilledMetaTyVar tv) zonkTyCoVarsAndFV :: TcTyCoVarSet -> TcS TcTyCoVarSet zonkTyCoVarsAndFV tvs = wrapTcS (TcM.zonkTyCoVarsAndFV tvs) +zonkTyCoVarsAndFVList :: [TcTyCoVar] -> TcS [TcTyCoVar] +zonkTyCoVarsAndFVList tvs = wrapTcS (TcM.zonkTyCoVarsAndFVList tvs) + zonkCo :: Coercion -> TcS Coercion zonkCo = wrapTcS . TcM.zonkCo diff --git a/compiler/typecheck/TcSimplify.hs b/compiler/typecheck/TcSimplify.hs index e22a5f6..39923cf 100644 --- a/compiler/typecheck/TcSimplify.hs +++ b/compiler/typecheck/TcSimplify.hs @@ -130,9 +130,8 @@ simpl_top wanteds | isEmptyWC wc = return wc | otherwise - = do { free_tvs <- TcS.zonkTyCoVarsAndFV (tyCoVarsOfWC wc) - ; let meta_tvs = varSetElems $ - filterVarSet (isTyVar <&&> isMetaTyVar) free_tvs + = do { free_tvs <- TcS.zonkTyCoVarsAndFVList (tyCoVarsOfWCList wc) + ; let meta_tvs = filter (isTyVar <&&> isMetaTyVar) free_tvs -- zonkTyCoVarsAndFV: the wc_first_go is not yet zonked -- filter isMetaTyVar: we might have runtime-skolems in GHCi, -- and we definitely don't want to try to assign to those! From git at git.haskell.org Mon Jul 25 14:58:25 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 25 Jul 2016 14:58:25 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Kill varSetElems in markNominal (cc36fe3) Message-ID: <20160725145825.3F45D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/cc36fe3c80abb99b6b9ed367f5f29cc5d2f9bb85/ghc >--------------------------------------------------------------- commit cc36fe3c80abb99b6b9ed367f5f29cc5d2f9bb85 Author: Bartosz Nitka Date: Tue Apr 26 13:04:08 2016 -0700 Kill varSetElems in markNominal varSetElems introduces unnecessary nondeterminism and it was straighforward to just get a deterministic list. Test Plan: ./validate Reviewers: austin, goldfire, bgamari, simonmar, simonpj Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2145 GHC Trac Issues: #4012 (cherry picked from commit f13a8d219fbb16ece2bede66ac47f8599a86d3e2) >--------------------------------------------------------------- cc36fe3c80abb99b6b9ed367f5f29cc5d2f9bb85 compiler/typecheck/TcTyDecls.hs | 21 +++++++++++---------- compiler/types/TyCoRep.hs | 2 +- 2 files changed, 12 insertions(+), 11 deletions(-) diff --git a/compiler/typecheck/TcTyDecls.hs b/compiler/typecheck/TcTyDecls.hs index a4b6537..53b1c08 100644 --- a/compiler/typecheck/TcTyDecls.hs +++ b/compiler/typecheck/TcTyDecls.hs @@ -31,7 +31,7 @@ module TcTyDecls( import TcRnMonad import TcEnv import TcBinds( tcRecSelBinds ) -import TyCoRep( Type(..), TyBinder(..), delBinderVar ) +import TyCoRep( Type(..), TyBinder(..), delBinderVarFV ) import TcType import TysWiredIn( unitTy ) import MkCore( rEC_SEL_ERROR_ID ) @@ -61,6 +61,7 @@ import Maybes import Data.List import Bag import FastString +import FV import Control.Monad @@ -726,21 +727,21 @@ irExTyVars orig_tvs thing = go emptyVarSet orig_tvs markNominal :: TyVarSet -- local variables -> Type -> RoleM () -markNominal lcls ty = let nvars = get_ty_vars ty `minusVarSet` lcls in - mapM_ (updateRole Nominal) (varSetElems nvars) +markNominal lcls ty = let nvars = fvVarList (FV.delFVs lcls $ get_ty_vars ty) in + mapM_ (updateRole Nominal) nvars where -- get_ty_vars gets all the tyvars (no covars!) from a type *without* -- recurring into coercions. Recall: coercions are totally ignored during -- role inference. See [Coercions in role inference] - get_ty_vars (TyVarTy tv) = unitVarSet tv - get_ty_vars (AppTy t1 t2) = get_ty_vars t1 `unionVarSet` get_ty_vars t2 - get_ty_vars (TyConApp _ tys) = foldr (unionVarSet . get_ty_vars) emptyVarSet tys + get_ty_vars (TyVarTy tv) = FV.unitFV tv + get_ty_vars (AppTy t1 t2) = get_ty_vars t1 `unionFV` get_ty_vars t2 + get_ty_vars (TyConApp _ tys) = mapUnionFV get_ty_vars tys get_ty_vars (ForAllTy bndr ty) - = get_ty_vars ty `delBinderVar` bndr - `unionVarSet` (tyCoVarsOfType $ binderType bndr) - get_ty_vars (LitTy {}) = emptyVarSet + = delBinderVarFV bndr (get_ty_vars ty) + `unionFV` (tyCoFVsOfType $ binderType bndr) + get_ty_vars (LitTy {}) = emptyFV get_ty_vars (CastTy ty _) = get_ty_vars ty - get_ty_vars (CoercionTy _) = emptyVarSet + get_ty_vars (CoercionTy _) = emptyFV -- like lookupRoles, but with Nominal tags at the end for oversaturated TyConApps lookupRolesX :: TyCon -> RoleM [Role] diff --git a/compiler/types/TyCoRep.hs b/compiler/types/TyCoRep.hs index 7054ed5..59799e1 100644 --- a/compiler/types/TyCoRep.hs +++ b/compiler/types/TyCoRep.hs @@ -45,7 +45,7 @@ module TyCoRep ( -- Functions over binders binderType, delBinderVar, isInvisibleBinder, isVisibleBinder, - isNamedBinder, isAnonBinder, + isNamedBinder, isAnonBinder, delBinderVarFV, -- Functions over coercions pickLR, From git at git.haskell.org Mon Jul 25 14:58:27 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 25 Jul 2016 14:58:27 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Kill varSetElems in injImproveEqns (8a6f976) Message-ID: <20160725145827.D9BAF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/8a6f976e93ec10774de03c4778c06dc7a86c29e7/ghc >--------------------------------------------------------------- commit 8a6f976e93ec10774de03c4778c06dc7a86c29e7 Author: Bartosz Nitka Date: Thu Apr 28 05:40:39 2016 -0700 Kill varSetElems in injImproveEqns We want to remove varSetElems at the source level because it might be a source of nondeterminism. I don't think it introduces nondeterminism here, but it's easy to do the same thing deterministically for the same price. instFlexiTcS :: [TKVar] -> TcS (TCvSubst, [TcType]) instFlexiTcS currently gives the range of the produced substitution as the second element of the tuple, but it's not used anywhere right now. If it started to be used in the code I'm modifying it would cause nondeterminism problems. Test Plan: ./validate Reviewers: austin, goldfire, bgamari, simonmar, simonpj Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2149 GHC Trac Issues: #4012 (cherry picked from commit 82538f65f48f370764691264c3c71b975fd43e16) >--------------------------------------------------------------- 8a6f976e93ec10774de03c4778c06dc7a86c29e7 compiler/typecheck/TcInteract.hs | 15 ++++++++++----- 1 file changed, 10 insertions(+), 5 deletions(-) diff --git a/compiler/typecheck/TcInteract.hs b/compiler/typecheck/TcInteract.hs index 39ad787..ca5d912 100644 --- a/compiler/typecheck/TcInteract.hs +++ b/compiler/typecheck/TcInteract.hs @@ -1491,7 +1491,7 @@ improve_top_fun_eqs fam_envs fam_tc args rhs_ty -> (a -> [Type]) -- get LHS of an axiom -> (a -> Type) -- get RHS of an axiom -> (a -> Maybe CoAxBranch) -- Just => apartness check required - -> [( [Type], TCvSubst, TyVarSet, Maybe CoAxBranch )] + -> [( [Type], TCvSubst, [TyVar], Maybe CoAxBranch )] -- Result: -- ( [arguments of a matching axiom] -- , RHS-unifying substitution @@ -1503,15 +1503,20 @@ improve_top_fun_eqs fam_envs fam_tc args rhs_ty , let ax_args = axiomLHS axiom , let ax_rhs = axiomRHS axiom , Just subst <- [tcUnifyTyWithTFs False ax_rhs rhs_ty] - , let tvs = tyCoVarsOfTypes ax_args + , let tvs = tyCoVarsOfTypesList ax_args notInSubst tv = not (tv `elemVarEnv` getTvSubstEnv subst) - unsubstTvs = filterVarSet (notInSubst <&&> isTyVar) tvs ] + unsubstTvs = filter (notInSubst <&&> isTyVar) tvs ] injImproveEqns :: [Bool] - -> ([Type], TCvSubst, TyCoVarSet, Maybe CoAxBranch) + -> ([Type], TCvSubst, [TyCoVar], Maybe CoAxBranch) -> TcS [Eqn] injImproveEqns inj_args (ax_args, theta, unsubstTvs, cabr) = do - (theta', _) <- instFlexiTcS (varSetElems unsubstTvs) + (theta', _) <- instFlexiTcS unsubstTvs + -- The use of deterministically ordered list for `unsubstTvs` + -- is not strictly necessary here, we only use the substitution + -- part of the result of instFlexiTcS. If we used the second + -- part of the tuple, which is the range of the substitution then + -- the order could be important. let subst = theta `unionTCvSubst` theta' return [ Pair arg (substTyUnchecked subst ax_arg) | case cabr of From git at git.haskell.org Mon Jul 25 14:58:30 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 25 Jul 2016 14:58:30 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Kill non-deterministic foldUFM in TrieMap and TcAppMap (64e4b88) Message-ID: <20160725145830.887FD3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/64e4b88a37980ea7d484162f05d6dce736e951b3/ghc >--------------------------------------------------------------- commit 64e4b88a37980ea7d484162f05d6dce736e951b3 Author: Bartosz Nitka Date: Wed May 4 09:22:37 2016 -0700 Kill non-deterministic foldUFM in TrieMap and TcAppMap Summary: foldUFM introduces unnecessary non-determinism that actually leads to different generated code as explained in Note [TrieMap determinism]. As we're switching from UniqFM to UniqDFM here you might be concerned about performance. There's nothing that ./validate detects. nofib reports no change in Compile Allocations, but Compile Time got better on some tests and worse on some, yielding this summary: -1 s.d. ----- -3.8% +1 s.d. ----- +5.4% Average ----- +0.7% This is not a fair comparison as the order of Uniques changes what GHC is actually doing. One benefit from making this deterministic is also that it will make the performance results more stable. Full nofib results: P108 Test Plan: ./validate, nofib Reviewers: goldfire, simonpj, simonmar, austin, bgamari Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2169 GHC Trac Issues: #4012 (cherry picked from commit ad4392c142696d5092533480a82ed65322e9d413) >--------------------------------------------------------------- 64e4b88a37980ea7d484162f05d6dce736e951b3 compiler/basicTypes/NameEnv.hs | 24 ++++ compiler/basicTypes/VarEnv.hs | 8 ++ compiler/coreSyn/TrieMap.hs | 132 ++++++++++++++++----- compiler/typecheck/TcSMonad.hs | 28 +++-- .../tests/ghc-api/apirecomp001/apirecomp001.stderr | 16 +-- .../indexed-types/should_compile/T3017.stderr | 2 +- testsuite/tests/parser/should_compile/T2245.stderr | 8 +- .../should_compile/ExtraConstraints1.stderr | 6 +- .../should_compile/ExtraConstraints3.stderr | 32 ++--- .../WarningWildcardInstantiations.stderr | 2 +- .../InstantiatedNamedWildcardsInConstraints.stderr | 2 +- .../should_fail/WildcardInstantiations.stderr | 2 +- testsuite/tests/rebindable/rebindable6.stderr | 17 +-- .../tests/typecheck/should_compile/T10971a.stderr | 6 +- testsuite/tests/typecheck/should_fail/T5300.stderr | 4 +- testsuite/tests/typecheck/should_fail/T5853.stderr | 29 +++-- .../tests/typecheck/should_fail/tcfail171.stderr | 4 +- .../tests/typecheck/should_fail/tcfail204.stderr | 9 +- .../tests/warnings/should_compile/PluralS.stderr | 7 +- 19 files changed, 220 insertions(+), 118 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 64e4b88a37980ea7d484162f05d6dce736e951b3 From git at git.haskell.org Mon Jul 25 14:58:33 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 25 Jul 2016 14:58:33 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Make simplifyInstanceContexts deterministic (c8188d8) Message-ID: <20160725145833.313803A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/c8188d81d329318fea98f699b0b8d426fc0c376b/ghc >--------------------------------------------------------------- commit c8188d81d329318fea98f699b0b8d426fc0c376b Author: Bartosz Nitka Date: Tue May 10 05:32:28 2016 -0700 Make simplifyInstanceContexts deterministic simplifyInstanceContexts used cmpType which is nondeterministic for canonicalising typeclass constraints in derived instances. Following changes make it deterministic as explained by the Note [Deterministic simplifyInstanceContexts]. Test Plan: ./validate Reviewers: simonmar, goldfire, simonpj, austin, bgamari Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2173 GHC Trac Issues: #4012 (cherry picked from commit b58b0e18a568bbf6381a85eea7adc72679355671) >--------------------------------------------------------------- c8188d81d329318fea98f699b0b8d426fc0c376b compiler/basicTypes/Unique.hs | 15 ++++++++------- compiler/basicTypes/Var.hs | 14 ++++++++++++-- compiler/typecheck/TcDeriv.hs | 31 ++++++++++++++++++++++++++++--- compiler/types/Type.hs | 16 ++++++++++++++-- 4 files changed, 62 insertions(+), 14 deletions(-) diff --git a/compiler/basicTypes/Unique.hs b/compiler/basicTypes/Unique.hs index ca74373..eddf265 100644 --- a/compiler/basicTypes/Unique.hs +++ b/compiler/basicTypes/Unique.hs @@ -23,7 +23,7 @@ module Unique ( Unique, Uniquable(..), -- ** Constructors, destructors and operations on 'Unique's - hasKey, cmpByUnique, + hasKey, pprUnique, @@ -35,6 +35,7 @@ module Unique ( deriveUnique, -- Ditto newTagUnique, -- Used in CgCase initTyVarUnique, + nonDetCmpUnique, -- ** Making built-in uniques @@ -168,9 +169,6 @@ instance Uniquable FastString where instance Uniquable Int where getUnique i = mkUniqueGrimily i -cmpByUnique :: Uniquable a => a -> a -> Ordering -cmpByUnique x y = (getUnique x) `cmpUnique` (getUnique y) - {- ************************************************************************ * * @@ -204,8 +202,11 @@ eqUnique (MkUnique u1) (MkUnique u2) = u1 == u2 ltUnique (MkUnique u1) (MkUnique u2) = u1 < u2 leUnique (MkUnique u1) (MkUnique u2) = u1 <= u2 -cmpUnique :: Unique -> Unique -> Ordering -cmpUnique (MkUnique u1) (MkUnique u2) +-- Provided here to make it explicit at the call-site that it can +-- introduce non-determinism. +-- See Note [Unique Determinism] +nonDetCmpUnique :: Unique -> Unique -> Ordering +nonDetCmpUnique (MkUnique u1) (MkUnique u2) = if u1 == u2 then EQ else if u1 < u2 then LT else GT instance Eq Unique where @@ -217,7 +218,7 @@ instance Ord Unique where a <= b = leUnique a b a > b = not (leUnique a b) a >= b = not (ltUnique a b) - compare a b = cmpUnique a b + compare a b = nonDetCmpUnique a b ----------------- instance Uniquable Unique where diff --git a/compiler/basicTypes/Var.hs b/compiler/basicTypes/Var.hs index d6bd609..c70a304 100644 --- a/compiler/basicTypes/Var.hs +++ b/compiler/basicTypes/Var.hs @@ -64,7 +64,9 @@ module Var ( -- ** Modifying 'TyVar's setTyVarName, setTyVarUnique, setTyVarKind, updateTyVarKind, - updateTyVarKindM + updateTyVarKindM, + + nonDetCmpVar ) where @@ -80,6 +82,7 @@ import Util import DynFlags import Outputable +import Unique (nonDetCmpUnique) import Data.Data {- @@ -269,7 +272,14 @@ instance Ord Var where a < b = realUnique a < realUnique b a >= b = realUnique a >= realUnique b a > b = realUnique a > realUnique b - a `compare` b = varUnique a `compare` varUnique b + a `compare` b = a `nonDetCmpVar` b + +-- | Compare Vars by their Uniques. +-- This is what Ord Var does, provided here to make it explicit at the +-- call-site that it can introduce non-determinism. +-- See Note [Unique Determinism] +nonDetCmpVar :: Var -> Var -> Ordering +nonDetCmpVar a b = varUnique a `nonDetCmpUnique` varUnique b instance Data Var where -- don't traverse? diff --git a/compiler/typecheck/TcDeriv.hs b/compiler/typecheck/TcDeriv.hs index c74b450..944c513 100644 --- a/compiler/typecheck/TcDeriv.hs +++ b/compiler/typecheck/TcDeriv.hs @@ -1862,6 +1862,29 @@ this by simplifying the RHS to a form in which - the list is sorted by tyvar (major key) and then class (minor key) - no duplicates, of course +Note [Deterministic simplifyInstanceContexts] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Canonicalisation uses cmpType which is nondeterministic. Sorting +with cmpType puts the returned lists in a nondeterministic order. +If we were to return them, we'd get class constraints in +nondeterministic order. + +Consider: + + data ADT a b = Z a b deriving Eq + +The generated code could be either: + + instance (Eq a, Eq b) => Eq (Z a b) where + +Or: + + instance (Eq b, Eq a) => Eq (Z a b) where + +To prevent the order from being nondeterministic we only +canonicalize when comparing and return them in the same order as +simplifyDeriv returned them. +See also Note [cmpType nondeterminism] -} @@ -1909,8 +1932,10 @@ simplifyInstanceContexts infer_specs else iterate_deriv (n+1) new_solns } - eqSolution = eqListBy (eqListBy eqType) - + eqSolution a b = eqListBy (eqListBy eqType) (canSolution a) (canSolution b) + -- Canonicalise for comparison + -- See Note [Deterministic simplifyInstanceContexts] + canSolution = map (sortBy cmpType) ------------------------------------------------------------------ gen_soln :: DerivSpec ThetaOrigin -> TcM ThetaType gen_soln (DS { ds_loc = loc, ds_tvs = tyvars @@ -1925,7 +1950,7 @@ simplifyInstanceContexts infer_specs -- Claim: the result instance declaration is guaranteed valid -- Hence no need to call: -- checkValidInstance tyvars theta clas inst_tys - ; return (sortBy cmpType theta) } -- Canonicalise before returning the solution + ; return theta } where the_pred = mkClassPred clas inst_tys diff --git a/compiler/types/Type.hs b/compiler/types/Type.hs index b4a123b..69cf69f 100644 --- a/compiler/types/Type.hs +++ b/compiler/types/Type.hs @@ -223,6 +223,7 @@ import FastString import Pair import ListSetOps import Digraph +import Unique ( nonDetCmpUnique ) import Maybes ( orElse ) import Data.Maybe ( isJust, mapMaybe ) @@ -2098,6 +2099,16 @@ eqVarBndrs _ _ _= Nothing -- Now here comes the real worker +{- +Note [cmpType nondeterminism] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +cmpType is implemented in terms of cmpTypeX. cmpTypeX uses cmpTc which +compares TyCons by their Unique value. Using Uniques for ordering leads +to nondeterminism. We hit the same problem in the TyVarTy case, comparing +type variables is nondeterministic, note the call to nonDetCmpVar in cmpTypeX. +See Note [Unique Determinism] for more details. +-} + cmpType :: Type -> Type -> Ordering cmpType t1 t2 -- we know k1 and k2 have the same kind, because they both have kind *. @@ -2160,7 +2171,7 @@ cmpTypeX env orig_t1 orig_t2 = | Just t2' <- coreViewOneStarKind t2 = go env t1 t2' go env (TyVarTy tv1) (TyVarTy tv2) - = liftOrdering $ rnOccL env tv1 `compare` rnOccR env tv2 + = liftOrdering $ rnOccL env tv1 `nonDetCmpVar` rnOccR env tv2 go env (ForAllTy (Named tv1 _) t1) (ForAllTy (Named tv2 _) t2) = go env (tyVarKind tv1) (tyVarKind tv2) `thenCmpTy` go (rnBndr2 env tv1 tv2) t1 t2 @@ -2211,10 +2222,11 @@ cmpTypesX _ _ [] = GT -- | Compare two 'TyCon's. NB: This should /never/ see the "star synonyms", -- as recognized by Kind.isStarKindSynonymTyCon. See Note -- [Kind Constraint and kind *] in Kind. +-- See Note [cmpType nondeterminism] cmpTc :: TyCon -> TyCon -> Ordering cmpTc tc1 tc2 = ASSERT( not (isStarKindSynonymTyCon tc1) && not (isStarKindSynonymTyCon tc2) ) - u1 `compare` u2 + u1 `nonDetCmpUnique` u2 where u1 = tyConUnique tc1 u2 = tyConUnique tc2 From git at git.haskell.org Mon Jul 25 14:58:35 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 25 Jul 2016 14:58:35 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Remove some varSetElems in dsCmdStmt (0234bfa) Message-ID: <20160725145835.D26713A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/0234bfa6c15c3f49f60c288c3a29399105450ca0/ghc >--------------------------------------------------------------- commit 0234bfa6c15c3f49f60c288c3a29399105450ca0 Author: Bartosz Nitka Date: Wed May 11 07:47:15 2016 -0700 Remove some varSetElems in dsCmdStmt varSetElems introduces unnecessary determinism and it's easy to preserve determinism here. Test Plan: ./validate Reviewers: goldfire, simonmar, austin, bgamari, simonpj Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2195 GHC Trac Issues: #4012 (cherry picked from commit 0e719885f53e20f2e14a94b32d858b47b516a8fc) >--------------------------------------------------------------- 0234bfa6c15c3f49f60c288c3a29399105450ca0 compiler/deSugar/DsArrows.hs | 8 +++++--- 1 file changed, 5 insertions(+), 3 deletions(-) diff --git a/compiler/deSugar/DsArrows.hs b/compiler/deSugar/DsArrows.hs index ea10b74..cdf839a 100644 --- a/compiler/deSugar/DsArrows.hs +++ b/compiler/deSugar/DsArrows.hs @@ -48,6 +48,7 @@ import VarSet import SrcLoc import ListSetOps( assocDefault ) import Data.List +import Util data DsCmdEnv = DsCmdEnv { arr_id, compose_id, first_id, app_id, choice_id, loop_id :: CoreExpr @@ -786,7 +787,7 @@ dsCmdStmt ids local_vars out_ids (BindStmt pat cmd _ _ _) env_ids = do (core_cmd, fv_cmd, env_ids1) <- dsfixCmd ids local_vars unitTy pat_ty cmd let pat_vars = mkVarSet (collectPatBinders pat) let - env_ids2 = varSetElems (mkVarSet out_ids `minusVarSet` pat_vars) + env_ids2 = filterOut (`elemVarSet` pat_vars) out_ids env_ty2 = mkBigCoreVarTupTy env_ids2 -- multiplexing function @@ -863,8 +864,9 @@ dsCmdStmt ids local_vars out_ids , recS_later_rets = later_rets, recS_rec_rets = rec_rets }) env_ids = do let - env2_id_set = mkVarSet out_ids `minusVarSet` mkVarSet later_ids - env2_ids = varSetElems env2_id_set + later_ids_set = mkVarSet later_ids + env2_ids = filterOut (`elemVarSet` later_ids_set) out_ids + env2_id_set = mkVarSet env2_ids env2_ty = mkBigCoreVarTupTy env2_ids -- post_loop_fn = \((later_ids),(env2_ids)) -> (out_ids) From git at git.haskell.org Mon Jul 25 14:58:38 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 25 Jul 2016 14:58:38 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Make absentError not depend on uniques (29c0807) Message-ID: <20160725145838.77EC73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/29c0807d23e78502ee05fad4055343d904e55c29/ghc >--------------------------------------------------------------- commit 29c0807d23e78502ee05fad4055343d904e55c29 Author: Bartosz Nitka Date: Thu May 12 05:42:21 2016 -0700 Make absentError not depend on uniques As explained in the comment it will cause changes in inlining if we don't suppress them. Test Plan: ./validate Reviewers: bgamari, austin, simonpj, goldfire, simonmar Reviewed By: simonmar Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2203 GHC Trac Issues: #4012 (cherry picked from commit 925b0aea8edc1761fcc16feba1601bea38422c92) >--------------------------------------------------------------- 29c0807d23e78502ee05fad4055343d904e55c29 compiler/stranal/WwLib.hs | 9 ++++++++- 1 file changed, 8 insertions(+), 1 deletion(-) diff --git a/compiler/stranal/WwLib.hs b/compiler/stranal/WwLib.hs index 1472ead..09bc204 100644 --- a/compiler/stranal/WwLib.hs +++ b/compiler/stranal/WwLib.hs @@ -757,7 +757,14 @@ mk_absent_let dflags arg where arg_ty = idType arg abs_rhs = mkRuntimeErrorApp aBSENT_ERROR_ID arg_ty msg - msg = showSDoc dflags (ppr arg <+> ppr (idType arg)) + msg = showSDoc (gopt_set dflags Opt_SuppressUniques) + (ppr arg <+> ppr (idType arg)) + -- We need to suppress uniques here because otherwise they'd + -- end up in the generated code as strings. This is bad for + -- determinism, because with different uniques the strings + -- will have different lengths and hence different costs for + -- the inliner leading to different inlining. + -- See also Note [Unique Determinism] in Unique mk_seq_case :: Id -> CoreExpr -> CoreExpr mk_seq_case arg body = Case (Var arg) (sanitiseCaseBndr arg) (exprType body) [(DEFAULT, [], body)] From git at git.haskell.org Mon Jul 25 14:58:41 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 25 Jul 2016 14:58:41 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Kill varEnvElts in specImports (f38fe3f) Message-ID: <20160725145841.27DFE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/f38fe3f239340666086528ab712c8ab53c0e1efb/ghc >--------------------------------------------------------------- commit f38fe3f239340666086528ab712c8ab53c0e1efb Author: Bartosz Nitka Date: Thu May 12 06:55:00 2016 -0700 Kill varEnvElts in specImports We need the order of specialized binds and rules to be deterministic, so we use a deterministic set here. Test Plan: ./validate Reviewers: simonmar, bgamari, austin, simonpj Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2197 GHC Trac Issues: #4012 (cherry picked from commit 6bf0eef74d2b2ce9a48c7acc08ca2a1c0c8a7fbc) >--------------------------------------------------------------- f38fe3f239340666086528ab712c8ab53c0e1efb compiler/basicTypes/VarEnv.hs | 25 +++++++++++++++++++++++-- compiler/specialise/Specialise.hs | 28 ++++++++++++++++++---------- compiler/utils/UniqDFM.hs | 32 ++++++++++++++++++++++++++++++++ 3 files changed, 73 insertions(+), 12 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc f38fe3f239340666086528ab712c8ab53c0e1efb From git at git.haskell.org Mon Jul 25 14:58:43 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 25 Jul 2016 14:58:43 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Kill varSetElems in tcInferPatSynDecl (233b1ab) Message-ID: <20160725145843.C4F263A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/233b1ab187d063c51b1dda5bcb6f92fffadf4cf5/ghc >--------------------------------------------------------------- commit 233b1ab187d063c51b1dda5bcb6f92fffadf4cf5 Author: Bartosz Nitka Date: Mon May 16 03:27:53 2016 -0700 Kill varSetElems in tcInferPatSynDecl varSetElems introduces unnecessary non-determinism and while I didn't estabilish experimentally that this matters here I'm convinced that it will, because I expect pattern synonyms to end up in interface files. Test Plan: ./validate Reviewers: austin, simonmar, bgamari, mpickering, simonpj Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2206 GHC Trac Issues: #4012 (cherry picked from commit 21fe4ffd049c8ab4b9ee36af3cf8f70b46d6beda) >--------------------------------------------------------------- 233b1ab187d063c51b1dda5bcb6f92fffadf4cf5 compiler/typecheck/TcPatSyn.hs | 42 ++++++++++++++++++++++++++---------------- 1 file changed, 26 insertions(+), 16 deletions(-) diff --git a/compiler/typecheck/TcPatSyn.hs b/compiler/typecheck/TcPatSyn.hs index 633b8d6..3cf1a86 100644 --- a/compiler/typecheck/TcPatSyn.hs +++ b/compiler/typecheck/TcPatSyn.hs @@ -47,6 +47,7 @@ import FieldLabel import Bag import Util import ErrUtils +import FV import Control.Monad ( unless, zipWithM ) import Data.List( partition ) #if __GLASGOW_HASKELL__ < 709 @@ -219,9 +220,8 @@ tcInferPatSynDecl PSB{ psb_id = lname@(L _ name), psb_args = details, ; (qtvs, req_dicts, ev_binds) <- simplifyInfer tclvl False [] named_taus wanted - ; let (ex_vars, prov_dicts) = tcCollectEx lpat' + ; let ((ex_tvs, ex_vars), prov_dicts) = tcCollectEx lpat' univ_tvs = filter (not . (`elemVarSet` ex_vars)) qtvs - ex_tvs = varSetElems ex_vars prov_theta = map evVarPred prov_dicts req_theta = map evVarPred req_dicts @@ -948,34 +948,44 @@ nonBidirectionalErr name = failWithTc $ -- These are used in computing the type of a pattern synonym and also -- in generating matcher functions, since success continuations need -- to be passed these pattern-bound evidences. -tcCollectEx :: LPat Id -> (TyVarSet, [EvVar]) -tcCollectEx pat = go pat +tcCollectEx + :: LPat Id + -> ( ([Var], VarSet) -- Existentially-bound type variables as a + -- deterministically ordered list and a set. + -- See Note [Deterministic FV] in FV + , [EvVar] + ) +tcCollectEx pat = let (fv, evs) = go pat in (fvVarListVarSet fv, evs) where - go :: LPat Id -> (TyVarSet, [EvVar]) + go :: LPat Id -> (FV, [EvVar]) go = go1 . unLoc - go1 :: Pat Id -> (TyVarSet, [EvVar]) + go1 :: Pat Id -> (FV, [EvVar]) go1 (LazyPat p) = go p go1 (AsPat _ p) = go p go1 (ParPat p) = go p go1 (BangPat p) = go p - go1 (ListPat ps _ _) = mconcat . map go $ ps - go1 (TuplePat ps _ _) = mconcat . map go $ ps - go1 (PArrPat ps _) = mconcat . map go $ ps + go1 (ListPat ps _ _) = mergeMany . map go $ ps + go1 (TuplePat ps _ _) = mergeMany . map go $ ps + go1 (PArrPat ps _) = mergeMany . map go $ ps go1 (ViewPat _ p _) = go p - go1 con at ConPatOut{} = mappend (mkVarSet (pat_tvs con), pat_dicts con) $ + go1 con at ConPatOut{} = merge (FV.mkFVs (pat_tvs con), pat_dicts con) $ goConDetails $ pat_args con go1 (SigPatOut p _) = go p go1 (CoPat _ p _) = go1 p go1 (NPlusKPat n k _ geq subtract _) = pprPanic "TODO: NPlusKPat" $ ppr n $$ ppr k $$ ppr geq $$ ppr subtract - go1 _ = mempty + go1 _ = empty - goConDetails :: HsConPatDetails Id -> (TyVarSet, [EvVar]) - goConDetails (PrefixCon ps) = mconcat . map go $ ps - goConDetails (InfixCon p1 p2) = go p1 `mappend` go p2 + goConDetails :: HsConPatDetails Id -> (FV, [EvVar]) + goConDetails (PrefixCon ps) = mergeMany . map go $ ps + goConDetails (InfixCon p1 p2) = go p1 `merge` go p2 goConDetails (RecCon HsRecFields{ rec_flds = flds }) - = mconcat . map goRecFd $ flds + = mergeMany . map goRecFd $ flds - goRecFd :: LHsRecField Id (LPat Id) -> (TyVarSet, [EvVar]) + goRecFd :: LHsRecField Id (LPat Id) -> (FV, [EvVar]) goRecFd (L _ HsRecField{ hsRecFieldArg = p }) = go p + + merge (vs1, evs1) (vs2, evs2) = (vs1 `unionFV` vs2, evs1 ++ evs2) + mergeMany = foldr merge empty + empty = (emptyFV, []) From git at git.haskell.org Mon Jul 25 14:58:46 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 25 Jul 2016 14:58:46 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Refactor free tyvars on LHS of rules (ae94a31) Message-ID: <20160725145846.802783A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/ae94a31e7f162b4a3ef6b6f837bd6006a98f639a/ghc >--------------------------------------------------------------- commit ae94a31e7f162b4a3ef6b6f837bd6006a98f639a Author: Simon Peyton Jones Date: Fri Apr 22 10:47:14 2016 +0100 Refactor free tyvars on LHS of rules A RULE can have unbound meta-tyvars on the LHS. Consider data T a = C foo :: T a -> Int foo C = 1 {-# RULES "myrule" foo C = 1 #-} After type checking the LHS becomes (foo alpha (C alpah)) and we do not want to zap the unbound meta-tyvar 'alpha' to Any, because that limits the applicability of the rule. Instead, we want to quantify over it! Previously there was a rather clunky implementation of this quantification, buried in the zonker in TcHsSyn (zonkTvCollecting). This patch refactors it so that the zonker just turns the meta-tyvar into a skolem, and the desugarer adds the quantification. See DsBinds Note [Free tyvars on rule LHS]. As it happened, the desugarer was already doing something similar for dictionaries. See DsBinds Note [Free dictionaries on rule LHS] No change in functionality, but less cruft. (cherry picked from commit 6ad2b42f866fa718855cc5c850e3549bc1428b3c) >--------------------------------------------------------------- ae94a31e7f162b4a3ef6b6f837bd6006a98f639a compiler/deSugar/DsBinds.hs | 99 +++++++++++++++++++------------ compiler/typecheck/TcHsSyn.hs | 134 ++++++++++++++++++------------------------ 2 files changed, 121 insertions(+), 112 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc ae94a31e7f162b4a3ef6b6f837bd6006a98f639a From git at git.haskell.org Mon Jul 25 14:58:49 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 25 Jul 2016 14:58:49 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Make accept (1c59d37) Message-ID: <20160725145849.4B21E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/1c59d376b2073f47de936ff49e463e0e1320f779/ghc >--------------------------------------------------------------- commit 1c59d376b2073f47de936ff49e463e0e1320f779 Author: Bartosz Nitka Date: Mon May 16 12:47:25 2016 -0700 Make accept This updates some test output after it got reordered by determinism fixes. There's no corresponding commit in the master branch. >--------------------------------------------------------------- 1c59d376b2073f47de936ff49e463e0e1320f779 testsuite/tests/ado/ado004.stderr | 16 +- testsuite/tests/determinism/determ007/A.hs | 3 + testsuite/tests/determinism/determ007/Makefile | 13 ++ testsuite/tests/determinism/determ007/all.T | 4 + .../determ007.stdout} | 0 testsuite/tests/determinism/determ008/A.hs | 3 + testsuite/tests/determinism/determ008/Makefile | 13 ++ testsuite/tests/determinism/determ008/all.T | 4 + .../determ008.stdout} | 0 testsuite/tests/determinism/determ009/A.hs | 4 + testsuite/tests/determinism/determ009/Makefile | 13 ++ testsuite/tests/determinism/determ009/all.T | 4 + .../determ009.stdout} | 0 testsuite/tests/determinism/determ011/A.hs | 26 +++ testsuite/tests/determinism/determ011/Makefile | 13 ++ testsuite/tests/determinism/determ011/all.T | 4 + .../determ011.stdout} | 0 testsuite/tests/determinism/determ012/A.hs | 10 + testsuite/tests/determinism/determ012/Makefile | 13 ++ testsuite/tests/determinism/determ012/all.T | 4 + .../tests/determinism/determ012/determ012.stdout | 2 + testsuite/tests/determinism/determ013/A.hs | 19 ++ testsuite/tests/determinism/determ013/Makefile | 13 ++ testsuite/tests/determinism/determ013/all.T | 4 + .../tests/determinism/determ013/determ013.stdout | 2 + .../T10934.hs => determinism/determ014/A.hs} | 0 testsuite/tests/determinism/determ014/Makefile | 13 ++ testsuite/tests/determinism/determ014/all.T | 4 + .../tests/determinism/determ014/determ014.stdout | 2 + testsuite/tests/determinism/determ015/A.hs | 59 ++++++ testsuite/tests/determinism/determ015/Makefile | 13 ++ testsuite/tests/determinism/determ015/all.T | 4 + .../determ015.stdout} | 0 testsuite/tests/determinism/determ016/A.hs | 19 ++ testsuite/tests/determinism/determ016/Makefile | 13 ++ testsuite/tests/determinism/determ016/all.T | 4 + .../determ016.stdout} | 0 testsuite/tests/determinism/determ017/A.hs | 215 +++++++++++++++++++++ testsuite/tests/determinism/determ017/Makefile | 13 ++ testsuite/tests/determinism/determ017/all.T | 4 + .../determ017.stdout} | 0 .../tests/ghci.debugger/scripts/break006.stderr | 4 +- testsuite/tests/ghci/scripts/T6018ghcifail.stderr | 4 +- testsuite/tests/typecheck/should_fail/T5095.stderr | 2 +- .../typecheck/should_fail/T6018failclosed.stderr | 144 +++++++------- .../tests/typecheck/should_fail/tcfail133.stderr | 2 +- 46 files changed, 620 insertions(+), 86 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 1c59d376b2073f47de936ff49e463e0e1320f779 From git at git.haskell.org Mon Jul 25 14:58:51 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 25 Jul 2016 14:58:51 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Make inert_model and inert_eqs deterministic sets (fbccc0b) Message-ID: <20160725145851.F079A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/fbccc0b61184bf93c1135b87c2dc0687ca4a6976/ghc >--------------------------------------------------------------- commit fbccc0b61184bf93c1135b87c2dc0687ca4a6976 Author: Bartosz Nitka Date: Tue May 17 05:45:43 2016 -0700 Make inert_model and inert_eqs deterministic sets The order inert_model and intert_eqs fold affects the order that the typechecker looks at things. I've been able to experimentally confirm that the order of equalities and the order of the model matter for determinism. This is just a straigthforward replacement of nondeterministic VarEnv for deterministic DVarEnv. Test Plan: ./validate Reviewers: simonpj, goldfire, austin, bgamari, simonmar Reviewed By: simonmar Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2232 GHC Trac Issues: #4012 (cherry picked from commit fffe3a25adab41d44943ed1be0191cf570d3e154) >--------------------------------------------------------------- fbccc0b61184bf93c1135b87c2dc0687ca4a6976 compiler/basicTypes/VarEnv.hs | 28 +++++++++-- compiler/typecheck/TcFlatten.hs | 4 +- compiler/typecheck/TcInteract.hs | 2 +- compiler/typecheck/TcSMonad.hs | 58 +++++++++++----------- compiler/utils/UniqDFM.hs | 22 +++++++- .../tests/indexed-types/should_fail/T3330a.stderr | 5 +- .../tests/indexed-types/should_fail/T4174.stderr | 4 +- .../tests/indexed-types/should_fail/T4179.stderr | 6 +-- .../tests/indexed-types/should_fail/T9662.stderr | 4 +- testsuite/tests/polykinds/T9017.stderr | 4 +- testsuite/tests/typecheck/should_fail/T7869.stderr | 8 ++- 11 files changed, 93 insertions(+), 52 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc fbccc0b61184bf93c1135b87c2dc0687ca4a6976 From git at git.haskell.org Mon Jul 25 14:58:54 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 25 Jul 2016 14:58:54 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Refactor validity checking for type/data instances (2b3de32) Message-ID: <20160725145854.A64243A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/2b3de328f24a2c2113f65ceef715e6ee57045577/ghc >--------------------------------------------------------------- commit 2b3de328f24a2c2113f65ceef715e6ee57045577 Author: Simon Peyton Jones Date: Fri Jan 22 16:40:55 2016 +0000 Refactor validity checking for type/data instances I found that there was some code duplication going on, so I've put more into the shared function checkValidFamPats. I did some refactoring in checkConsistentFamInst too, preparatory to #11450; the error messages change a little but no change in behaviour. (cherry picked from commit 746764cce9a111a082a13bc3cd34b50e34fd2a31) >--------------------------------------------------------------- 2b3de328f24a2c2113f65ceef715e6ee57045577 compiler/typecheck/TcInstDcls.hs | 9 +- compiler/typecheck/TcTyClsDecls.hs | 2 + compiler/typecheck/TcValidity.hs | 154 ++++++++++++--------- .../indexed-types/should_fail/SimpleFail2a.stderr | 11 +- 4 files changed, 101 insertions(+), 75 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 2b3de328f24a2c2113f65ceef715e6ee57045577 From git at git.haskell.org Mon Jul 25 14:58:57 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 25 Jul 2016 14:58:57 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Kill varSetElems in tidyFreeTyCoVars (bcc1cf4) Message-ID: <20160725145857.591B43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/bcc1cf47fb7eeb890eb70c267ff353bf01207241/ghc >--------------------------------------------------------------- commit bcc1cf47fb7eeb890eb70c267ff353bf01207241 Author: Bartosz Nitka Date: Wed May 18 10:36:49 2016 -0700 Kill varSetElems in tidyFreeTyCoVars I haven't observed this to have an effect on nondeterminism, but tidyOccName appears to modify the TidyOccEnv in a way dependent on the order of inputs. It's easy enough to change it to be deterministic to be on the safe side. Test Plan: ./validate Reviewers: simonmar, austin, bgamari, simonpj Reviewed By: simonpj Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2238 GHC Trac Issues: #4012 (cherry picked from commit 6282bc31808e335cd8386dd20d469bc2457f84de) >--------------------------------------------------------------- bcc1cf47fb7eeb890eb70c267ff353bf01207241 compiler/typecheck/TcErrors.hs | 8 +- compiler/typecheck/TcRnMonad.hs | 2 +- compiler/typecheck/TcValidity.hs | 10 +- compiler/types/TyCoRep.hs | 8 +- .../tests/indexed-types/should_fail/T2693.stderr | 4 +- .../should_fail/overloadedlabelsfail01.stderr | 46 ++-- testsuite/tests/parser/should_fail/T7848.stderr | 4 +- testsuite/tests/rename/should_fail/T10618.stderr | 2 +- .../tests/typecheck/should_fail/T11355.stderr | 2 +- testsuite/tests/typecheck/should_fail/T5684.stderr | 286 ++++++++++----------- testsuite/tests/typecheck/should_fail/T7851.stderr | 4 +- .../tests/typecheck/should_fail/tcfail001.stderr | 2 +- 12 files changed, 189 insertions(+), 189 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc bcc1cf47fb7eeb890eb70c267ff353bf01207241 From git at git.haskell.org Mon Jul 25 14:59:01 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 25 Jul 2016 14:59:01 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Make Arrow desugaring deterministic (5ba488f) Message-ID: <20160725145901.2849C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/5ba488f66e35911d57b3a224c0467c864334e54e/ghc >--------------------------------------------------------------- commit 5ba488f66e35911d57b3a224c0467c864334e54e Author: Bartosz Nitka Date: Tue May 24 04:44:37 2016 -0700 Make Arrow desugaring deterministic This kills two instances of varSetElems that turned out to be nondeterministic. I've tried to untangle this before, but it's a bit hard with the fixDs in the middle. Fortunately I now have a test case that proves that we need determinism here. Test Plan: ./validate, new testcase Reviewers: simonpj, simonmar, austin, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2258 GHC Trac Issues: #4012 (cherry picked from commit 9d06ef1ae451a145607301dc7556931b537a7d83) >--------------------------------------------------------------- 5ba488f66e35911d57b3a224c0467c864334e54e compiler/coreSyn/CoreFVs.hs | 33 ++++++++++++ compiler/deSugar/DsArrows.hs | 63 +++++++++++----------- compiler/utils/UniqDFM.hs | 7 ++- testsuite/tests/determinism/determ018/A.hs | 32 +++++++++++ .../determinism/{determ013 => determ018}/Makefile | 2 +- .../determinism/{determ009 => determ018}/all.T | 4 +- .../determ018.stdout} | 0 7 files changed, 106 insertions(+), 35 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 5ba488f66e35911d57b3a224c0467c864334e54e From git at git.haskell.org Mon Jul 25 14:59:03 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 25 Jul 2016 14:59:03 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Serialize vParallelTyCons in a stable order (3b745a1) Message-ID: <20160725145903.C37BF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/3b745a14f69d1a6143df17d58c8eb3368ed9812c/ghc >--------------------------------------------------------------- commit 3b745a14f69d1a6143df17d58c8eb3368ed9812c Author: Bartosz Nitka Date: Thu Jun 2 09:51:04 2016 -0700 Serialize vParallelTyCons in a stable order nameSetElems can introduce nondeterminism and while I haven't observed this being a problem in practice (possibly because this is dead code) there's no downside to doing this. Test Plan: ./validate Reviewers: bgamari, austin, simonpj, simonmar Reviewed By: simonmar Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2296 GHC Trac Issues: #4012 (cherry picked from commit d348acd527548fc71a59e239a963e982c69af1f8) >--------------------------------------------------------------- 3b745a14f69d1a6143df17d58c8eb3368ed9812c compiler/iface/MkIface.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/iface/MkIface.hs b/compiler/iface/MkIface.hs index 1a31afd..1b9570c 100644 --- a/compiler/iface/MkIface.hs +++ b/compiler/iface/MkIface.hs @@ -326,7 +326,7 @@ mkIface_ hsc_env maybe_old_fingerprint , ifaceVectInfoTyCon = [tyConName t | (t, t_v) <- nameEnvElts vTyCon, t /= t_v] , ifaceVectInfoTyConReuse = [tyConName t | (t, t_v) <- nameEnvElts vTyCon, t == t_v] , ifaceVectInfoParallelVars = [Var.varName v | v <- varSetElems vParallelVars] - , ifaceVectInfoParallelTyCons = nameSetElems vParallelTyCons + , ifaceVectInfoParallelTyCons = nameSetElemsStable vParallelTyCons } ----------------------------- From git at git.haskell.org Mon Jul 25 14:59:06 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 25 Jul 2016 14:59:06 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Add nameSetElemsStable and fix the build (2d3e064) Message-ID: <20160725145906.71D153A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/2d3e064dd5d726c106537e1e65926b991275ba16/ghc >--------------------------------------------------------------- commit 2d3e064dd5d726c106537e1e65926b991275ba16 Author: Bartosz Nitka Date: Thu Jun 2 10:34:57 2016 -0700 Add nameSetElemsStable and fix the build (cherry picked from commit 3eac3a0e9f74ad936375e3ba65f5d8454ea9d408) >--------------------------------------------------------------- 2d3e064dd5d726c106537e1e65926b991275ba16 compiler/basicTypes/NameSet.hs | 11 +++++++++++ compiler/utils/UniqFM.hs | 6 +++++- 2 files changed, 16 insertions(+), 1 deletion(-) diff --git a/compiler/basicTypes/NameSet.hs b/compiler/basicTypes/NameSet.hs index 7bca479..b764bd9 100644 --- a/compiler/basicTypes/NameSet.hs +++ b/compiler/basicTypes/NameSet.hs @@ -13,6 +13,7 @@ module NameSet ( minusNameSet, elemNameSet, nameSetElems, extendNameSet, extendNameSetList, delFromNameSet, delListFromNameSet, isEmptyNameSet, foldNameSet, filterNameSet, intersectsNameSet, intersectNameSet, + nameSetElemsStable, -- * Free variables FreeVars, @@ -33,6 +34,8 @@ module NameSet ( import Name import UniqSet +import UniqFM +import Data.List (sortBy) {- ************************************************************************ @@ -84,6 +87,14 @@ delListFromNameSet set ns = foldl delFromNameSet set ns intersectsNameSet s1 s2 = not (isEmptyNameSet (s1 `intersectNameSet` s2)) +-- | Get the elements of a NameSet with some stable ordering. +-- See Note [Deterministic UniqFM] to learn about nondeterminism +nameSetElemsStable :: NameSet -> [Name] +nameSetElemsStable ns = + sortBy stableNameCmp $ nonDetEltsUFM ns + -- It's OK to use nonDetEltsUFM here because we immediately sort + -- with stableNameCmp + {- ************************************************************************ * * diff --git a/compiler/utils/UniqFM.hs b/compiler/utils/UniqFM.hs index 0df5a2d..0056287 100644 --- a/compiler/utils/UniqFM.hs +++ b/compiler/utils/UniqFM.hs @@ -64,7 +64,7 @@ module UniqFM ( isNullUFM, lookupUFM, lookupUFM_Directly, lookupWithDefaultUFM, lookupWithDefaultUFM_Directly, - eltsUFM, keysUFM, splitUFM, + eltsUFM, keysUFM, splitUFM, nonDetEltsUFM, ufmToSet_Directly, ufmToList, ufmToIntMap, joinUFM, pprUniqFM, pprUFM, pluralUFM @@ -304,6 +304,10 @@ ufmToList (UFM m) = map (\(k, v) -> (getUnique k, v)) $ M.toList m ufmToIntMap :: UniqFM elt -> M.IntMap elt ufmToIntMap (UFM m) = m +-- See Note [Deterministic UniqFM] to learn about nondeterminism +nonDetEltsUFM :: UniqFM elt -> [elt] +nonDetEltsUFM (UFM m) = M.elems m + -- Hoopl joinUFM :: JoinFun v -> JoinFun (UniqFM v) joinUFM eltJoin l (OldFact old) (NewFact new) = foldUFM_Directly add (NoChange, old) new From git at git.haskell.org Mon Jul 25 14:59:09 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 25 Jul 2016 14:59:09 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Implement deterministic CallInfoSet (d563710) Message-ID: <20160725145909.1F94D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/d563710d4277897b4704e7e116d2a805de0ec962/ghc >--------------------------------------------------------------- commit d563710d4277897b4704e7e116d2a805de0ec962 Author: Bartosz Nitka Date: Mon Jun 6 04:36:21 2016 -0700 Implement deterministic CallInfoSet We need CallInfoSet to be deterministic because it determines the order that the binds get generated. Currently it's not deterministic because it's keyed on `CallKey = [Maybe Type]` and `Ord CallKey` is implemented with `cmpType` which is nondeterministic. See Note [CallInfoSet determinism] for more details. Test Plan: ./validate Reviewers: simonpj, bgamari, austin, simonmar Reviewed By: simonmar Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2242 GHC Trac Issues: #4012 (cherry picked from commit 48e9a1f5521fa3185510d144dd28a87e452ce134) >--------------------------------------------------------------- d563710d4277897b4704e7e116d2a805de0ec962 compiler/specialise/Specialise.hs | 111 +++++++++++++++++++++++++------------- 1 file changed, 74 insertions(+), 37 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc d563710d4277897b4704e7e116d2a805de0ec962 From git at git.haskell.org Mon Jul 25 14:59:12 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 25 Jul 2016 14:59:12 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Add -foptimal-applicative-do (77a9f01) Message-ID: <20160725145912.420C73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/77a9f0130836363f8fe28b179285da949340633d/ghc >--------------------------------------------------------------- commit 77a9f0130836363f8fe28b179285da949340633d Author: Simon Marlow Date: Fri Mar 4 13:06:42 2016 +0000 Add -foptimal-applicative-do Summary: The algorithm for ApplicativeDo rearrangement is based on a heuristic that runs in O(n^2). This patch adds the optimal algorithm, which is O(n^3), selected by a flag (-foptimal-applicative-do). It finds better solutions in a small number of cases (about 2% of the cases where ApplicativeDo makes a difference), but it can be very slow for large do expressions. I'm mainly adding it for experimental reasons. ToDo: user guide docs Test Plan: validate Reviewers: simonpj, bgamari, austin, niteria, erikd Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D1969 (cherry picked from commit 2f45cf3f48162a5f843005755dafa1c5c1b451a7) >--------------------------------------------------------------- 77a9f0130836363f8fe28b179285da949340633d compiler/main/DynFlags.hs | 2 + compiler/rename/RnExpr.hs | 226 ++++++++++++++++--------- docs/users_guide/glasgow_exts.rst | 17 ++ testsuite/tests/ado/ado-optimal.hs | 59 +++++++ testsuite/tests/ado/ado-optimal.stdout | 1 + testsuite/tests/ado/ado004.hs | 9 + testsuite/tests/ado/ado004.stderr | 6 + testsuite/tests/ado/all.T | 1 + utils/mkUserGuidePart/Options/Optimizations.hs | 6 + 9 files changed, 251 insertions(+), 76 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 77a9f0130836363f8fe28b179285da949340633d From git at git.haskell.org Mon Jul 25 14:59:16 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 25 Jul 2016 14:59:16 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Desugar ApplicativeDo and RecDo deterministically (a448c03) Message-ID: <20160725145916.235323A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/a448c03832853c9c4bca1ab0ef6b3e259fed3cbe/ghc >--------------------------------------------------------------- commit a448c03832853c9c4bca1ab0ef6b3e259fed3cbe Author: Bartosz Nitka Date: Mon Jun 6 06:08:54 2016 -0700 Desugar ApplicativeDo and RecDo deterministically This fixes a problem described in Note [Deterministic ApplicativeDo and RecursiveDo desugaring]. Test Plan: ./validate + new testcase Reviewers: simonpj, bgamari, austin, simonmar Reviewed By: simonmar Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2287 GHC Trac Issues: #4012 (cherry picked from commit e684f5469399b9d239693eb54f9d1b4d55253ac4) >--------------------------------------------------------------- a448c03832853c9c4bca1ab0ef6b3e259fed3cbe compiler/basicTypes/Name.hs | 4 +- compiler/basicTypes/NameSet.hs | 2 + compiler/rename/RnExpr.hs | 43 +++++++++++++--- testsuite/tests/determinism/determ019/A.hs | 57 ++++++++++++++++++++++ .../determinism/{determ013 => determ019}/Makefile | 2 +- .../determinism/{determ007 => determ019}/all.T | 4 +- .../determ019.stdout} | 0 7 files changed, 101 insertions(+), 11 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc a448c03832853c9c4bca1ab0ef6b3e259fed3cbe From git at git.haskell.org Mon Jul 25 14:59:18 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 25 Jul 2016 14:59:18 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Make UnitIdMap a deterministic map (9b6fa58) Message-ID: <20160725145918.C95E13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/9b6fa58f486c84f0c5d49b6aa61072c7ae8e799c/ghc >--------------------------------------------------------------- commit 9b6fa58f486c84f0c5d49b6aa61072c7ae8e799c Author: Bartosz Nitka Date: Mon Jun 6 08:54:17 2016 -0700 Make UnitIdMap a deterministic map This impacts at least the order in which version macros are generated. It's pretty hard to track what kind of nondeterminism is benign and this should have no performance impact as the number of packages should be relatively small. Test Plan: ./validate Reviewers: simonmar, austin, bgamari, ezyang Reviewed By: ezyang Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2308 GHC Trac Issues: #4012 (cherry picked from commit 1937ef1c506b538f0f93cd290fa4a42fc85ab769) >--------------------------------------------------------------- 9b6fa58f486c84f0c5d49b6aa61072c7ae8e799c compiler/main/Packages.hs | 53 ++++++++++++++++++++++++----------------------- compiler/utils/UniqDFM.hs | 7 ++++++- 2 files changed, 33 insertions(+), 27 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 9b6fa58f486c84f0c5d49b6aa61072c7ae8e799c From git at git.haskell.org Mon Jul 25 14:59:21 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 25 Jul 2016 14:59:21 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Use DVarSet in Vectorise.Exp (65225c7) Message-ID: <20160725145921.775CA3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/65225c7cab8c72279b4c7c099a9d6c9577914390/ghc >--------------------------------------------------------------- commit 65225c7cab8c72279b4c7c099a9d6c9577914390 Author: Bartosz Nitka Date: Tue Jun 7 06:28:51 2016 -0700 Use DVarSet in Vectorise.Exp I believe this part of code is a bit unused. That's probably why it never became a problem in my testing. I'm changing to deterministic sets here to be safer. Test Plan: ./validate Reviewers: simonmar, austin, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2312 GHC Trac Issues: #4012 (cherry picked from commit ad8e2032b86389814f4e1da64c84ab3d3c4c3802) >--------------------------------------------------------------- 65225c7cab8c72279b4c7c099a9d6c9577914390 compiler/vectorise/Vectorise/Exp.hs | 53 ++++++++++++++++++------------------- 1 file changed, 26 insertions(+), 27 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 65225c7cab8c72279b4c7c099a9d6c9577914390 From git at git.haskell.org Mon Jul 25 14:59:24 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 25 Jul 2016 14:59:24 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Make vectInfoParallelVars a DVarSet (87f886c) Message-ID: <20160725145924.4AA6C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/87f886c91b7d789b0db233935fccfd1ea60cc54d/ghc >--------------------------------------------------------------- commit 87f886c91b7d789b0db233935fccfd1ea60cc54d Author: Bartosz Nitka Date: Tue Jun 7 07:19:30 2016 -0700 Make vectInfoParallelVars a DVarSet We dump it in the interface file, so we need to do it in a deterministic order. I haven't seen any problems with this during my testing, but that's probably because it's unused. Test Plan: ./validate Reviewers: simonmar, austin, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2313 GHC Trac Issues: #4012 (cherry picked from commit 5db93d2e567ecb7169b06097244361327ec1eb2a) >--------------------------------------------------------------- 87f886c91b7d789b0db233935fccfd1ea60cc54d compiler/iface/MkIface.hs | 2 +- compiler/iface/TcIface.hs | 2 +- compiler/main/HscTypes.hs | 6 +++--- compiler/main/TidyPgm.hs | 11 ++++++----- compiler/vectorise/Vectorise/Env.hs | 7 ++++--- compiler/vectorise/Vectorise/Exp.hs | 4 ++-- compiler/vectorise/Vectorise/Monad.hs | 2 +- compiler/vectorise/Vectorise/Monad/Global.hs | 2 +- 8 files changed, 19 insertions(+), 17 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 87f886c91b7d789b0db233935fccfd1ea60cc54d From git at git.haskell.org Mon Jul 25 14:59:26 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 25 Jul 2016 14:59:26 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Use UniqFM for SigOf (560b7af) Message-ID: <20160725145926.EE1B13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/560b7af436b347d6b3f5ecc5a73eef54472f83bd/ghc >--------------------------------------------------------------- commit 560b7af436b347d6b3f5ecc5a73eef54472f83bd Author: Bartosz Nitka Date: Mon Jun 13 07:35:32 2016 -0700 Use UniqFM for SigOf Summary: The Ord instance for ModuleName is currently implemented in terms of Uniques causing potential determinism problems. I plan to change it to use the actual FastStrings and in preparation for that I'm switching to UniqFM where it's possible (you need *one* Unique per key, and you can't get the keys back), so that the performance doesn't suffer. Test Plan: ./validate Reviewers: simonmar, austin, ezyang, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2320 GHC Trac Issues: #4012 (cherry picked from commit 586d55815401c54f4687d053fb033e53865e0bf1) >--------------------------------------------------------------- 560b7af436b347d6b3f5ecc5a73eef54472f83bd compiler/main/DynFlags.hs | 9 +++++---- 1 file changed, 5 insertions(+), 4 deletions(-) diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index f6598b9..0a944b7 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -164,6 +164,7 @@ import CmdLineParser import Constants import Panic import Util +import UniqFM import Maybes import MonadUtils import qualified Pretty @@ -629,10 +630,10 @@ instance Show SafeHaskellMode where instance Outputable SafeHaskellMode where ppr = text . show -type SigOf = Map ModuleName Module +type SigOf = ModuleNameEnv Module getSigOf :: DynFlags -> ModuleName -> Maybe Module -getSigOf dflags n = Map.lookup n (sigOf dflags) +getSigOf dflags n = lookupUFM (sigOf dflags) n -- | Contains not only a collection of 'GeneralFlag's but also a plethora of -- information relating to the compilation of a single file or GHC session @@ -1438,7 +1439,7 @@ defaultDynFlags mySettings = ghcMode = CompManager, ghcLink = LinkBinary, hscTarget = defaultHscTarget (sTargetPlatform mySettings), - sigOf = Map.empty, + sigOf = emptyUFM, verbosity = 0, optLevel = 0, debugLevel = 0, @@ -1981,7 +1982,7 @@ parseSigOf :: String -> SigOf parseSigOf str = case filter ((=="").snd) (readP_to_S parse str) of [(r, "")] -> r _ -> throwGhcException $ CmdLineError ("Can't parse -sig-of: " ++ str) - where parse = Map.fromList <$> sepBy parseEntry (R.char ',') + where parse = listToUFM <$> sepBy parseEntry (R.char ',') parseEntry = do n <- tok $ parseModuleName -- ToDo: deprecate this 'is' syntax? From git at git.haskell.org Mon Jul 25 14:59:29 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 25 Jul 2016 14:59:29 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Make checkFamInstConsistency less expensive (bab927c) Message-ID: <20160725145929.954A83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/bab927c9f0cb094a3e59d46372125dfe2bf514bf/ghc >--------------------------------------------------------------- commit bab927c9f0cb094a3e59d46372125dfe2bf514bf Author: Bartosz Nitka Date: Tue Jun 21 15:54:00 2016 -0700 Make checkFamInstConsistency less expensive Doing canonicalization on every comparison turned out to be very expensive. Caching the canonicalization through the smart `modulePair` constructor gives `8%` reduction in allocations on `haddock.compiler` and `8.5%` reduction in allocations on `haddock.Cabal`. Possibly other things as well, but it's really visible in Haddock. Test Plan: ./validate Reviewers: jstolarek, simonpj, austin, simonmar, bgamari Reviewed By: simonpj, simonmar Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2350 GHC Trac Issues: #12191 (cherry picked from commit 123062946dfdbcfc24abd468e24e358118b8e2eb) >--------------------------------------------------------------- bab927c9f0cb094a3e59d46372125dfe2bf514bf compiler/typecheck/FamInst.hs | 32 +++++++++++++++----------------- testsuite/tests/perf/haddock/all.T | 10 ++++++++-- 2 files changed, 23 insertions(+), 19 deletions(-) diff --git a/compiler/typecheck/FamInst.hs b/compiler/typecheck/FamInst.hs index 1d9e1ce..784bc81 100644 --- a/compiler/typecheck/FamInst.hs +++ b/compiler/typecheck/FamInst.hs @@ -40,8 +40,8 @@ import Pair import Panic import VarSet import Control.Monad -import Data.Map (Map) -import qualified Data.Map as Map +import Data.Set (Set) +import qualified Data.Set as Set #if __GLASGOW_HASKELL__ < 709 import Prelude hiding ( and ) @@ -124,28 +124,25 @@ certain that the modules in our `HscTypes.dep_finsts' are consistent.) -- whose family instances need to be checked for consistency. -- data ModulePair = ModulePair Module Module + -- Invariant: first Module < second Module + -- use the smart constructor + deriving (Ord, Eq) --- canonical order of the components of a module pair --- -canon :: ModulePair -> (Module, Module) -canon (ModulePair m1 m2) | m1 < m2 = (m1, m2) - | otherwise = (m2, m1) - -instance Eq ModulePair where - mp1 == mp2 = canon mp1 == canon mp2 - -instance Ord ModulePair where - mp1 `compare` mp2 = canon mp1 `compare` canon mp2 +-- | Smart constructor that establishes the invariant +modulePair :: Module -> Module -> ModulePair +modulePair a b + | a < b = ModulePair a b + | otherwise = ModulePair b a instance Outputable ModulePair where ppr (ModulePair m1 m2) = angleBrackets (ppr m1 <> comma <+> ppr m2) -- Sets of module pairs -- -type ModulePairSet = Map ModulePair () +type ModulePairSet = Set ModulePair listToSet :: [ModulePair] -> ModulePairSet -listToSet l = Map.fromList (zip l (repeat ())) +listToSet l = Set.fromList l checkFamInstConsistency :: [Module] -> [Module] -> TcM () checkFamInstConsistency famInstMods directlyImpMods @@ -170,7 +167,8 @@ checkFamInstConsistency famInstMods directlyImpMods -- instances of okPairs are consistent ; criticalPairs = listToSet $ allPairs famInstMods -- all pairs that we need to consider - ; toCheckPairs = Map.keys $ criticalPairs `Map.difference` okPairs + ; toCheckPairs = + Set.elems $ criticalPairs `Set.difference` okPairs -- the difference gives us the pairs we need to check now } @@ -178,7 +176,7 @@ checkFamInstConsistency famInstMods directlyImpMods } where allPairs [] = [] - allPairs (m:ms) = map (ModulePair m) ms ++ allPairs ms + allPairs (m:ms) = map (modulePair m) ms ++ allPairs ms check hpt_fam_insts (ModulePair m1 m2) = do { env1 <- getFamInsts hpt_fam_insts m1 diff --git a/testsuite/tests/perf/haddock/all.T b/testsuite/tests/perf/haddock/all.T index de45ea4..6ee448f 100644 --- a/testsuite/tests/perf/haddock/all.T +++ b/testsuite/tests/perf/haddock/all.T @@ -52,7 +52,7 @@ test('haddock.base', test('haddock.Cabal', [unless(in_tree_compiler(), skip), req_haddock ,stats_num_field('bytes allocated', - [(wordsize(64), 10941742184, 5) + [(wordsize(64), 10070330520, 5) # 2012-08-14: 3255435248 (amd64/Linux) # 2012-08-29: 3324606664 (amd64/Linux, new codegen) # 2012-10-08: 3373401360 (amd64/Linux) @@ -78,6 +78,11 @@ test('haddock.Cabal', # 2015-12-22: 10519532424 (amd64/Linux) - Lots of new Semigroup instances in Cabal # 2016-03-29: 11517963232 (amd64/Linux) - not yet investigated # 2016-03-30: 10941742184 (amd64/Linux) - defer inlining of Int* Ord methods + # 2016-04-06: 11542374816 (amd64/Linux) - CSE improvements and others + # 2016-04-07: 10963514352 (amd64/Linux) - Revert to what phabricator claims + # 2016-05-22: 11805238152 (amd64/Linux) - Make Generic1 poly-kinded + # 2016-06-05: 10997887320 (amd64/Linux) - Refactor derived Generic instances to reduce allocations + # 2016-06-21: 10070330520 (amd64/Linux) - D2350: Make checkFamInstConsistency less expensive ,(platform('i386-unknown-mingw32'), 3293415576, 5) # 2012-10-30: 1733638168 (x86/Windows) @@ -99,7 +104,7 @@ test('haddock.Cabal', test('haddock.compiler', [unless(in_tree_compiler(), skip), req_haddock ,stats_num_field('bytes allocated', - [(wordsize(64), 58017214568, 10) + [(wordsize(64), 55314944264, 10) # 2012P-08-14: 26070600504 (amd64/Linux) # 2012-08-29: 26353100288 (amd64/Linux, new CG) # 2012-09-18: 26882813032 (amd64/Linux) @@ -113,6 +118,7 @@ test('haddock.compiler', # 2015-12-03: 44721228752 (amd64/Linux) slow creep upwards # 2015-12-15: 49395782136 (amd64/Linux) more creep, following kind-equalities # 2015-12-17: 58017214568 (amd64/Linux) update Haddock to master + # 2016-06-21: 55314944264 (amd64/Linux) D2350: Make checkFamInstConsistency less expensive ,(platform('i386-unknown-mingw32'), 902576468, 10) # 2012-10-30: 13773051312 (x86/Windows) From git at git.haskell.org Mon Jul 25 14:59:32 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 25 Jul 2016 14:59:32 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Make the Ord Module independent of Unique order (2nd try) (daa058e) Message-ID: <20160725145932.4643F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/daa058e080936a7a764ffdf0b70deb85faae9044/ghc >--------------------------------------------------------------- commit daa058e080936a7a764ffdf0b70deb85faae9044 Author: Bartosz Nitka Date: Thu Jun 9 08:50:32 2016 -0700 Make the Ord Module independent of Unique order (2nd try) The `Ord Module` instance currently uses `Unique`s for comparison. We don't want to use the `Unique` order because it can introduce nondeterminism. This switches `Ord ModuleName` and `Ord UnitId` to use lexicographic ordering making `Ord Module` deterministic transitively. I've run `nofib` and it doesn't make a measurable difference. See also Note [ModuleEnv determinism and performance]. This fixes #12191 - the regression, that the previous version of this patch had. Test Plan: ./validate run nofib: P112 Reviewers: simonmar, bgamari, austin Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2354 GHC Trac Issues: #4012, #12191 (cherry picked from commit 348f2dbb835b1208f601bb1e8daa1d1d54507eda) >--------------------------------------------------------------- daa058e080936a7a764ffdf0b70deb85faae9044 compiler/basicTypes/Module.hs | 99 +++++++++++++++------- compiler/typecheck/FamInst.hs | 35 +++++++- testsuite/tests/driver/sigof01/all.T | 2 +- .../should_fail/overloadedrecfldsfail10.stderr | 4 +- testsuite/tests/rename/should_fail/T11071.stderr | 2 +- testsuite/tests/rename/should_fail/T11071a.stderr | 32 +++---- .../tests/typecheck/should_fail/T6018fail.stderr | 4 +- 7 files changed, 122 insertions(+), 56 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc daa058e080936a7a764ffdf0b70deb85faae9044 From git at git.haskell.org Mon Jul 25 14:59:34 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 25 Jul 2016 14:59:34 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Refactor match to not use Unique order (6fc97cd) Message-ID: <20160725145934.E17383A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/6fc97cd5f055d97c49646ee8c89762bd05e46b15/ghc >--------------------------------------------------------------- commit 6fc97cd5f055d97c49646ee8c89762bd05e46b15 Author: Bartosz Nitka Date: Wed Jun 29 03:27:49 2016 -0700 Refactor match to not use Unique order Unique order can introduce nondeterminism. As a step towards removing the Ord Unique instance I've refactored the code to use deterministic sets instead. Test Plan: ./validate Reviewers: simonmar, austin, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2369 GHC Trac Issues: #4012 (cherry picked from commit 9a645a1687aca21f965206f1d8c8bb23dd6410e5) >--------------------------------------------------------------- 6fc97cd5f055d97c49646ee8c89762bd05e46b15 compiler/deSugar/Match.hs | 32 +++++++++++++++++++++++--------- 1 file changed, 23 insertions(+), 9 deletions(-) diff --git a/compiler/deSugar/Match.hs b/compiler/deSugar/Match.hs index fc70cc6..ecbed46 100644 --- a/compiler/deSugar/Match.hs +++ b/compiler/deSugar/Match.hs @@ -46,6 +46,8 @@ import Util import Name import Outputable import BasicTypes ( isGenerated ) +import Unique +import UniqDFM import Control.Monad( when, unless ) import qualified Data.Map as Map @@ -196,9 +198,9 @@ match vars@(v:_) ty eqns -- Eqns *can* be empty match_group [] = panic "match_group" match_group eqns@((group,_) : _) = case group of - PgCon {} -> matchConFamily vars ty (subGroup [(c,e) | (PgCon c, e) <- eqns]) + PgCon {} -> matchConFamily vars ty (subGroupUniq [(c,e) | (PgCon c, e) <- eqns]) PgSyn {} -> matchPatSyn vars ty (dropGroup eqns) - PgLit {} -> matchLiterals vars ty (subGroup [(l,e) | (PgLit l, e) <- eqns]) + PgLit {} -> matchLiterals vars ty (subGroupOrd [(l,e) | (PgLit l, e) <- eqns]) PgAny -> matchVariables vars ty (dropGroup eqns) PgN {} -> matchNPats vars ty (dropGroup eqns) PgNpK {} -> matchNPlusKPats vars ty (dropGroup eqns) @@ -809,22 +811,34 @@ groupEquations dflags eqns same_gp :: (PatGroup,EquationInfo) -> (PatGroup,EquationInfo) -> Bool (pg1,_) `same_gp` (pg2,_) = pg1 `sameGroup` pg2 -subGroup :: Ord a => [(a, EquationInfo)] -> [[EquationInfo]] +subGroup :: (m -> [[EquationInfo]]) -- Map.elems + -> m -- Map.empty + -> (a -> m -> Maybe [EquationInfo]) -- Map.lookup + -> (a -> [EquationInfo] -> m -> m) -- Map.insert + -> [(a, EquationInfo)] -> [[EquationInfo]] -- Input is a particular group. The result sub-groups the -- equations by with particular constructor, literal etc they match. -- Each sub-list in the result has the same PatGroup -- See Note [Take care with pattern order] -subGroup group - = map reverse $ Map.elems $ foldl accumulate Map.empty group +-- Parameterized by map operations to allow different implementations +-- and constraints, eg. types without Ord instance. +subGroup elems empty lookup insert group + = map reverse $ elems $ foldl accumulate empty group where accumulate pg_map (pg, eqn) - = case Map.lookup pg pg_map of - Just eqns -> Map.insert pg (eqn:eqns) pg_map - Nothing -> Map.insert pg [eqn] pg_map - + = case lookup pg pg_map of + Just eqns -> insert pg (eqn:eqns) pg_map + Nothing -> insert pg [eqn] pg_map -- pg_map :: Map a [EquationInfo] -- Equations seen so far in reverse order of appearance +subGroupOrd :: Ord a => [(a, EquationInfo)] -> [[EquationInfo]] +subGroupOrd = subGroup Map.elems Map.empty Map.lookup Map.insert + +subGroupUniq :: Uniquable a => [(a, EquationInfo)] -> [[EquationInfo]] +subGroupUniq = + subGroup eltsUDFM emptyUDFM (flip lookupUDFM) (\k v m -> addToUDFM m k v) + {- Note [Pattern synonym groups] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ If we see From git at git.haskell.org Mon Jul 25 14:59:38 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 25 Jul 2016 14:59:38 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Add a new determinism test (7952f10) Message-ID: <20160725145938.5FBAE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/7952f10fcc47a9460dc2608225d5e55eb01b2ede/ghc >--------------------------------------------------------------- commit 7952f10fcc47a9460dc2608225d5e55eb01b2ede Author: Bartosz Nitka Date: Thu Jun 30 06:59:02 2016 -0700 Add a new determinism test This is one of the testcases that I forgot to commit (cherry picked from commit 9854f14ef0a3a6f399a1aa4c141c5e3dddcd77ff) >--------------------------------------------------------------- 7952f10fcc47a9460dc2608225d5e55eb01b2ede testsuite/tests/determinism/determ021/A.hs | 8 ++++++++ testsuite/tests/determinism/determ021/Makefile | 11 +++++++++++ .../determinism/{determ009 => determ021}/all.T | 4 ++-- .../tests/determinism/determ021/determ021.stdout | 22 ++++++++++++++++++++++ 4 files changed, 43 insertions(+), 2 deletions(-) diff --git a/testsuite/tests/determinism/determ021/A.hs b/testsuite/tests/determinism/determ021/A.hs new file mode 100644 index 0000000..773a012 --- /dev/null +++ b/testsuite/tests/determinism/determ021/A.hs @@ -0,0 +1,8 @@ +{-# LANGUAGE ApplicativeDo #-} +{-# OPTIONS_GHC -ddump-types #-} +module A where + +test2 f = do + x <- f 3 + y <- f 4 + return (x + y) diff --git a/testsuite/tests/determinism/determ021/Makefile b/testsuite/tests/determinism/determ021/Makefile new file mode 100644 index 0000000..e88edef --- /dev/null +++ b/testsuite/tests/determinism/determ021/Makefile @@ -0,0 +1,11 @@ +TOP=../../.. +include $(TOP)/mk/boilerplate.mk +include $(TOP)/mk/test.mk + +determ021: + $(RM) A.hi A.o + '$(TEST_HC)' $(TEST_HC_OPTS) -O -dinitial-unique=0 -dunique-increment=1 A.hs + $(CP) A.hi A.normal.hi + $(RM) A.hi A.o + '$(TEST_HC)' $(TEST_HC_OPTS) -O -dinitial-unique=16777215 -dunique-increment=-1 A.hs + diff A.hi A.normal.hi diff --git a/testsuite/tests/determinism/determ009/all.T b/testsuite/tests/determinism/determ021/all.T similarity index 50% copy from testsuite/tests/determinism/determ009/all.T copy to testsuite/tests/determinism/determ021/all.T index 7cae393..35af362 100644 --- a/testsuite/tests/determinism/determ009/all.T +++ b/testsuite/tests/determinism/determ021/all.T @@ -1,4 +1,4 @@ -test('determ009', +test('determ021', extra_clean(['A.o', 'A.hi', 'A.normal.hi']), run_command, - ['$MAKE -s --no-print-directory determ009']) + ['$MAKE -s --no-print-directory determ021']) diff --git a/testsuite/tests/determinism/determ021/determ021.stdout b/testsuite/tests/determinism/determ021/determ021.stdout new file mode 100644 index 0000000..747064f --- /dev/null +++ b/testsuite/tests/determinism/determ021/determ021.stdout @@ -0,0 +1,22 @@ +[1 of 1] Compiling A ( A.hs, A.o ) +TYPE SIGNATURES + test2 :: + forall t b (f :: * -> *). + (Num b, Num t, Applicative f) => + (t -> f b) -> f b +TYPE CONSTRUCTORS +COERCION AXIOMS +Dependent modules: [] +Dependent packages: [base-4.9.0.0, ghc-prim-0.5.0.0, + integer-gmp-1.0.0.1] +[1 of 1] Compiling A ( A.hs, A.o ) +TYPE SIGNATURES + test2 :: + forall t b (f :: * -> *). + (Num b, Num t, Applicative f) => + (t -> f b) -> f b +TYPE CONSTRUCTORS +COERCION AXIOMS +Dependent modules: [] +Dependent packages: [base-4.9.0.0, ghc-prim-0.5.0.0, + integer-gmp-1.0.0.1] From git at git.haskell.org Mon Jul 25 14:59:41 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 25 Jul 2016 14:59:41 +0000 (UTC) Subject: [commit: ghc] wip/ghc-8.0-det: Make accept (7dd591c) Message-ID: <20160725145941.0C78D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ghc-8.0-det Link : http://ghc.haskell.org/trac/ghc/changeset/7dd591c42af3bb3abed4b119a3acaccbe6fd7940/ghc >--------------------------------------------------------------- commit 7dd591c42af3bb3abed4b119a3acaccbe6fd7940 Author: Bartosz Nitka Date: Wed Jul 13 12:41:45 2016 -0700 Make accept This updates the test output to account for determinism related reordering. There's no corresponding commit in the master branch. >--------------------------------------------------------------- 7dd591c42af3bb3abed4b119a3acaccbe6fd7940 testsuite/tests/ado/ado004.stderr | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/testsuite/tests/ado/ado004.stderr b/testsuite/tests/ado/ado004.stderr index 2bb2e6d..8f5a816 100644 --- a/testsuite/tests/ado/ado004.stderr +++ b/testsuite/tests/ado/ado004.stderr @@ -6,8 +6,8 @@ TYPE SIGNATURES (Num b, Num t, Applicative f) => (t -> f b) -> f b test2a :: - forall (f :: * -> *) b t. - (Num t, Num b, Functor f) => + forall t b (f :: * -> *). + (Num b, Num t, Functor f) => (t -> f b) -> f b test2b :: forall (m :: * -> *) a t. (Num t, Monad m) => (t -> a) -> m a From git at git.haskell.org Mon Jul 25 18:36:29 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 25 Jul 2016 18:36:29 +0000 (UTC) Subject: [commit: ghc] ghc-8.0: Fix bytecode gen to deal with rep-polymorphism (a8d4759) Message-ID: <20160725183629.D806C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.0 Link : http://ghc.haskell.org/trac/ghc/changeset/a8d4759eb7add57bcee29cc17023f5e900c44f44/ghc >--------------------------------------------------------------- commit a8d4759eb7add57bcee29cc17023f5e900c44f44 Author: Simon Peyton Jones Date: Thu May 26 14:20:29 2016 +0100 Fix bytecode gen to deal with rep-polymorphism When faced runtime-rep-polymorphic code from a pattern-synonym matcher, the bytecode generator was treating the result as lifted, which it isn't. The fix is just to treat those rep-polymorphic continuations like unlifted types, and add a dummy arg. Trac #12007 is a case in point. (cherry picked from commit 0f1e315b9274725c4a2c975f4d06a5c956cf5385) >--------------------------------------------------------------- a8d4759eb7add57bcee29cc17023f5e900c44f44 compiler/ghci/ByteCodeGen.hs | 37 ++++++++++++++++++++---------- testsuite/tests/ghci/scripts/T12007.hs | 7 ++++++ testsuite/tests/ghci/scripts/T12007.script | 3 +++ testsuite/tests/ghci/scripts/T12007.stdout | 1 + testsuite/tests/ghci/scripts/all.T | 1 + 5 files changed, 37 insertions(+), 12 deletions(-) diff --git a/compiler/ghci/ByteCodeGen.hs b/compiler/ghci/ByteCodeGen.hs index bf11edb..9a78054 100644 --- a/compiler/ghci/ByteCodeGen.hs +++ b/compiler/ghci/ByteCodeGen.hs @@ -31,6 +31,7 @@ import Literal import PrimOp import CoreFVs import Type +import Kind ( isLiftedTypeKind ) import DataCon import TyCon import Util @@ -486,35 +487,47 @@ schemeE d s p (AnnLet binds (_,body)) = do thunk_codes <- sequence compile_binds return (alloc_code `appOL` concatOL thunk_codes `appOL` body_code) --- introduce a let binding for a ticked case expression. This rule +-- Introduce a let binding for a ticked case expression. This rule -- *should* only fire when the expression was not already let-bound -- (the code gen for let bindings should take care of that). Todo: we -- call exprFreeVars on a deAnnotated expression, this may not be the -- best way to calculate the free vars but it seemed like the least -- intrusive thing to do schemeE d s p exp@(AnnTick (Breakpoint _id _fvs) _rhs) - = if isUnliftedType ty - then do - -- If the result type is unlifted, then we must generate + | isLiftedTypeKind (typeKind ty) + = do id <- newId ty + -- Todo: is emptyVarSet correct on the next line? + let letExp = AnnLet (AnnNonRec id (fvs, exp)) (emptyDVarSet, AnnVar id) + schemeE d s p letExp + + | otherwise + = do -- If the result type is not definitely lifted, then we must generate -- let f = \s . tick e -- in f realWorld# -- When we stop at the breakpoint, _result will have an unlifted -- type and hence won't be bound in the environment, but the -- breakpoint will otherwise work fine. + -- + -- NB (Trac #12007) this /also/ applies for if (ty :: TYPE r), where + -- r :: RuntimeRep is a variable. This can happen in the + -- continuations for a pattern-synonym matcher + -- match = /\(r::RuntimeRep) /\(a::TYPE r). + -- \(k :: Int -> a) \(v::T). + -- case v of MkV n -> k n + -- Here (k n) :: a :: Type r, so we don't know if it's lifted + -- or not; but that should be fine provided we add that void arg. + id <- newId (mkFunTy realWorldStatePrimTy ty) st <- newId realWorldStatePrimTy let letExp = AnnLet (AnnNonRec id (fvs, AnnLam st (emptyDVarSet, exp))) (emptyDVarSet, (AnnApp (emptyDVarSet, AnnVar id) (emptyDVarSet, AnnVar realWorldPrimId))) schemeE d s p letExp - else do - id <- newId ty - -- Todo: is emptyVarSet correct on the next line? - let letExp = AnnLet (AnnNonRec id (fvs, exp)) (emptyDVarSet, AnnVar id) - schemeE d s p letExp - where exp' = deAnnotate' exp - fvs = exprFreeVarsDSet exp' - ty = exprType exp' + + where + exp' = deAnnotate' exp + fvs = exprFreeVarsDSet exp' + ty = exprType exp' -- ignore other kinds of tick schemeE d s p (AnnTick _ (_, rhs)) = schemeE d s p rhs diff --git a/testsuite/tests/ghci/scripts/T12007.hs b/testsuite/tests/ghci/scripts/T12007.hs new file mode 100644 index 0000000..c678727 --- /dev/null +++ b/testsuite/tests/ghci/scripts/T12007.hs @@ -0,0 +1,7 @@ +{-# LANGUAGE PatternSynonyms #-} +module T12007 where + +data Foo a = Foo a a + +pattern A a1 a2 = Foo a1 a2 +pattern B a1 a2 = A a1 a2 diff --git a/testsuite/tests/ghci/scripts/T12007.script b/testsuite/tests/ghci/scripts/T12007.script new file mode 100644 index 0000000..8e6a27a --- /dev/null +++ b/testsuite/tests/ghci/scripts/T12007.script @@ -0,0 +1,3 @@ +:l T12007 +let f (B x y) = (y,x) +f (Foo 'c' 'd') diff --git a/testsuite/tests/ghci/scripts/T12007.stdout b/testsuite/tests/ghci/scripts/T12007.stdout new file mode 100644 index 0000000..a6a2425 --- /dev/null +++ b/testsuite/tests/ghci/scripts/T12007.stdout @@ -0,0 +1 @@ +('d','c') diff --git a/testsuite/tests/ghci/scripts/all.T b/testsuite/tests/ghci/scripts/all.T index 47a775b..a0b5f1b 100755 --- a/testsuite/tests/ghci/scripts/all.T +++ b/testsuite/tests/ghci/scripts/all.T @@ -248,3 +248,4 @@ test('T11524a', normal, ghci_script, ['T11524a.script']) test('T11456', normal, ghci_script, ['T11456.script']) test('TypeAppData', normal, ghci_script, ['TypeAppData.script']) test('T11376', normal, ghci_script, ['T11376.script']) +test('T12007', normal, ghci_script, ['T12007.script']) From git at git.haskell.org Mon Jul 25 18:36:32 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 25 Jul 2016 18:36:32 +0000 (UTC) Subject: [commit: ghc] ghc-8.0: Abort the build when a Core plugin pass is specified in stage1 compiler (151f193) Message-ID: <20160725183632.8263C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.0 Link : http://ghc.haskell.org/trac/ghc/changeset/151f19385cdc6ee40db97e773b1a869b324c2059/ghc >--------------------------------------------------------------- commit 151f19385cdc6ee40db97e773b1a869b324c2059 Author: Ömer Sinan Ağacan Date: Fri Jun 17 07:54:28 2016 +0000 Abort the build when a Core plugin pass is specified in stage1 compiler This also makes the behavior the same with frontend plugin errors -- frontend was failing with an exception (`CmdLineError`) while the simplifier was just ignoring plugins. Now we abort with `CmdLineError` in both cases with a slightly improved error message. Test Plan: - add tests (will add tests once #12197 is implemented) - validate (done) Reviewers: austin, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2334 GHC Trac Issues: #11690 (cherry picked from commit 930a525a5906fdd65ab0c3e804085d5875517a20) >--------------------------------------------------------------- 151f19385cdc6ee40db97e773b1a869b324c2059 compiler/main/DynamicLoading.hs | 23 +++++++++++++++++++++++ compiler/simplCore/SimplCore.hs | 8 +++++++- ghc/Main.hs | 5 +++-- 3 files changed, 33 insertions(+), 3 deletions(-) diff --git a/compiler/main/DynamicLoading.hs b/compiler/main/DynamicLoading.hs index e7a2b95..2b2365f 100644 --- a/compiler/main/DynamicLoading.hs +++ b/compiler/main/DynamicLoading.hs @@ -19,6 +19,8 @@ module DynamicLoading ( getValueSafely, getHValueSafely, lessUnsafeCoerce +#else + pluginError, #endif ) where @@ -55,6 +57,16 @@ import Hooks import Data.Maybe ( mapMaybe ) import GHC.Exts ( unsafeCoerce# ) +#else + +import Module ( ModuleName, moduleNameString ) +import Panic + +import Data.List ( intercalate ) + +#endif + +#ifdef GHCI loadPlugins :: HscEnv -> IO [(ModuleName, Plugin, [CommandLineOption])] loadPlugins hsc_env @@ -243,4 +255,15 @@ throwCmdLineErrorS dflags = throwCmdLineError . showSDoc dflags throwCmdLineError :: String -> IO a throwCmdLineError = throwGhcExceptionIO . CmdLineError + +#else + +pluginError :: [ModuleName] -> a +pluginError modnames = throwGhcException (CmdLineError msg) + where + msg = "not built for interactive use - can't load plugins (" + -- module names are not z-encoded + ++ intercalate ", " (map moduleNameString modnames) + ++ ")" + #endif diff --git a/compiler/simplCore/SimplCore.hs b/compiler/simplCore/SimplCore.hs index 5fadd03..3abc9bc 100644 --- a/compiler/simplCore/SimplCore.hs +++ b/compiler/simplCore/SimplCore.hs @@ -57,6 +57,8 @@ import Control.Monad #ifdef GHCI import DynamicLoading ( loadPlugins ) import Plugins ( installCoreToDos ) +#else +import DynamicLoading ( pluginError ) #endif {- @@ -333,7 +335,11 @@ getCoreToDo dflags addPluginPasses :: [CoreToDo] -> CoreM [CoreToDo] #ifndef GHCI -addPluginPasses builtin_passes = return builtin_passes +addPluginPasses builtin_passes + = do { dflags <- getDynFlags + ; let pluginMods = pluginModNames dflags + ; unless (null pluginMods) (pluginError pluginMods) + ; return builtin_passes } #else addPluginPasses builtin_passes = do { hsc_env <- getHscEnv diff --git a/ghc/Main.hs b/ghc/Main.hs index 5605438..1a6cbeb 100644 --- a/ghc/Main.hs +++ b/ghc/Main.hs @@ -32,6 +32,8 @@ import GHCi.UI ( interactiveUI, ghciWelcomeMsg, defaultGhciSettings ) #ifdef GHCI import DynamicLoading import Plugins +#else +import DynamicLoading ( pluginError ) #endif import Module ( ModuleName ) @@ -841,8 +843,7 @@ dumpPackagesSimple dflags = putMsg dflags (pprPackagesSimple dflags) doFrontend :: ModuleName -> [(String, Maybe Phase)] -> Ghc () #ifndef GHCI -doFrontend _ _ = - throwGhcException (CmdLineError "not built for interactive use") +doFrontend modname _ = pluginError [modname] #else doFrontend modname srcs = do hsc_env <- getSession From git at git.haskell.org Mon Jul 25 18:36:35 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 25 Jul 2016 18:36:35 +0000 (UTC) Subject: [commit: ghc] ghc-8.0: Fix GetTime.c on Darwin with clock_gettime (a0f1809) Message-ID: <20160725183635.301A83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.0 Link : http://ghc.haskell.org/trac/ghc/changeset/a0f1809742160ca0c07778f91f3e2a8ea147c0a4/ghc >--------------------------------------------------------------- commit a0f1809742160ca0c07778f91f3e2a8ea147c0a4 Author: Misty De Meo Date: Wed Jun 15 15:02:13 2016 -0700 Fix GetTime.c on Darwin with clock_gettime On Darwin versions with clock_gettime, #ifdefs will prevent the mach-specific time functions from being used in most places, and the mach time headers won't be included; however, this section was guarded incorrectly and would still try to use them. Fixes #12195. (cherry picked from commit b7b130c5102948b38aaba723044288e16a80d492) >--------------------------------------------------------------- a0f1809742160ca0c07778f91f3e2a8ea147c0a4 rts/posix/GetTime.c | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/rts/posix/GetTime.c b/rts/posix/GetTime.c index def78a4..f6182f9 100644 --- a/rts/posix/GetTime.c +++ b/rts/posix/GetTime.c @@ -29,14 +29,14 @@ // we'll implement getProcessCPUTime() and getProcessElapsedTime() // separately, using getrusage() and gettimeofday() respectively -#ifdef darwin_HOST_OS +#if !defined(HAVE_CLOCK_GETTIME) && defined(darwin_HOST_OS) static uint64_t timer_scaling_factor_numer = 0; static uint64_t timer_scaling_factor_denom = 0; #endif void initializeTimer() { -#ifdef darwin_HOST_OS +#if !defined(HAVE_CLOCK_GETTIME) && defined(darwin_HOST_OS) mach_timebase_info_data_t info; (void) mach_timebase_info(&info); timer_scaling_factor_numer = (uint64_t)info.numer; From git at git.haskell.org Mon Jul 25 18:36:38 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 25 Jul 2016 18:36:38 +0000 (UTC) Subject: [commit: ghc] ghc-8.0: Don't quantify over Refl in a RULE (cd9c4a5) Message-ID: <20160725183638.45EAC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.0 Link : http://ghc.haskell.org/trac/ghc/changeset/cd9c4a5db6500bb61bee2904a14d5969b1910b5a/ghc >--------------------------------------------------------------- commit cd9c4a5db6500bb61bee2904a14d5969b1910b5a Author: Simon Peyton Jones Date: Mon Jun 20 15:48:09 2016 +0100 Don't quantify over Refl in a RULE This fixes Trac #12212. It's quite hard to provoke, but I've added a standalone test case that does so. The issue is explained in Note [Evidence foralls] in Specialise. (cherry picked from commit d09e982c534b20908064f36d701a1a3a6a2eb55a) >--------------------------------------------------------------- cd9c4a5db6500bb61bee2904a14d5969b1910b5a compiler/specialise/Specialise.hs | 35 ++++++++++++++++++---- testsuite/tests/simplCore/should_compile/T12212.hs | 17 +++++++++++ .../tests/simplCore/should_compile/T7785.stderr | 2 +- testsuite/tests/simplCore/should_compile/all.T | 1 + 4 files changed, 48 insertions(+), 7 deletions(-) diff --git a/compiler/specialise/Specialise.hs b/compiler/specialise/Specialise.hs index 0c1d398..33ce1ac 100644 --- a/compiler/specialise/Specialise.hs +++ b/compiler/specialise/Specialise.hs @@ -12,8 +12,8 @@ module Specialise ( specProgram, specUnfolding ) where import Id import TcType hiding( substTy ) import Type hiding( substTy, extendTvSubstList ) -import Coercion( Coercion ) import Module( Module, HasModule(..) ) +import Coercion( Coercion ) import CoreMonad import qualified CoreSubst import CoreUnfold @@ -22,7 +22,7 @@ import VarEnv import CoreSyn import Rules import CoreUtils ( exprIsTrivial, applyTypeToArgs, mkCast ) -import CoreFVs ( exprFreeVars, exprsFreeVars, idFreeVars ) +import CoreFVs ( exprFreeVars, exprsFreeVars, idFreeVars, exprsFreeIdsList ) import UniqSupply import Name import MkId ( voidArgId, voidPrimId ) @@ -1230,6 +1230,9 @@ specCalls mb_mod env rules_for_me calls_for_me fn rhs -- Construct the new binding -- f1 = SUBST[a->t1,c->t3, d1->d1', d2->d2'] (/\ b -> rhs) + -- PLUS the rule + -- RULE "SPEC f" forall b d1' d2'. f b d1' d2' = f1 b + -- In the rule, d1' and d2' are just wildcards, not used in the RHS -- PLUS the usage-details -- { d1' = dx1; d2' = dx2 } -- where d1', d2' are cloned versions of d1,d2, with the type substitution @@ -1252,9 +1255,10 @@ specCalls mb_mod env rules_for_me calls_for_me fn rhs ; let (rhs_env2, dx_binds, spec_dict_args) = bindAuxiliaryDicts rhs_env rhs_dict_ids call_ds inst_dict_ids ty_args = mk_ty_args call_ts poly_tyvars - rule_args = ty_args ++ map varToCoreExpr inst_dict_ids - -- varToCoreExpr does the right thing for CoVars - rule_bndrs = poly_tyvars ++ inst_dict_ids + ev_args = map varToCoreExpr inst_dict_ids -- ev_args, ev_bndrs: + ev_bndrs = exprsFreeIdsList ev_args -- See Note [Evidence foralls] + rule_args = ty_args ++ ev_args + rule_bndrs = poly_tyvars ++ ev_bndrs ; dflags <- getDynFlags ; if already_covered dflags rule_args then @@ -1338,7 +1342,26 @@ specCalls mb_mod env rules_for_me calls_for_me fn rhs ; return (Just ((spec_f_w_arity, spec_rhs), final_uds, spec_env_rule)) } } -{- +{- Note [Evidence foralls] +~~~~~~~~~~~~~~~~~~~~~~~~~~ +Suppose (Trac #12212) that we are specialising + f :: forall a b. (Num a, F a ~ F b) => blah +with a=b=Int. Then the RULE will be something like + RULE forall (d:Num Int) (g :: F Int ~ F Int). + f Int Int d g = f_spec +But both varToCoreExpr (when constructing the LHS args), and the +simplifier (when simplifying the LHS args), will transform to + RULE forall (d:Num Int) (g :: F Int ~ F Int). + f Int Int d = f_spec +by replacing g with Refl. So now 'g' is unbound, which results in a later +crash. So we use Refl right off the bat, and do not forall-quantify 'g': + * varToCoreExpr generates a Refl + * exprsFreeIdsList returns the Ids bound by the args, + which won't include g + +You might wonder if this will match as often, but the simplifer replaces +complicated Refl coercions with Refl pretty aggressively. + Note [Orphans and auto-generated rules] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ When we specialise an INLINEABLE function, or when we have diff --git a/testsuite/tests/simplCore/should_compile/T12212.hs b/testsuite/tests/simplCore/should_compile/T12212.hs new file mode 100644 index 0000000..ed284c3 --- /dev/null +++ b/testsuite/tests/simplCore/should_compile/T12212.hs @@ -0,0 +1,17 @@ +{-# LANGUAGE TypeFamilies #-} + +module T12212 where + +type family F a +type instance F Int = Int + +foo :: a -> F a +{-# NOINLINE foo #-} +foo = undefined + +-- Inferred type +-- forall a b. (Num a, F a ~# F b) => a -> b -> [F a] +f x y = [ foo x, foo y ] ++ f (x-1) y + +-- Specialised call to f @ Int @ Int dNumInt +g = f (3::Int) (4::Int) diff --git a/testsuite/tests/simplCore/should_compile/T7785.stderr b/testsuite/tests/simplCore/should_compile/T7785.stderr index db80b99..c71a077 100644 --- a/testsuite/tests/simplCore/should_compile/T7785.stderr +++ b/testsuite/tests/simplCore/should_compile/T7785.stderr @@ -1,7 +1,7 @@ ==================== Tidy Core rules ==================== "SPEC shared @ []" [ALWAYS] - forall ($dMyFunctor :: MyFunctor []) (irred :: Domain [] Int). + forall (irred :: Domain [] Int) ($dMyFunctor :: MyFunctor []). shared @ [] $dMyFunctor irred = bar_$sshared diff --git a/testsuite/tests/simplCore/should_compile/all.T b/testsuite/tests/simplCore/should_compile/all.T index f50fd83..36b94c7 100644 --- a/testsuite/tests/simplCore/should_compile/all.T +++ b/testsuite/tests/simplCore/should_compile/all.T @@ -232,3 +232,4 @@ test('T11232', normal, compile, ['-O2']) test('T11562', normal, compile, ['-O2']) test('T11644', normal, compile, ['-O2']) test('T11742', normal, compile, ['-O2']) +test('T12212', normal, compile, ['-O']) From git at git.haskell.org Mon Jul 25 18:36:41 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 25 Jul 2016 18:36:41 +0000 (UTC) Subject: [commit: ghc] ghc-8.0: Allow unlifted types in pattern synonym result type (66d70fd) Message-ID: <20160725183641.5D9983A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.0 Link : http://ghc.haskell.org/trac/ghc/changeset/66d70fd68b4b52f0e6751679f5702964c122f767/ghc >--------------------------------------------------------------- commit 66d70fd68b4b52f0e6751679f5702964c122f767 Author: Matthew Pickering Date: Sun May 22 11:52:26 2016 +0100 Allow unlifted types in pattern synonym result type Fixes #12094 Test Plan: ./validate Reviewers: austin, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2255 GHC Trac Issues: #12094 (cherry picked from commit 8c9b8a31dd9e085704ecac3361a64f196a0bc09d) >--------------------------------------------------------------- 66d70fd68b4b52f0e6751679f5702964c122f767 compiler/typecheck/TcPatSyn.hs | 6 ++++-- testsuite/tests/patsyn/should_compile/T12094.hs | 8 ++++++++ testsuite/tests/patsyn/should_compile/all.T | 1 + 3 files changed, 13 insertions(+), 2 deletions(-) diff --git a/compiler/typecheck/TcPatSyn.hs b/compiler/typecheck/TcPatSyn.hs index 3cf1a86..5113856 100644 --- a/compiler/typecheck/TcPatSyn.hs +++ b/compiler/typecheck/TcPatSyn.hs @@ -14,7 +14,7 @@ module TcPatSyn ( tcPatSynSig, tcInferPatSynDecl, tcCheckPatSynDecl import HsSyn import TcPat import TcHsType( tcImplicitTKBndrs, tcExplicitTKBndrs - , tcHsContext, tcHsLiftedType, tcHsOpenType, kindGeneralize ) + , tcHsContext, tcHsOpenType, kindGeneralize ) import TcRnMonad import TcEnv import TcMType @@ -117,7 +117,9 @@ tcPatSynSig name sig_ty do { req <- tcHsContext hs_req ; prov <- tcHsContext hs_prov ; arg_tys <- mapM tcHsOpenType (hs_arg_tys :: [LHsType Name]) - ; body_ty <- tcHsLiftedType hs_body_ty + -- A (literal) pattern can be unlifted; + -- -- e.g. pattern Zero <- 0# (Trac #12094) + ; body_ty <- tcHsOpenType hs_body_ty ; let bound_tvs = unionVarSets [ allBoundVariabless req , allBoundVariabless prov diff --git a/testsuite/tests/patsyn/should_compile/T12094.hs b/testsuite/tests/patsyn/should_compile/T12094.hs new file mode 100644 index 0000000..5b4e6b4 --- /dev/null +++ b/testsuite/tests/patsyn/should_compile/T12094.hs @@ -0,0 +1,8 @@ +{-# LANGUAGE MagicHash #-} +{-# LANGUAGE PatternSynonyms #-} +module T12094 where + +import GHC.Exts (Int#) + +pattern Zero :: Int# -- commenting out this line works +pattern Zero <- 0# diff --git a/testsuite/tests/patsyn/should_compile/all.T b/testsuite/tests/patsyn/should_compile/all.T index 8eddc7b..29a1e33 100644 --- a/testsuite/tests/patsyn/should_compile/all.T +++ b/testsuite/tests/patsyn/should_compile/all.T @@ -51,3 +51,4 @@ test('T11283', normal, compile, ['']) test('T11367', normal, compile, ['']) test('T11351', normal, compile, ['']) test('T11633', normal, compile, ['']) +test('T12094', normal, compile, ['']) From git at git.haskell.org Mon Jul 25 18:36:44 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 25 Jul 2016 18:36:44 +0000 (UTC) Subject: [commit: ghc] ghc-8.0: Trac #11554 fix loopy GADTs (2a09e6e) Message-ID: <20160725183644.94EE43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.0 Link : http://ghc.haskell.org/trac/ghc/changeset/2a09e6edca54ce8788aba724f0a4156876e6ded0/ghc >--------------------------------------------------------------- commit 2a09e6edca54ce8788aba724f0a4156876e6ded0 Author: Alexander Vieth Date: Mon Jun 20 09:22:18 2016 +0200 Trac #11554 fix loopy GADTs Summary: Fixes T11554 Reviewers: goldfire, thomie, simonpj, austin, bgamari Reviewed By: thomie, simonpj, bgamari Subscribers: simonpj, goldfire, thomie Differential Revision: https://phabricator.haskell.org/D2283 GHC Trac Issues: #11554 (cherry picked from commit 430f5c84dac1eab550110d543831a70516b5cac8) >--------------------------------------------------------------- 2a09e6edca54ce8788aba724f0a4156876e6ded0 compiler/typecheck/TcHsType.hs | 26 +++++++++++++++++++++++++- docs/users_guide/bugs.rst | 7 ------- testsuite/tests/polykinds/T11554.hs | 10 ++++++++++ testsuite/tests/polykinds/T11554.stderr | 7 +++++++ testsuite/tests/polykinds/all.T | 1 + 5 files changed, 43 insertions(+), 8 deletions(-) diff --git a/compiler/typecheck/TcHsType.hs b/compiler/typecheck/TcHsType.hs index c533399..ea6a292 100644 --- a/compiler/typecheck/TcHsType.hs +++ b/compiler/typecheck/TcHsType.hs @@ -881,7 +881,11 @@ tcTyVar mode name -- Could be a tyvar, a tycon, or a datacon ; case thing of ATyVar _ tv -> return (mkTyVarTy tv, tyVarKind tv) - ATcTyCon tc_tc -> do { check_tc tc_tc + ATcTyCon tc_tc -> do { -- See Note [GADT kind self-reference] + unless + (isTypeLevel (mode_level mode)) + (promotionErr name TyConPE) + ; check_tc tc_tc ; tc <- get_loopy_tc name tc_tc ; handle_tyfams tc tc_tc } -- mkNakedTyConApp: see Note [Type-checking inside the knot] @@ -1003,6 +1007,26 @@ look at the TyCon or Class involved. This is horribly delicate. I hate it. A good example of how delicate it is can be seen in Trac #7903. +Note [GADT kind self-reference] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + +A promoted type cannot be used in the body of that type's declaration. +Trac #11554 shows this example, which made GHC loop: + + import Data.Kind + data P (x :: k) = Q + data A :: Type where + B :: forall (a :: A). P a -> A + +In order to check the constructor B, we need have the promoted type A, but in +order to get that promoted type, B must first be checked. To prevent looping, a +TyConPE promotion error is given when tcTyVar checks an ATcTyCon in kind mode. +Any ATcTyCon is a TyCon being defined in the current recursive group (see data +type decl for TcTyThing), and all such TyCons are illegal in kinds. + +Trac #11962 proposes checking the head of a data declaration separately from +its constructors. This would allow the example above to pass. + Note [Body kind of a HsForAllTy] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ The body of a forall is usually a type, but in principle diff --git a/docs/users_guide/bugs.rst b/docs/users_guide/bugs.rst index c4ac9ce..a1ec885 100644 --- a/docs/users_guide/bugs.rst +++ b/docs/users_guide/bugs.rst @@ -479,13 +479,6 @@ Bugs in GHC in the compiler's internal representation and can be unified producing unexpected results. See :ghc-ticket:`11715` for one example. -- :ghc-flag:`-XTypeInType` still has a few rough edges, especially where - it interacts with other advanced type-system features. For instance, - this definition causes the typechecker to loop (:ghc-ticket:`11559`), :: - - data A :: Type where - B :: forall (a :: A). A - - There is known to be maleficent interactions between weak references and laziness. Particularly, it has been observed that placing a thunk containing a reference to a weak reference inside of another weak reference may cause diff --git a/testsuite/tests/polykinds/T11554.hs b/testsuite/tests/polykinds/T11554.hs new file mode 100644 index 0000000..e7a35bd --- /dev/null +++ b/testsuite/tests/polykinds/T11554.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE GADTs, TypeInType, RankNTypes #-} + +module T11554 where + +import Data.Kind + +data P (x :: k) = Q + +data A :: Type where + B :: forall (a :: A). P a -> A diff --git a/testsuite/tests/polykinds/T11554.stderr b/testsuite/tests/polykinds/T11554.stderr new file mode 100644 index 0000000..e3045c8 --- /dev/null +++ b/testsuite/tests/polykinds/T11554.stderr @@ -0,0 +1,7 @@ + +T11554.hs:10:21: error: + • Type constructor ‘A’ cannot be used here + (it is defined and used in the same recursive group) + • In the kind ‘A’ + In the definition of data constructor ‘B’ + In the data declaration for ‘A’ diff --git a/testsuite/tests/polykinds/all.T b/testsuite/tests/polykinds/all.T index 522ae43..b2e1c7b 100644 --- a/testsuite/tests/polykinds/all.T +++ b/testsuite/tests/polykinds/all.T @@ -145,3 +145,4 @@ test('T11611', normal, compile_fail, ['']) test('T11648', normal, compile, ['']) test('T11648b', normal, compile_fail, ['']) test('KindVType', normal, compile_fail, ['']) +test('T11554', normal, compile_fail, ['']) From git at git.haskell.org Mon Jul 25 18:36:47 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 25 Jul 2016 18:36:47 +0000 (UTC) Subject: [commit: ghc] ghc-8.0: Don't omit any evidence bindings (b4bdbe4) Message-ID: <20160725183647.9CF043A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.0 Link : http://ghc.haskell.org/trac/ghc/changeset/b4bdbe4957ae8b82c4cda5584203b44d3c4f004f/ghc >--------------------------------------------------------------- commit b4bdbe4957ae8b82c4cda5584203b44d3c4f004f Author: Simon Peyton Jones Date: Fri Jun 24 15:49:05 2016 +0100 Don't omit any evidence bindings This fixes Trac #12156, where we were omitting to make an evidence binding (because cec_suppress was on), but yet the program was compiled and run. The fix is easy, and involves deleting code :-). (cherry picked from commit af21e38855f7d517774542b360178b05045ecb08) >--------------------------------------------------------------- b4bdbe4957ae8b82c4cda5584203b44d3c4f004f compiler/typecheck/TcErrors.hs | 57 +++++++++++----------- .../should_compile/T12156.hs} | 3 ++ .../partial-sigs/should_compile/T12156.stderr | 3 ++ testsuite/tests/partial-sigs/should_compile/all.T | 1 + 4 files changed, 36 insertions(+), 28 deletions(-) diff --git a/compiler/typecheck/TcErrors.hs b/compiler/typecheck/TcErrors.hs index 991a559..406f13d 100644 --- a/compiler/typecheck/TcErrors.hs +++ b/compiler/typecheck/TcErrors.hs @@ -244,6 +244,16 @@ data HoleChoice | HoleWarn -- Defer to runtime, emit a compile-time warning | HoleDefer -- Defer to runtime, no warning +instance Outputable HoleChoice where + ppr HoleError = text "HoleError" + ppr HoleWarn = text "HoleWarn" + ppr HoleDefer = text "HoleDefer" + +instance Outputable TypeErrorChoice where + ppr TypeError = text "TypeError" + ppr TypeWarn = text "TypeWarn" + ppr TypeDefer = text "TypeDefer" + data ReportErrCtxt = CEC { cec_encl :: [Implication] -- Enclosing implications -- (innermost first) @@ -421,7 +431,7 @@ reportWanteds ctxt tc_lvl (WC { wc_simple = simples, wc_insol = insols, wc_impl , ("skolem eq1", very_wrong, True, mkSkolReporter) , ("skolem eq2", skolem_eq, True, mkSkolReporter) , ("non-tv eq", non_tv_eq, True, mkSkolReporter) - , ("Out of scope", is_out_of_scope, True, mkHoleReporter) + , ("Out of scope", is_out_of_scope, True, mkHoleReporter) , ("Holes", is_hole, False, mkHoleReporter) -- The only remaining equalities are alpha ~ ty, @@ -528,14 +538,14 @@ mkSkolReporter ctxt cts mkHoleReporter :: Reporter -- Reports errors one at a time mkHoleReporter ctxt - = mapM_ $ \ct -> - do { err <- mkHoleError ctxt ct - ; maybeReportHoleError ctxt ct err - ; maybeAddDeferredHoleBinding ctxt err ct } + = mapM_ $ \ct -> do { err <- mkHoleError ctxt ct + ; maybeReportHoleError ctxt ct err + ; maybeAddDeferredHoleBinding ctxt err ct } mkUserTypeErrorReporter :: Reporter mkUserTypeErrorReporter ctxt - = mapM_ $ \ct -> maybeReportError ctxt =<< mkUserTypeError ctxt ct + = mapM_ $ \ct -> do { err <- mkUserTypeError ctxt ct + ; maybeReportError ctxt err } mkUserTypeError :: ReportErrCtxt -> Ct -> TcM ErrMsg mkUserTypeError ctxt ct = mkErrorMsgFromCt ctxt ct @@ -553,7 +563,6 @@ mkGroupReporter :: (ReportErrCtxt -> [Ct] -> TcM ErrMsg) -- and report only the first (to avoid a cascade) mkGroupReporter mk_err ctxt cts = mapM_ (reportGroup mk_err ctxt) (equivClasses cmp_loc cts) - where cmp_lhs_type :: Ct -> Ct -> Ordering cmp_lhs_type ct1 ct2 @@ -577,9 +586,13 @@ reportGroup mk_err ctxt cts = (_, cts') -> do { err <- mk_err ctxt cts' ; maybeReportError ctxt err - ; mapM_ (maybeAddDeferredBinding ctxt err) cts' } - -- Add deferred bindings for all - -- But see Note [Always warn with -fdefer-type-errors] + -- But see Note [Always warn with -fdefer-type-errors] + ; traceTc "reportGroup" (ppr cts') + ; mapM_ (addDeferredBinding ctxt err) cts' } + -- Add deferred bindings for all + -- Redundant if we are going to abort compilation, + -- but that's hard to know for sure, and if we don't + -- abort, we need bindings for all (e.g. Trac #12156) where isMonadFailInstanceMissing ct = case ctLocOrigin (ctLoc ct) of @@ -649,23 +662,10 @@ addDeferredBinding ctxt err ct maybeAddDeferredHoleBinding :: ReportErrCtxt -> ErrMsg -> Ct -> TcM () maybeAddDeferredHoleBinding ctxt err ct - | isExprHoleCt ct - , case cec_expr_holes ctxt of - HoleDefer -> True - HoleWarn -> True - HoleError -> False - = addDeferredBinding ctxt err ct -- Only add bindings for holes in expressions - | otherwise -- not for holes in partial type signatures - = return () - -maybeAddDeferredBinding :: ReportErrCtxt -> ErrMsg -> Ct -> TcM () -maybeAddDeferredBinding ctxt err ct = - case cec_defer_type_errors ctxt of - TypeDefer -> deferred - TypeWarn -> deferred - TypeError -> return () - where - deferred = addDeferredBinding ctxt err ct + | isExprHoleCt ct + = addDeferredBinding ctxt err ct -- Only add bindings for holes in expressions + | otherwise -- not for holes in partial type signatures + = return () tryReporters :: ReportErrCtxt -> [ReporterSpec] -> [Ct] -> TcM (ReportErrCtxt, [Ct]) -- Use the first reporter in the list whose predicate says True @@ -688,9 +688,10 @@ tryReporters ctxt reporters cts tryReporter :: ReportErrCtxt -> ReporterSpec -> [Ct] -> TcM (ReportErrCtxt, [Ct]) tryReporter ctxt (str, keep_me, suppress_after, reporter) cts | null yeses = return (ctxt, cts) - | otherwise = do { traceTc "tryReporter:" (text str <+> ppr yeses) + | otherwise = do { traceTc "tryReporter{ " (text str <+> ppr yeses) ; reporter ctxt yeses ; let ctxt' = ctxt { cec_suppress = suppress_after || cec_suppress ctxt } + ; traceTc "tryReporter end }" (text str <+> ppr (cec_suppress ctxt) <+> ppr suppress_after) ; return (ctxt', nos) } where (yeses, nos) = partition (\ct -> keep_me ct (classifyPredType (ctPred ct))) cts diff --git a/testsuite/tests/module/T7765.hs b/testsuite/tests/partial-sigs/should_compile/T12156.hs similarity index 51% copy from testsuite/tests/module/T7765.hs copy to testsuite/tests/partial-sigs/should_compile/T12156.hs index 6ca9a1f..b8d639f 100644 --- a/testsuite/tests/module/T7765.hs +++ b/testsuite/tests/partial-sigs/should_compile/T12156.hs @@ -1 +1,4 @@ module Main where + +main = print v + diff --git a/testsuite/tests/partial-sigs/should_compile/T12156.stderr b/testsuite/tests/partial-sigs/should_compile/T12156.stderr new file mode 100644 index 0000000..6508d8a --- /dev/null +++ b/testsuite/tests/partial-sigs/should_compile/T12156.stderr @@ -0,0 +1,3 @@ + +T12156.hs:3:14: warning: [-Wtyped-holes (in -Wdefault)] + Variable not in scope: v diff --git a/testsuite/tests/partial-sigs/should_compile/all.T b/testsuite/tests/partial-sigs/should_compile/all.T index 2d600a6..bc3531a 100644 --- a/testsuite/tests/partial-sigs/should_compile/all.T +++ b/testsuite/tests/partial-sigs/should_compile/all.T @@ -62,3 +62,4 @@ test('T10463', normal, compile, ['']) test('ExprSigLocal', normal, compile, ['']) test('T11016', normal, compile, ['']) test('T11192', normal, compile, ['']) +test('T12156', normal, compile, ['-fdefer-typed-holes']) From git at git.haskell.org Mon Jul 25 18:36:50 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 25 Jul 2016 18:36:50 +0000 (UTC) Subject: [commit: ghc] ghc-8.0: Fix renamer panic (8736625) Message-ID: <20160725183650.C01DB3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.0 Link : http://ghc.haskell.org/trac/ghc/changeset/8736625f143d55616e76ff660d476ce4a9cdb2d9/ghc >--------------------------------------------------------------- commit 8736625f143d55616e76ff660d476ce4a9cdb2d9 Author: Simon Peyton Jones Date: Fri Jun 24 08:59:20 2016 +0100 Fix renamer panic This patch fixes Trac #12216 and #12127. The 'combine' function in 'imp_occ_env' in RnNames.filterImports checked for an empty field-selector list, which was (a) unnecessary and (b) wrong. I've elaborated the comments. This does NOT fix #11959 which is related but not the same (it concerns bundling of pattern synonyms). (cherry picked from commit 393928db9fc35ef8bdeb241c051224a6c4bdf749) >--------------------------------------------------------------- 8736625f143d55616e76ff660d476ce4a9cdb2d9 compiler/rename/RnNames.hs | 22 +++++++++++++++------- testsuite/tests/rename/should_compile/T12127.hs | 3 +++ .../should_compile/{DodgyA.hs => T12127a.hs} | 6 +++--- testsuite/tests/rename/should_compile/all.T | 4 ++++ 4 files changed, 25 insertions(+), 10 deletions(-) diff --git a/compiler/rename/RnNames.hs b/compiler/rename/RnNames.hs index bcb247a..a284d3a 100644 --- a/compiler/rename/RnNames.hs +++ b/compiler/rename/RnNames.hs @@ -742,8 +742,15 @@ The situation is made more complicated by associated types. E.g. instance C Bool where { data T Int = T3 } Then M's export_avails are (recall the AvailTC invariant from Avails.hs) C(C,T), T(T,T1,T2,T3) -Notice that T appears *twice*, once as a child and once as a parent. -From this we construct the imp_occ_env +Notice that T appears *twice*, once as a child and once as a parent. From +this list we construt a raw list including + T -> (T, T( T1, T2, T3 ), Nothing) + T -> (C, C( C, T ), Nothing) +and we combine these (in function 'combine' in 'imp_occ_env' in +'filterImports') to get + T -> (T, T(T,T1,T2,T3), Just C) + +So the overall imp_occ_env is C -> (C, C(C,T), Nothing) T -> (T, T(T,T1,T2,T3), Just C) T1 -> (T1, T(T1,T2,T3), Nothing) -- similarly T2,T3 @@ -796,12 +803,13 @@ filterImports iface decl_spec (Just (want_hiding, L l import_items)) imp_occ_env = mkOccEnv_C combine [ (nameOccName n, (n, a, Nothing)) | a <- all_avails, n <- availNames a] where - -- See example in Note [Dealing with imports] - -- 'combine' is only called for associated types which appear twice - -- in the all_avails. In the example, we combine + -- See Note [Dealing with imports] + -- 'combine' is only called for associated data types which appear + -- twice in the all_avails. In the example, we combine -- T(T,T1,T2,T3) and C(C,T) to give (T, T(T,T1,T2,T3), Just C) - combine (name1, a1@(AvailTC p1 _ []), mp1) - (name2, a2@(AvailTC p2 _ []), mp2) + -- NB: the AvailTC can have fields as well as data constructors (Trac #12127) + combine (name1, a1@(AvailTC p1 _ _), mp1) + (name2, a2@(AvailTC p2 _ _), mp2) = ASSERT( name1 == name2 && isNothing mp1 && isNothing mp2 ) if p1 == name1 then (name1, a1, Just p2) else (name1, a2, Just p1) diff --git a/testsuite/tests/rename/should_compile/T12127.hs b/testsuite/tests/rename/should_compile/T12127.hs new file mode 100644 index 0000000..749e406 --- /dev/null +++ b/testsuite/tests/rename/should_compile/T12127.hs @@ -0,0 +1,3 @@ +module T12127 where + +import T12127a( T(..), C(..) ) diff --git a/testsuite/tests/rename/should_compile/DodgyA.hs b/testsuite/tests/rename/should_compile/T12127a.hs similarity index 50% copy from testsuite/tests/rename/should_compile/DodgyA.hs copy to testsuite/tests/rename/should_compile/T12127a.hs index 39cb3ec..53c1b7e 100644 --- a/testsuite/tests/rename/should_compile/DodgyA.hs +++ b/testsuite/tests/rename/should_compile/T12127a.hs @@ -1,9 +1,9 @@ {-# LANGUAGE TypeFamilies #-} -module DodgyA(C(..), X(..)) where +module T12127a where class C a where - data X a + data T a instance C Int where - data X Int = X1 Bool + data T Int = MkT { x, y :: Int } diff --git a/testsuite/tests/rename/should_compile/all.T b/testsuite/tests/rename/should_compile/all.T index cfad164..79106c0 100644 --- a/testsuite/tests/rename/should_compile/all.T +++ b/testsuite/tests/rename/should_compile/all.T @@ -237,3 +237,7 @@ test('T11662', [extra_clean(['T11662_A.hi', 'T11662_A.o'])], multimod_compile, ['T11662', '-v0']) +test('T12127', + [extra_clean(['T12127a.hi', 'T12127a.o'])], + multimod_compile, + ['T12127', '-v0']) From git at git.haskell.org Mon Jul 25 18:36:54 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 25 Jul 2016 18:36:54 +0000 (UTC) Subject: [commit: ghc] ghc-8.0: Avoid find_tycon panic if datacon is not in scope (694e0f3) Message-ID: <20160725183654.0807B3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.0 Link : http://ghc.haskell.org/trac/ghc/changeset/694e0f3a0803072687fab6e3a5792627f5761bd2/ghc >--------------------------------------------------------------- commit 694e0f3a0803072687fab6e3a5792627f5761bd2 Author: Adam Gundry Date: Sat Jun 18 12:27:47 2016 +0200 Avoid find_tycon panic if datacon is not in scope When using TH to splice expressions involving record field construction, the parent datacon may not be in scope. We shouldn't panic about this, because we will be renaming Exact RdrNames which don't require any disambiguation. Test Plan: new test th/T12130 Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2321 GHC Trac Issues: #12130 (cherry picked from commit 4d71cc89b4e9648f3fbb29c8fcd25d725616e265) >--------------------------------------------------------------- 694e0f3a0803072687fab6e3a5792627f5761bd2 compiler/rename/RnPat.hs | 7 ++++--- testsuite/tests/th/T12130.hs | 8 ++++++++ testsuite/tests/th/T12130a.hs | 17 +++++++++++++++++ testsuite/tests/th/all.T | 2 ++ 4 files changed, 31 insertions(+), 3 deletions(-) diff --git a/compiler/rename/RnPat.hs b/compiler/rename/RnPat.hs index 51ddea9..f1b61e3 100644 --- a/compiler/rename/RnPat.hs +++ b/compiler/rename/RnPat.hs @@ -636,7 +636,7 @@ rnHsRecFields ctxt mk_arg (HsRecFields { rec_flds = flds, rec_dotdot = dotdot }) find_tycon :: GlobalRdrEnv -> Name {- DataCon -} -> Maybe Name {- TyCon -} -- Return the parent *type constructor* of the data constructor -- (that is, the parent of the data constructor), - -- or 'Nothing' if it is a pattern synonym. + -- or 'Nothing' if it is a pattern synonym or not in scope. -- That's the parent to use for looking up record fields. find_tycon env con | Just (AConLike (RealDataCon dc)) <- wiredInNameTyThing_maybe con @@ -648,8 +648,9 @@ rnHsRecFields ctxt mk_arg (HsRecFields { rec_flds = flds, rec_dotdot = dotdot }) ParentIs p -> Just p _ -> Nothing - | otherwise - = pprPanic "find_tycon" (ppr con $$ ppr (lookupGRE_Name env con)) + | otherwise = Nothing + -- This can happen if the datacon is not in scope + -- and we are in a TH splice (Trac #12130) dup_flds :: [[RdrName]] -- Each list represents a RdrName that occurred more than once diff --git a/testsuite/tests/th/T12130.hs b/testsuite/tests/th/T12130.hs new file mode 100644 index 0000000..7ab7492 --- /dev/null +++ b/testsuite/tests/th/T12130.hs @@ -0,0 +1,8 @@ +{-# Language TemplateHaskell #-} +{-# Language DisambiguateRecordFields #-} + +module T12130 where + +import T12130a hiding (Block) + +b = $(block) diff --git a/testsuite/tests/th/T12130a.hs b/testsuite/tests/th/T12130a.hs new file mode 100644 index 0000000..f393967 --- /dev/null +++ b/testsuite/tests/th/T12130a.hs @@ -0,0 +1,17 @@ +{-# LANGUAGE TemplateHaskell #-} + +module T12130a where + +import Language.Haskell.TH + +data Block = Block + { blockSelector :: () + } + +block :: Q Exp +block = + [| Block { + -- Using record syntax is neccesary to trigger the bug. + blockSelector = () + } + |] diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index 864fa74..2e7a6ba 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -408,3 +408,5 @@ test('T11680', normal, compile_fail, ['-v0']) test('T11809', normal, compile, ['-v0']) test('T11797', normal, compile, ['-v0 -dsuppress-uniques']) test('T11941', normal, compile_fail, ['-v0']) +test('T12130', extra_clean(['T12130a.hi','T12130a.o']), + multimod_compile, ['T12130', '-v0 ' + config.ghc_th_way_flags]) From git at git.haskell.org Mon Jul 25 18:36:56 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 25 Jul 2016 18:36:56 +0000 (UTC) Subject: [commit: ghc] ghc-8.0: Fix Ticky histogram on Windows (b2796aa) Message-ID: <20160725183656.A50FF3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.0 Link : http://ghc.haskell.org/trac/ghc/changeset/b2796aaee78f1e7d9dcd5285e48c955b390f514e/ghc >--------------------------------------------------------------- commit b2796aaee78f1e7d9dcd5285e48c955b390f514e Author: Tamar Christina Date: Thu Jun 9 17:49:20 2016 +0200 Fix Ticky histogram on Windows The histogram types are defined in `Ticky.c` as `StgInt` values. ``` EXTERN StgInt RET_NEW_hst[TICKY_BIN_COUNT] INIT({0}); EXTERN StgInt RET_OLD_hst[TICKY_BIN_COUNT] INIT({0}); EXTERN StgInt RET_UNBOXED_TUP_hst[TICKY_BIN_COUNT] INIT({0}); ``` which means they'll be `32-bits` on `x86` and `64-bits` on `x86_64`. However the `bumpHistogram` in `StgCmmTicky` is incrementing them as if they're a `cLong`. A long on Windows `x86_64` is `32-bit`. As such when then value for the `_hst_1` is being set what it's actually doing is setting the value of the high bits of the first entry. This ends up giving us `0b‭100000000000000000000000000000000‬` or `4294967296` as is displayed in the ticket on #8308. Since `StgInt` is defined using the `WORD` size. Just use that directly in `bumpHistogram`. Also since `cLong` is no longer used after this commit it will also be dropped. Test Plan: make TEST=T8308 Reviewers: mlen, jstolarek, bgamari, thomie, goldfire, simonmar, austin Reviewed By: bgamari, thomie Subscribers: #ghc_windows_task_force Differential Revision: https://phabricator.haskell.org/D2318 GHC Trac Issues: #8308 (cherry picked from commit b020db2a841c397a02ec352f8b6dc110b38b927b) >--------------------------------------------------------------- b2796aaee78f1e7d9dcd5285e48c955b390f514e compiler/cmm/CmmType.hs | 16 +++++----------- compiler/codeGen/StgCmmTicky.hs | 10 +++++----- 2 files changed, 10 insertions(+), 16 deletions(-) diff --git a/compiler/cmm/CmmType.hs b/compiler/cmm/CmmType.hs index ae46330..4abbeaf 100644 --- a/compiler/cmm/CmmType.hs +++ b/compiler/cmm/CmmType.hs @@ -3,14 +3,14 @@ module CmmType ( CmmType -- Abstract , b8, b16, b32, b64, b128, b256, b512, f32, f64, bWord, bHalfWord, gcWord - , cInt, cLong + , cInt , cmmBits, cmmFloat , typeWidth, cmmEqType, cmmEqType_ignoring_ptrhood , isFloatType, isGcPtrType, isWord32, isWord64, isFloat64, isFloat32 , Width(..) , widthInBits, widthInBytes, widthInLog, widthFromBytes - , wordWidth, halfWordWidth, cIntWidth, cLongWidth + , wordWidth, halfWordWidth, cIntWidth , halfWordMask , narrowU, narrowS , rEP_CostCentreStack_mem_alloc @@ -129,10 +129,8 @@ bHalfWord dflags = cmmBits (halfWordWidth dflags) gcWord :: DynFlags -> CmmType gcWord dflags = CmmType GcPtrCat (wordWidth dflags) -cInt, cLong :: DynFlags -> CmmType -cInt dflags = cmmBits (cIntWidth dflags) -cLong dflags = cmmBits (cLongWidth dflags) - +cInt :: DynFlags -> CmmType +cInt dflags = cmmBits (cIntWidth dflags) ------------ Predicates ---------------- isFloatType, isGcPtrType :: CmmType -> Bool @@ -207,15 +205,11 @@ halfWordMask dflags | otherwise = panic "MachOp.halfWordMask: Unknown word size" -- cIntRep is the Width for a C-language 'int' -cIntWidth, cLongWidth :: DynFlags -> Width +cIntWidth :: DynFlags -> Width cIntWidth dflags = case cINT_SIZE dflags of 4 -> W32 8 -> W64 s -> panic ("cIntWidth: Unknown cINT_SIZE: " ++ show s) -cLongWidth dflags = case cLONG_SIZE dflags of - 4 -> W32 - 8 -> W64 - s -> panic ("cIntWidth: Unknown cLONG_SIZE: " ++ show s) widthInBits :: Width -> Int widthInBits W8 = 8 diff --git a/compiler/codeGen/StgCmmTicky.hs b/compiler/codeGen/StgCmmTicky.hs index cdbcd25..4118383 100644 --- a/compiler/codeGen/StgCmmTicky.hs +++ b/compiler/codeGen/StgCmmTicky.hs @@ -466,12 +466,12 @@ tickyAllocHeap genuine hp (CmmLit (cmmLabelOffB ticky_ctr (oFFSET_StgEntCounter_allocs dflags))) bytes, -- Bump the global allocation total ALLOC_HEAP_tot - addToMemLbl (cLong dflags) + addToMemLbl (bWord dflags) (mkCmmDataLabel rtsUnitId (fsLit "ALLOC_HEAP_tot")) bytes, -- Bump the global allocation counter ALLOC_HEAP_ctr if not genuine then mkNop - else addToMemLbl (cLong dflags) + else addToMemLbl (bWord dflags) (mkCmmDataLabel rtsUnitId (fsLit "ALLOC_HEAP_ctr")) 1 ]} @@ -580,11 +580,11 @@ bumpHistogram :: FastString -> Int -> FCode () bumpHistogram lbl n = do dflags <- getDynFlags let offset = n `min` (tICKY_BIN_COUNT dflags - 1) - emit (addToMem (cLong dflags) + emit (addToMem (bWord dflags) (cmmIndexExpr dflags - (cLongWidth dflags) + (wordWidth dflags) (CmmLit (CmmLabel (mkCmmDataLabel rtsUnitId lbl))) - (CmmLit (CmmInt (fromIntegral offset) (cLongWidth dflags)))) + (CmmLit (CmmInt (fromIntegral offset) (wordWidth dflags)))) 1) ------------------------------------------------------------------ From git at git.haskell.org Mon Jul 25 18:36:59 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 25 Jul 2016 18:36:59 +0000 (UTC) Subject: [commit: ghc] ghc-8.0: Fix trac #10647: Notice about lack of SIMD support (c650949) Message-ID: <20160725183659.4BA993A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.0 Link : http://ghc.haskell.org/trac/ghc/changeset/c6509496e5bdeac688118613639c42f17c8652bd/ghc >--------------------------------------------------------------- commit c6509496e5bdeac688118613639c42f17c8652bd Author: Seraphime Kirkovski Date: Sat Jun 18 12:28:19 2016 +0200 Fix trac #10647: Notice about lack of SIMD support Fixes #10647. Changes the error message when a SIMD size variable is required in the native code generation backend. Test Plan: Try compiling the test case given in the ticket : {-# LANGUAGE MagicHash #-} module Foo where import GHC.Prim data V = V Int8X16# GHC should give a clearer error message Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2325 GHC Trac Issues: #10647 (cherry picked from commit f12fb8ab5d5ad7a26c84f98e446bc70064dcdcec) >--------------------------------------------------------------- c6509496e5bdeac688118613639c42f17c8652bd compiler/nativeGen/Format.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/compiler/nativeGen/Format.hs b/compiler/nativeGen/Format.hs index 92a8ef8..00811f1 100644 --- a/compiler/nativeGen/Format.hs +++ b/compiler/nativeGen/Format.hs @@ -57,7 +57,9 @@ intFormat width W16 -> II16 W32 -> II32 W64 -> II64 - other -> pprPanic "Format.intFormat" (ppr other) + other -> sorry $ "The native code generator cannot " ++ + "produce code for Format.intFormat " ++ show other + ++ "\n\tConsider using the llvm backend with -fllvm" -- | Get the float format of this width. From git at git.haskell.org Mon Jul 25 18:37:02 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 25 Jul 2016 18:37:02 +0000 (UTC) Subject: [commit: ghc] ghc-8.0: Fix histograms for ticky code (f0eb4f7) Message-ID: <20160725183702.D79383A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.0 Link : http://ghc.haskell.org/trac/ghc/changeset/f0eb4f7a1a63da057016fb93f009c7b57f481096/ghc >--------------------------------------------------------------- commit f0eb4f7a1a63da057016fb93f009c7b57f481096 Author: Mateusz Lenik Date: Tue May 17 08:33:54 2016 +0200 Fix histograms for ticky code This patch fixes Cmm generation required to produce histograms when compiling with -ticky flag, strips dead code from rts/Ticky.c and reworks it to use a shared constant in both C and Haskell code. Fixes #8308. Test Plan: T8308 Reviewers: jstolarek, simonpj, austin Reviewed By: simonpj Subscribers: mpickering, simonpj, bgamari, mlen, thomie, jstolarek Differential Revision: https://phabricator.haskell.org/D931 GHC Trac Issues: #8308 (cherry picked from commit f0f0ac859257a0b528815adb61d3f024c8bafa16) >--------------------------------------------------------------- f0eb4f7a1a63da057016fb93f009c7b57f481096 compiler/codeGen/StgCmmExpr.hs | 1 + compiler/codeGen/StgCmmTicky.hs | 38 +-- includes/stg/Ticky.h | 11 +- rts/RtsSymbols.c | 5 +- rts/Ticky.c | 298 ++------------------- testsuite/tests/rts/T8308/Makefile | 10 + testsuite/tests/rts/T8308/T8308.hs | 7 + .../T5149.stdout => rts/T8308/T8308.stdout} | 0 testsuite/tests/rts/T8308/all.T | 2 + utils/deriveConstants/Main.hs | 3 + 10 files changed, 74 insertions(+), 301 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc f0eb4f7a1a63da057016fb93f009c7b57f481096 From git at git.haskell.org Mon Jul 25 18:37:05 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 25 Jul 2016 18:37:05 +0000 (UTC) Subject: [commit: ghc] ghc-8.0: ApplicativeDo: allow "return $ e" (10b69f6) Message-ID: <20160725183705.851183A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.0 Link : http://ghc.haskell.org/trac/ghc/changeset/10b69f6871bb243a1fd0259edfd74538839044f9/ghc >--------------------------------------------------------------- commit 10b69f6871bb243a1fd0259edfd74538839044f9 Author: Simon Marlow Date: Sat Jun 18 14:51:04 2016 +0100 ApplicativeDo: allow "return $ e" Summary: There's a precedent for special-casing $, as we already have special typing rules for it. Test Plan: validate; new test cases Reviewers: ezyang, austin, niteria, bgamari, simonpj, erikd Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2345 GHC Trac Issues: #11835 (cherry picked from commit 0ba34b6bac988228948c65ae11d9e08afe82c878) >--------------------------------------------------------------- 10b69f6871bb243a1fd0259edfd74538839044f9 compiler/rename/RnExpr.hs | 22 +++++++++++++--------- docs/users_guide/glasgow_exts.rst | 4 ++++ testsuite/tests/ado/ado004.hs | 12 ++++++++++++ testsuite/tests/ado/ado004.stderr | 6 ++++++ 4 files changed, 35 insertions(+), 9 deletions(-) diff --git a/compiler/rename/RnExpr.hs b/compiler/rename/RnExpr.hs index 1ca677a..5d97332 100644 --- a/compiler/rename/RnExpr.hs +++ b/compiler/rename/RnExpr.hs @@ -1779,19 +1779,23 @@ needJoin [L loc (LastStmt e _ t)] | Just arg <- isReturnApp e = (False, [L loc (LastStmt arg True t)]) needJoin stmts = (True, stmts) --- | @Just e@, if the expression is @return e@, otherwise @Nothing@ +-- | @Just e@, if the expression is @return e@ or @return $ e@, +-- otherwise @Nothing@ isReturnApp :: LHsExpr Name -> Maybe (LHsExpr Name) isReturnApp (L _ (HsPar expr)) = isReturnApp expr -isReturnApp (L _ (HsApp f arg)) - | is_return f = Just arg - | otherwise = Nothing +isReturnApp (L _ e) = case e of + OpApp l op _ r | is_return l, is_dollar op -> Just r + HsApp f arg | is_return f -> Just arg + _otherwise -> Nothing where - is_return (L _ (HsPar e)) = is_return e - is_return (L _ (HsAppType e _)) = is_return e - is_return (L _ (HsVar (L _ r))) = r == returnMName || r == pureAName + is_var f (L _ (HsPar e)) = is_var f e + is_var f (L _ (HsAppType e _)) = is_var f e + is_var f (L _ (HsVar (L _ r))) = f r -- TODO: I don't know how to get this right for rebindable syntax - is_return _ = False -isReturnApp _ = Nothing + is_var _ _ = False + + is_return = is_var (\n -> n == returnMName || n == pureAName) + is_dollar = is_var (`hasKey` dollarIdKey) {- ************************************************************************ diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst index cbecda7..fd4f947 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -939,6 +939,10 @@ then the expression will only require ``Applicative``. Otherwise, the expression will require ``Monad``. The block may return a pure expression ``E`` depending upon the results ``p1...pn`` with either ``return`` or ``pure``. +Note: the final statement really must be of the form ``return E`` or +``pure E``, otherwise you get a ``Monad`` constraint. Using ``$`` as +in ``return $ E`` or ``pure $ E`` is also acceptable. + When the statements of a ``do`` expression have dependencies between them, and ``ApplicativeDo`` cannot infer an ``Applicative`` type, it uses a heuristic algorithm to try to use ``<*>`` as much as possible. diff --git a/testsuite/tests/ado/ado004.hs b/testsuite/tests/ado/ado004.hs index 6ddc839..fa3c723 100644 --- a/testsuite/tests/ado/ado004.hs +++ b/testsuite/tests/ado/ado004.hs @@ -9,6 +9,13 @@ test1 f = do y <- f 4 return (x + y) +-- The same using $ +test1a :: Applicative f => (Int -> f Int) -> f Int +test1a f = do + x <- f 3 + y <- f 4 + return $ x + y + -- Test we can also infer the Applicative version of the type test2 f = do x <- f 3 @@ -20,6 +27,11 @@ test2a f = do x <- f 3 return (x + 1) +-- The same using $ +test2c f = do + x <- f 3 + return $ x + 1 + -- Test for just one statement test2b f = do return (f 3) diff --git a/testsuite/tests/ado/ado004.stderr b/testsuite/tests/ado/ado004.stderr index 8f5a816..ec2ebbc 100644 --- a/testsuite/tests/ado/ado004.stderr +++ b/testsuite/tests/ado/ado004.stderr @@ -1,6 +1,8 @@ TYPE SIGNATURES test1 :: forall (f :: * -> *). Applicative f => (Int -> f Int) -> f Int + test1a :: + forall (f :: * -> *). Applicative f => (Int -> f Int) -> f Int test2 :: forall t b (f :: * -> *). (Num b, Num t, Applicative f) => @@ -11,6 +13,10 @@ TYPE SIGNATURES (t -> f b) -> f b test2b :: forall (m :: * -> *) a t. (Num t, Monad m) => (t -> a) -> m a + test2c :: + forall t b (f :: * -> *). + (Num b, Num t, Functor f) => + (t -> f b) -> f b test3 :: forall a t (m :: * -> *) t1. (Num t1, Monad m) => From git at git.haskell.org Mon Jul 25 18:37:08 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 25 Jul 2016 18:37:08 +0000 (UTC) Subject: [commit: ghc] ghc-8.0: Expand and clarify the docs for ApplicativeDo (#11835) (ba41416) Message-ID: <20160725183708.2EF373A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.0 Link : http://ghc.haskell.org/trac/ghc/changeset/ba414165bbf06e3b3c4f6e65301749d197beb69a/ghc >--------------------------------------------------------------- commit ba414165bbf06e3b3c4f6e65301749d197beb69a Author: Simon Marlow Date: Mon Jun 20 15:30:34 2016 +0100 Expand and clarify the docs for ApplicativeDo (#11835) (cherry picked from commit ee3bde7999877f108375651869f1dc5b362da9fe) >--------------------------------------------------------------- ba414165bbf06e3b3c4f6e65301749d197beb69a docs/users_guide/glasgow_exts.rst | 18 +++++++++++++++--- 1 file changed, 15 insertions(+), 3 deletions(-) diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst index fd4f947..555bfb6 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -939,9 +939,21 @@ then the expression will only require ``Applicative``. Otherwise, the expression will require ``Monad``. The block may return a pure expression ``E`` depending upon the results ``p1...pn`` with either ``return`` or ``pure``. -Note: the final statement really must be of the form ``return E`` or -``pure E``, otherwise you get a ``Monad`` constraint. Using ``$`` as -in ``return $ E`` or ``pure $ E`` is also acceptable. +Note: the final statement must match one of these patterns exactly: + +- ``return E`` +- ``return $ E`` +- ``pure E`` +- ``pure $ E`` + +otherwise GHC cannot recognise it as a ``return`` statement, and the +transformation to use ``<$>`` that we saw above does not apply. In +particular, slight variations such as ``return . Just $ x`` or ``let x += e in return x`` would not be recognised. + +If the final statement is not of one of these forms, GHC falls back to +standard ``do`` desugaring, and the expression will require a +``Monad`` constraint. When the statements of a ``do`` expression have dependencies between them, and ``ApplicativeDo`` cannot infer an ``Applicative`` type, it From git at git.haskell.org Mon Jul 25 18:37:11 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 25 Jul 2016 18:37:11 +0000 (UTC) Subject: [commit: ghc] ghc-8.0: Fix deriving Ord when RebindableSyntax is enabled (a064fa3) Message-ID: <20160725183711.3EE433A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.0 Link : http://ghc.haskell.org/trac/ghc/changeset/a064fa362d7e9ab33403b56c8f3e1aac0df07aca/ghc >--------------------------------------------------------------- commit a064fa362d7e9ab33403b56c8f3e1aac0df07aca Author: Andrew Farmer Date: Sat May 21 18:38:47 2016 +0200 Fix deriving Ord when RebindableSyntax is enabled Deriving clauses (Ord especially) generated if-expressions with nlHsIf which were subject to RebindableSyntax. This changes nlHsIf to generate concrete if-expressions. There was also an error about calling tagToEnum# at a polymorphic type, which is not allowed. Fixing nlHsIf didn't fix this for some reason, so I generated a type ascription around the call to tagToEnum#. Not sure why the typechecker could not figure this out. Test Plan: Added a test, ran validate. Reviewers: simonpj, simonmar, austin, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2247 GHC Trac Issues: #12080 (cherry picked from commit 527ed7246a35fe8bab89c7c582084cd20661018a) >--------------------------------------------------------------- a064fa362d7e9ab33403b56c8f3e1aac0df07aca compiler/hsSyn/HsUtils.hs | 7 ++++++- compiler/typecheck/TcGenDeriv.hs | 10 ++++++---- testsuite/tests/rebindable/T12080.hs | 16 ++++++++++++++++ testsuite/tests/rebindable/all.T | 1 + 4 files changed, 29 insertions(+), 5 deletions(-) diff --git a/compiler/hsSyn/HsUtils.hs b/compiler/hsSyn/HsUtils.hs index 5e531d6..232ca1f 100644 --- a/compiler/hsSyn/HsUtils.hs +++ b/compiler/hsSyn/HsUtils.hs @@ -454,7 +454,12 @@ nlList :: [LHsExpr RdrName] -> LHsExpr RdrName nlHsLam match = noLoc (HsLam (mkMatchGroup Generated [match])) nlHsPar e = noLoc (HsPar e) -nlHsIf cond true false = noLoc (mkHsIf cond true false) + +-- Note [Rebindable nlHsIf] +-- nlHsIf should generate if-expressions which are NOT subject to +-- RebindableSyntax, so the first field of HsIf is Nothing. (#12080) +nlHsIf cond true false = noLoc (HsIf Nothing cond true false) + nlHsCase expr matches = noLoc (HsCase expr (mkMatchGroup Generated matches)) nlList exprs = noLoc (ExplicitList placeHolderType Nothing exprs) diff --git a/compiler/typecheck/TcGenDeriv.hs b/compiler/typecheck/TcGenDeriv.hs index 133b398..e5b7ba2 100644 --- a/compiler/typecheck/TcGenDeriv.hs +++ b/compiler/typecheck/TcGenDeriv.hs @@ -529,11 +529,13 @@ unliftedCompare :: RdrName -> RdrName -> LHsExpr RdrName -- Return (if a < b then lt else if a == b then eq else gt) unliftedCompare lt_op eq_op a_expr b_expr lt eq gt - = nlHsIf (genPrimOpApp a_expr lt_op b_expr) lt $ + = nlHsIf (ascribeBool $ genPrimOpApp a_expr lt_op b_expr) lt $ -- Test (<) first, not (==), because the latter -- is true less often, so putting it first would -- mean more tests (dynamically) - nlHsIf (genPrimOpApp a_expr eq_op b_expr) eq gt + nlHsIf (ascribeBool $ genPrimOpApp a_expr eq_op b_expr) eq gt + where + ascribeBool e = nlExprWithTySig e (toLHsSigWcType boolTy) nlConWildPat :: DataCon -> LPat RdrName -- The pattern (K {}) @@ -2182,8 +2184,8 @@ gen_Newtype_binds loc cls inst_tvs cls_tys rhs_ty -- variables refer to the ones bound in the user_ty (_, _, tau_ty') = tcSplitSigmaTy tau_ty - nlExprWithTySig :: LHsExpr RdrName -> LHsSigWcType RdrName -> LHsExpr RdrName - nlExprWithTySig e s = noLoc (ExprWithTySig e s) +nlExprWithTySig :: LHsExpr RdrName -> LHsSigWcType RdrName -> LHsExpr RdrName +nlExprWithTySig e s = noLoc (ExprWithTySig e s) {- ************************************************************************ diff --git a/testsuite/tests/rebindable/T12080.hs b/testsuite/tests/rebindable/T12080.hs new file mode 100644 index 0000000..5413ed0 --- /dev/null +++ b/testsuite/tests/rebindable/T12080.hs @@ -0,0 +1,16 @@ +{-# LANGUAGE FlexibleInstances #-} +{-# LANGUAGE MultiParamTypeClasses #-} +{-# LANGUAGE RebindableSyntax #-} + +import Prelude + +class IfThenElse a b where + ifThenElse :: a -> b -> b -> b + +instance IfThenElse Bool b where + ifThenElse c x y = if c then x else y + +data Foo = Foo | Bar | Baz deriving (Eq, Ord) + +main :: IO () +main = print $ Foo < Bar diff --git a/testsuite/tests/rebindable/all.T b/testsuite/tests/rebindable/all.T index 3ca873e..f1737e9 100644 --- a/testsuite/tests/rebindable/all.T +++ b/testsuite/tests/rebindable/all.T @@ -32,3 +32,4 @@ test('T4851', normal, compile, ['']) test('T5908', normal, compile, ['']) test('T10112', normal, compile, ['']) test('T11216', [expect_broken(11216)], compile, ['']) +test('T12080', normal, compile, ['']) From git at git.haskell.org Mon Jul 25 18:37:14 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 25 Jul 2016 18:37:14 +0000 (UTC) Subject: [commit: ghc] ghc-8.0: Add tests for #11465 and the kind invariant (b0fd23b) Message-ID: <20160725183714.8EB953A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.0 Link : http://ghc.haskell.org/trac/ghc/changeset/b0fd23b58e4e194a7f65d0f42ca0e0e18c1c7e17/ghc >--------------------------------------------------------------- commit b0fd23b58e4e194a7f65d0f42ca0e0e18c1c7e17 Author: Ben Gamari Date: Fri Jan 22 13:01:55 2016 +0100 Add tests for #11465 and the kind invariant (cherry picked from commit 2df422161bccf7c0fad97e468085ebab1a17e19e) >--------------------------------------------------------------- b0fd23b58e4e194a7f65d0f42ca0e0e18c1c7e17 testsuite/tests/indexed-types/should_run/T11465a.hs | 19 +++++++++++++++++++ .../tests/indexed-types/should_run/T11465a.stdout | 1 + testsuite/tests/indexed-types/should_run/all.T | 1 + .../tests/typecheck/should_run/KindInvariant.script | 12 ++++++++++++ .../tests/typecheck/should_run/KindInvariant.stderr | 6 ++++++ .../tests/typecheck/should_run/KindInvariant.stdout | 2 ++ 6 files changed, 41 insertions(+) diff --git a/testsuite/tests/indexed-types/should_run/T11465a.hs b/testsuite/tests/indexed-types/should_run/T11465a.hs new file mode 100644 index 0000000..d3626cf --- /dev/null +++ b/testsuite/tests/indexed-types/should_run/T11465a.hs @@ -0,0 +1,19 @@ +{-# LANGUAGE PolyKinds #-} +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE MagicHash #-} +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE TypeInType #-} + +import GHC.Exts +import GHC.Types + +class BoxIt (a :: TYPE 'WordRep) where + type Boxed a :: * + boxed :: a -> Boxed a + +instance BoxIt Char# where + type Boxed Char# = Char + boxed x = C# x + +main :: IO () +main = print $ boxed 'c'# diff --git a/testsuite/tests/indexed-types/should_run/T11465a.stdout b/testsuite/tests/indexed-types/should_run/T11465a.stdout new file mode 100644 index 0000000..4076583 --- /dev/null +++ b/testsuite/tests/indexed-types/should_run/T11465a.stdout @@ -0,0 +1 @@ +'c' diff --git a/testsuite/tests/indexed-types/should_run/all.T b/testsuite/tests/indexed-types/should_run/all.T index f5c8c5c..8d72c46 100644 --- a/testsuite/tests/indexed-types/should_run/all.T +++ b/testsuite/tests/indexed-types/should_run/all.T @@ -6,3 +6,4 @@ test('T4235', normal, compile_and_run, ['']) test('GMapAssoc', normal, compile_and_run, ['-package containers']) test('GMapTop', normal, compile_and_run, ['-package containers']) test('T5719', normal, compile_and_run, ['']) +test('T11465a', normal, compile_and_run, ['']) \ No newline at end of file diff --git a/testsuite/tests/typecheck/should_run/KindInvariant.script b/testsuite/tests/typecheck/should_run/KindInvariant.script new file mode 100644 index 0000000..a993d51 --- /dev/null +++ b/testsuite/tests/typecheck/should_run/KindInvariant.script @@ -0,0 +1,12 @@ +:set -XTypeInType -XDataKinds -XKindSignatures -XMagicHash -XPolyKinds +:m + Data.Kind GHC.Exts + +data T (a :: k -> k') +:kind T State# + +data T (a :: * -> k') +:kind T State# + +-- this should fail +data T (a :: * -> *) +:kind T State# diff --git a/testsuite/tests/typecheck/should_run/KindInvariant.stderr b/testsuite/tests/typecheck/should_run/KindInvariant.stderr new file mode 100644 index 0000000..3fe8131 --- /dev/null +++ b/testsuite/tests/typecheck/should_run/KindInvariant.stderr @@ -0,0 +1,6 @@ + +:1:3: error: + • Expected kind ‘* -> *’, + but ‘State#’ has kind ‘* -> TYPE 'VoidRep’ + • In the first argument of ‘T’, namely ‘State#’ + In the type ‘T State#’ diff --git a/testsuite/tests/typecheck/should_run/KindInvariant.stdout b/testsuite/tests/typecheck/should_run/KindInvariant.stdout new file mode 100644 index 0000000..d7cbaed --- /dev/null +++ b/testsuite/tests/typecheck/should_run/KindInvariant.stdout @@ -0,0 +1,2 @@ +T State# :: * +T State# :: * From git at git.haskell.org Mon Jul 25 18:37:17 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 25 Jul 2016 18:37:17 +0000 (UTC) Subject: [commit: ghc] ghc-8.0: Accept more test wibbles (738b199) Message-ID: <20160725183717.39EEC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.0 Link : http://ghc.haskell.org/trac/ghc/changeset/738b199fface08733c825351a5b69c6db9a068da/ghc >--------------------------------------------------------------- commit 738b199fface08733c825351a5b69c6db9a068da Author: Ben Gamari Date: Mon Jul 25 20:08:58 2016 +0200 Accept more test wibbles >--------------------------------------------------------------- 738b199fface08733c825351a5b69c6db9a068da testsuite/tests/dependent/should_fail/T11471.stderr | 1 + 1 file changed, 1 insertion(+) diff --git a/testsuite/tests/dependent/should_fail/T11471.stderr b/testsuite/tests/dependent/should_fail/T11471.stderr index 0578910..80c5fc6 100644 --- a/testsuite/tests/dependent/should_fail/T11471.stderr +++ b/testsuite/tests/dependent/should_fail/T11471.stderr @@ -16,3 +16,4 @@ T11471.hs:15:35: error: • In the second argument of ‘f’, namely ‘3#’ In the expression: f (undefined :: Proxy Int#) 3# In an equation for ‘bad’: bad = f (undefined :: Proxy Int#) 3# + • Relevant bindings include bad :: F Int# (bound at T11471.hs:15:1) From git at git.haskell.org Mon Jul 25 18:37:19 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 25 Jul 2016 18:37:19 +0000 (UTC) Subject: [commit: ghc] ghc-8.0's head updated: Accept more test wibbles (738b199) Message-ID: <20160725183719.CAEDC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'ghc-8.0' now includes: 7bfc8c0 Kill some unnecessary varSetElems a082cd3 Remove some gratitious varSetElemsWellScoped b874bc9 Kill unnecessary varSetElemsWellScoped in deriveTyData 28c4a84 Rename FV related functions 3a6888e Remove mysterious varSetElemsWellScoped in tidyFreeTyCoVars 085f449 Get rid of varSetElemsWellScoped in abstractFloats 9f00629 Refactor computing dependent type vars 7c216d2 Fix two buglets in 17eb241 noticed by Richard cc02156 Make benign non-determinism in pretty-printing more obvious f775c44 Kill varSetElemsWellScoped in quantifyTyVars d0f95cf Kill varSetElems in TcErrors e41984c Kill varSetElems try_tyvar_defaulting cc36fe3 Kill varSetElems in markNominal 8a6f976 Kill varSetElems in injImproveEqns 64e4b88 Kill non-deterministic foldUFM in TrieMap and TcAppMap c8188d8 Make simplifyInstanceContexts deterministic 0234bfa Remove some varSetElems in dsCmdStmt 29c0807 Make absentError not depend on uniques f38fe3f Kill varEnvElts in specImports 233b1ab Kill varSetElems in tcInferPatSynDecl ae94a31 Refactor free tyvars on LHS of rules 1c59d37 Make accept fbccc0b Make inert_model and inert_eqs deterministic sets 2b3de32 Refactor validity checking for type/data instances bcc1cf4 Kill varSetElems in tidyFreeTyCoVars 5ba488f Make Arrow desugaring deterministic 3b745a1 Serialize vParallelTyCons in a stable order 2d3e064 Add nameSetElemsStable and fix the build d563710 Implement deterministic CallInfoSet 77a9f01 Add -foptimal-applicative-do a448c03 Desugar ApplicativeDo and RecDo deterministically 9b6fa58 Make UnitIdMap a deterministic map 65225c7 Use DVarSet in Vectorise.Exp 87f886c Make vectInfoParallelVars a DVarSet 560b7af Use UniqFM for SigOf bab927c Make checkFamInstConsistency less expensive daa058e Make the Ord Module independent of Unique order (2nd try) 6fc97cd Refactor match to not use Unique order 7952f10 Add a new determinism test 7dd591c Make accept a0f1809 Fix GetTime.c on Darwin with clock_gettime cd9c4a5 Don't quantify over Refl in a RULE 151f193 Abort the build when a Core plugin pass is specified in stage1 compiler a8d4759 Fix bytecode gen to deal with rep-polymorphism 66d70fd Allow unlifted types in pattern synonym result type 2a09e6e Trac #11554 fix loopy GADTs 8736625 Fix renamer panic 694e0f3 Avoid find_tycon panic if datacon is not in scope b4bdbe4 Don't omit any evidence bindings f0eb4f7 Fix histograms for ticky code b2796aa Fix Ticky histogram on Windows c650949 Fix trac #10647: Notice about lack of SIMD support 10b69f6 ApplicativeDo: allow "return $ e" ba41416 Expand and clarify the docs for ApplicativeDo (#11835) a064fa3 Fix deriving Ord when RebindableSyntax is enabled b0fd23b Add tests for #11465 and the kind invariant 738b199 Accept more test wibbles From git at git.haskell.org Mon Jul 25 22:36:53 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 25 Jul 2016 22:36:53 +0000 (UTC) Subject: [commit: ghc] master: Some typos in comments (1967d74) Message-ID: <20160725223653.2D2D73A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1967d74417759ba9228100a8fed715d99b9e6d5a/ghc >--------------------------------------------------------------- commit 1967d74417759ba9228100a8fed715d99b9e6d5a Author: Gabor Greif Date: Tue Jul 26 00:34:48 2016 +0200 Some typos in comments >--------------------------------------------------------------- 1967d74417759ba9228100a8fed715d99b9e6d5a compiler/codeGen/StgCmmExpr.hs | 4 ++-- compiler/simplCore/Simplify.hs | 2 +- compiler/stgSyn/StgSyn.hs | 2 +- compiler/typecheck/TcSplice.hs | 2 +- 4 files changed, 5 insertions(+), 5 deletions(-) diff --git a/compiler/codeGen/StgCmmExpr.hs b/compiler/codeGen/StgCmmExpr.hs index 142d30c..1965754 100644 --- a/compiler/codeGen/StgCmmExpr.hs +++ b/compiler/codeGen/StgCmmExpr.hs @@ -227,7 +227,7 @@ Suppose the inner loop is P->R->P->R etc. Then here is how many heap checks we get in the *inner loop* under various conditions - Alooc Heap check in branches (!Q!, !R!)? + Alloc Heap check in branches (!Q!, !R!)? P Q R yes no (absorb to !P!) -------------------------------------- n n n 0 0 @@ -877,7 +877,7 @@ emitEnter fun = do -- -- Note in particular that the label Lret is used as a -- destination by both the tag-test and the call. This is - -- becase Lret will necessarily be a proc-point, and we want to + -- because Lret will necessarily be a proc-point, and we want to -- ensure that we generate only one proc-point for this -- sequence. -- diff --git a/compiler/simplCore/Simplify.hs b/compiler/simplCore/Simplify.hs index 7138d89..8bc5dc4 100644 --- a/compiler/simplCore/Simplify.hs +++ b/compiler/simplCore/Simplify.hs @@ -590,7 +590,7 @@ makeTrivialWithInfo top_lvl env context info expr ; env' <- completeNonRecX top_lvl env False var var expr ; expr' <- simplVar env' var ; return (env', expr') } - -- The simplVar is needed becase we're constructing a new binding + -- The simplVar is needed because we're constructing a new binding -- a = rhs -- And if rhs is of form (rhs1 |> co), then we might get -- a1 = rhs1 diff --git a/compiler/stgSyn/StgSyn.hs b/compiler/stgSyn/StgSyn.hs index 2c22a29..2f29f1e 100644 --- a/compiler/stgSyn/StgSyn.hs +++ b/compiler/stgSyn/StgSyn.hs @@ -137,7 +137,7 @@ isAddrRep _ = False -- | Type of an @StgArg@ -- --- Very half baked becase we have lost the type arguments. +-- Very half baked because we have lost the type arguments. stgArgType :: StgArg -> Type stgArgType (StgVarArg v) = idType v stgArgType (StgLitArg lit) = literalType lit diff --git a/compiler/typecheck/TcSplice.hs b/compiler/typecheck/TcSplice.hs index 6ae1ba4..6e09b99 100644 --- a/compiler/typecheck/TcSplice.hs +++ b/compiler/typecheck/TcSplice.hs @@ -1262,7 +1262,7 @@ lookupThName_maybe th_name ; return (listToMaybe names) } where lookup rdr_name - = do { -- Repeat much of lookupOccRn, becase we want + = do { -- Repeat much of lookupOccRn, because we want -- to report errors in a TH-relevant way ; rdr_env <- getLocalRdrEnv ; case lookupLocalRdrEnv rdr_env rdr_name of From git at git.haskell.org Tue Jul 26 09:46:03 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 26 Jul 2016 09:46:03 +0000 (UTC) Subject: [commit: ghc] wip/12368: Degrade "case scrutinee not known to diverge for sure" Lint error (09c2d6e) Message-ID: <20160726094603.5751A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/12368 Link : http://ghc.haskell.org/trac/ghc/changeset/09c2d6e2bae5bf81e9ea567969c32a52a367c949/ghc >--------------------------------------------------------------- commit 09c2d6e2bae5bf81e9ea567969c32a52a367c949 Author: Joachim Breitner Date: Tue Jul 26 11:44:53 2016 +0200 Degrade "case scrutinee not known to diverge for sure" Lint error as proposed in #12435. For now, this is just on my branch to be able to continue compilation on the auto-builders. >--------------------------------------------------------------- 09c2d6e2bae5bf81e9ea567969c32a52a367c949 compiler/coreSyn/CoreLint.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/coreSyn/CoreLint.hs b/compiler/coreSyn/CoreLint.hs index dead929..d13d186 100644 --- a/compiler/coreSyn/CoreLint.hs +++ b/compiler/coreSyn/CoreLint.hs @@ -715,7 +715,7 @@ lintCoreExpr e@(Case scrut var alt_ty alts) = ; when (null alts) $ do { checkL (not (exprIsHNF scrut)) (text "No alternatives for a case scrutinee in head-normal form:" <+> ppr scrut) - ; checkL scrut_diverges + ; checkWarnL scrut_diverges (text "No alternatives for a case scrutinee not known to diverge for sure:" <+> ppr scrut) } From git at git.haskell.org Tue Jul 26 10:10:03 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 26 Jul 2016 10:10:03 +0000 (UTC) Subject: [commit: ghc] wip/12368: WwLib: Add strictness signature to "let x = absentError …" (437d6fb) Message-ID: <20160726101003.7799F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/12368 Link : http://ghc.haskell.org/trac/ghc/changeset/437d6fbab086fed3ffb814ea959e41448d5a3af8/ghc >--------------------------------------------------------------- commit 437d6fbab086fed3ffb814ea959e41448d5a3af8 Author: Joachim Breitner Date: Tue Jul 26 12:08:59 2016 +0200 WwLib: Add strictness signature to "let x = absentError …" indicating that it is bottom. This should help making the "empty cases" lint error give less false alarms. >--------------------------------------------------------------- 437d6fbab086fed3ffb814ea959e41448d5a3af8 compiler/basicTypes/Demand.hs | 7 +++++-- compiler/stranal/WwLib.hs | 11 ++++++----- 2 files changed, 11 insertions(+), 7 deletions(-) diff --git a/compiler/basicTypes/Demand.hs b/compiler/basicTypes/Demand.hs index 2ada6b3..7cbbbf8 100644 --- a/compiler/basicTypes/Demand.hs +++ b/compiler/basicTypes/Demand.hs @@ -35,7 +35,8 @@ module Demand ( vanillaCprProdRes, cprSumRes, appIsBottom, isBottomingSig, pprIfaceStrictSig, trimCPRInfo, returnsCPR_maybe, - StrictSig(..), mkStrictSig, mkClosedStrictSig, nopSig, botSig, cprProdSig, + StrictSig(..), mkStrictSig, mkClosedStrictSig, + nopSig, botSig, exnSig, cprProdSig, isTopSig, hasDemandEnvSig, splitStrictSig, strictSigDmdEnv, increaseStrictSigArity, @@ -1264,9 +1265,10 @@ emptyDmdEnv = emptyVarEnv -- (lazy, absent, no CPR information, no termination information). -- Note that it is ''not'' the top of the lattice (which would be "may use everything"), -- so it is (no longer) called topDmd -nopDmdType, botDmdType :: DmdType +nopDmdType, botDmdType, exnDmdType :: DmdType nopDmdType = DmdType emptyDmdEnv [] topRes botDmdType = DmdType emptyDmdEnv [] botRes +exnDmdType = DmdType emptyDmdEnv [] exnRes cprProdDmdType :: Arity -> DmdType cprProdDmdType arity @@ -1694,6 +1696,7 @@ isBottomingSig (StrictSig (DmdType _ _ res)) = isBotRes res nopSig, botSig :: StrictSig nopSig = StrictSig nopDmdType botSig = StrictSig botDmdType +exnSig = StrictSig exnDmdType cprProdSig :: Arity -> StrictSig cprProdSig arity = StrictSig (cprProdDmdType arity) diff --git a/compiler/stranal/WwLib.hs b/compiler/stranal/WwLib.hs index 812252c..c0b1af3 100644 --- a/compiler/stranal/WwLib.hs +++ b/compiler/stranal/WwLib.hs @@ -709,7 +709,7 @@ every primitive type, so the function is partial. mk_absent_let :: DynFlags -> Id -> Maybe (CoreExpr -> CoreExpr) mk_absent_let dflags arg | not (isUnliftedType arg_ty) - = Just (Let (NonRec arg abs_rhs)) + = Just (Let (NonRec lifted_arg abs_rhs)) | Just tc <- tyConAppTyCon_maybe arg_ty , Just lit <- absentLiteralOf tc = Just (Let (NonRec arg (Lit lit))) @@ -719,10 +719,11 @@ mk_absent_let dflags arg = WARN( True, text "No absent value for" <+> ppr arg_ty ) Nothing where - arg_ty = idType arg - abs_rhs = mkRuntimeErrorApp aBSENT_ERROR_ID arg_ty msg - msg = showSDoc (gopt_set dflags Opt_SuppressUniques) - (ppr arg <+> ppr (idType arg)) + arg_ty = idType arg + abs_rhs = mkRuntimeErrorApp aBSENT_ERROR_ID arg_ty msg + lifted_arg = arg `setIdStrictness` exnSig + msg = showSDoc (gopt_set dflags Opt_SuppressUniques) + (ppr arg <+> ppr (idType arg)) -- We need to suppress uniques here because otherwise they'd -- end up in the generated code as strings. This is bad for -- determinism, because with different uniques the strings From git at git.haskell.org Tue Jul 26 11:30:35 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 26 Jul 2016 11:30:35 +0000 (UTC) Subject: [commit: ghc] wip/12368: WwLib: Add strictness signature to "let x = absentError …" (d20fee5) Message-ID: <20160726113035.E4BD43A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/12368 Link : http://ghc.haskell.org/trac/ghc/changeset/d20fee5383d9618690fa505d8c59653d27782a02/ghc >--------------------------------------------------------------- commit d20fee5383d9618690fa505d8c59653d27782a02 Author: Joachim Breitner Date: Tue Jul 26 12:08:59 2016 +0200 WwLib: Add strictness signature to "let x = absentError …" indicating that it is bottom. This should help making the "empty cases" lint error give less false alarms. >--------------------------------------------------------------- d20fee5383d9618690fa505d8c59653d27782a02 compiler/basicTypes/Demand.hs | 9 ++++++--- compiler/stranal/WwLib.hs | 11 ++++++----- 2 files changed, 12 insertions(+), 8 deletions(-) diff --git a/compiler/basicTypes/Demand.hs b/compiler/basicTypes/Demand.hs index 2ada6b3..d79fa6e 100644 --- a/compiler/basicTypes/Demand.hs +++ b/compiler/basicTypes/Demand.hs @@ -35,7 +35,8 @@ module Demand ( vanillaCprProdRes, cprSumRes, appIsBottom, isBottomingSig, pprIfaceStrictSig, trimCPRInfo, returnsCPR_maybe, - StrictSig(..), mkStrictSig, mkClosedStrictSig, nopSig, botSig, cprProdSig, + StrictSig(..), mkStrictSig, mkClosedStrictSig, + nopSig, botSig, exnSig, cprProdSig, isTopSig, hasDemandEnvSig, splitStrictSig, strictSigDmdEnv, increaseStrictSigArity, @@ -1264,9 +1265,10 @@ emptyDmdEnv = emptyVarEnv -- (lazy, absent, no CPR information, no termination information). -- Note that it is ''not'' the top of the lattice (which would be "may use everything"), -- so it is (no longer) called topDmd -nopDmdType, botDmdType :: DmdType +nopDmdType, botDmdType, exnDmdType :: DmdType nopDmdType = DmdType emptyDmdEnv [] topRes botDmdType = DmdType emptyDmdEnv [] botRes +exnDmdType = DmdType emptyDmdEnv [] exnRes cprProdDmdType :: Arity -> DmdType cprProdDmdType arity @@ -1691,9 +1693,10 @@ isBottomingSig :: StrictSig -> Bool -- True if the signature diverges or throws an exception isBottomingSig (StrictSig (DmdType _ _ res)) = isBotRes res -nopSig, botSig :: StrictSig +nopSig, botSig, exnSig :: StrictSig nopSig = StrictSig nopDmdType botSig = StrictSig botDmdType +exnSig = StrictSig exnDmdType cprProdSig :: Arity -> StrictSig cprProdSig arity = StrictSig (cprProdDmdType arity) diff --git a/compiler/stranal/WwLib.hs b/compiler/stranal/WwLib.hs index 812252c..c0b1af3 100644 --- a/compiler/stranal/WwLib.hs +++ b/compiler/stranal/WwLib.hs @@ -709,7 +709,7 @@ every primitive type, so the function is partial. mk_absent_let :: DynFlags -> Id -> Maybe (CoreExpr -> CoreExpr) mk_absent_let dflags arg | not (isUnliftedType arg_ty) - = Just (Let (NonRec arg abs_rhs)) + = Just (Let (NonRec lifted_arg abs_rhs)) | Just tc <- tyConAppTyCon_maybe arg_ty , Just lit <- absentLiteralOf tc = Just (Let (NonRec arg (Lit lit))) @@ -719,10 +719,11 @@ mk_absent_let dflags arg = WARN( True, text "No absent value for" <+> ppr arg_ty ) Nothing where - arg_ty = idType arg - abs_rhs = mkRuntimeErrorApp aBSENT_ERROR_ID arg_ty msg - msg = showSDoc (gopt_set dflags Opt_SuppressUniques) - (ppr arg <+> ppr (idType arg)) + arg_ty = idType arg + abs_rhs = mkRuntimeErrorApp aBSENT_ERROR_ID arg_ty msg + lifted_arg = arg `setIdStrictness` exnSig + msg = showSDoc (gopt_set dflags Opt_SuppressUniques) + (ppr arg <+> ppr (idType arg)) -- We need to suppress uniques here because otherwise they'd -- end up in the generated code as strings. This is bad for -- determinism, because with different uniques the strings From git at git.haskell.org Tue Jul 26 14:06:17 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 26 Jul 2016 14:06:17 +0000 (UTC) Subject: [commit: ghc] wip/12368: dmdFix abortion: Get lazy_fv from set of free variables (a1acc1f) Message-ID: <20160726140617.8A7463A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/12368 Link : http://ghc.haskell.org/trac/ghc/changeset/a1acc1f4b23ef96f869acec284348bf8588c9546/ghc >--------------------------------------------------------------- commit a1acc1f4b23ef96f869acec284348bf8588c9546 Author: Joachim Breitner Date: Tue Jul 26 16:05:42 2016 +0200 dmdFix abortion: Get lazy_fv from set of free variables hopefully more reliable. >--------------------------------------------------------------- a1acc1f4b23ef96f869acec284348bf8588c9546 compiler/stranal/DmdAnal.hs | 10 ++++++---- 1 file changed, 6 insertions(+), 4 deletions(-) diff --git a/compiler/stranal/DmdAnal.hs b/compiler/stranal/DmdAnal.hs index 22e1faa..fb0b4c5 100644 --- a/compiler/stranal/DmdAnal.hs +++ b/compiler/stranal/DmdAnal.hs @@ -24,6 +24,7 @@ import Data.List import DataCon import Id import CoreUtils ( exprIsHNF, exprType, exprIsTrivial ) +import CoreFVs import TyCon import Type import Coercion ( Coercion, coVarsOfCo ) @@ -495,11 +496,12 @@ dmdFix top_lvl env orig_pairs -- If fixed-point iteration does not yield a result we use this instead -- See Note [Safe abortion in the fixed-point iteration] abort :: (AnalEnv, DmdEnv, [(Id,CoreExpr)]) - abort = (env, lazy_fv', zapped_pairs) - where (lazy_fv, pairs') = step True (zapIdStrictness orig_pairs) + abort = (env, lazy_fv, zapped_pairs) + where (_, pairs') = step True (zapIdStrictness orig_pairs) -- Note [Lazy and unleasheable free variables] - non_lazy_fvs = plusVarEnvList $ map (strictSigDmdEnv . idStrictness . fst) pairs' - lazy_fv' = lazy_fv `plusVarEnv` mapVarEnv (const topDmd) non_lazy_fvs + lazy_fv = mkVarEnv [ (v, topDmd) + | (_,rhs) <- orig_pairs + , v <- exprFreeIdsList rhs ] zapped_pairs = zapIdStrictness pairs' -- The fixed-point varies the idStrictness field of the binders, and terminates if that From git at git.haskell.org Tue Jul 26 14:48:10 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 26 Jul 2016 14:48:10 +0000 (UTC) Subject: [commit: ghc] master: MonadUtils: Typos in comments (a9251c6) Message-ID: <20160726144810.4E9A83A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a9251c6158217271f0e59b8b91b69fe932e3e77f/ghc >--------------------------------------------------------------- commit a9251c6158217271f0e59b8b91b69fe932e3e77f Author: Ömer Sinan Ağacan Date: Tue Jul 26 14:47:43 2016 +0000 MonadUtils: Typos in comments >--------------------------------------------------------------- a9251c6158217271f0e59b8b91b69fe932e3e77f compiler/utils/MonadUtils.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/utils/MonadUtils.hs b/compiler/utils/MonadUtils.hs index 812e4e8..d1c0adb 100644 --- a/compiler/utils/MonadUtils.hs +++ b/compiler/utils/MonadUtils.hs @@ -1,7 +1,7 @@ {-# LANGUAGE CPP #-} -- | Utilities related to Monad and Applicative classes --- Mostly for backwards compatability. +-- Mostly for backwards compatibility. module MonadUtils ( Applicative(..) @@ -126,7 +126,7 @@ mapAndUnzip5M f (x:xs) = do -- | Monadic version of mapAccumL mapAccumLM :: Monad m - => (acc -> x -> m (acc, y)) -- ^ combining funcction + => (acc -> x -> m (acc, y)) -- ^ combining function -> acc -- ^ initial state -> [x] -- ^ inputs -> m (acc, [y]) -- ^ final state, outputs From git at git.haskell.org Tue Jul 26 16:30:17 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 26 Jul 2016 16:30:17 +0000 (UTC) Subject: [commit: ghc] master: Fix productivity calculation (#12424) (1783011) Message-ID: <20160726163017.AB03E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1783011726a355ac7647246699d43bc7d8b6d9f1/ghc >--------------------------------------------------------------- commit 1783011726a355ac7647246699d43bc7d8b6d9f1 Author: Simon Marlow Date: Tue Jul 26 07:55:37 2016 -0700 Fix productivity calculation (#12424) >--------------------------------------------------------------- 1783011726a355ac7647246699d43bc7d8b6d9f1 rts/Stats.c | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/rts/Stats.c b/rts/Stats.c index 30f346e..e422a36 100644 --- a/rts/Stats.c +++ b/rts/Stats.c @@ -699,8 +699,8 @@ stat_exit (void) TimeToSecondsDbl(tot_cpu - gc_cpu - PROF_VAL(RP_tot_time + HC_tot_time) - init_cpu) * 100 / TimeToSecondsDbl(tot_cpu), - TimeToSecondsDbl(tot_cpu - gc_cpu - - PROF_VAL(RP_tot_time + HC_tot_time) - init_cpu) * 100 + TimeToSecondsDbl(tot_elapsed - gc_elapsed - + PROF_VAL(RPe_tot_time + HCe_tot_time) - init_elapsed) * 100 / TimeToSecondsDbl(tot_elapsed)); /* From git at git.haskell.org Tue Jul 26 16:30:20 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 26 Jul 2016 16:30:20 +0000 (UTC) Subject: [commit: ghc] master: Accept better stats for T9675 (9d62f0d) Message-ID: <20160726163020.703E03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9d62f0d1086ad5c112b41a0ddae10c20e8ffb77e/ghc >--------------------------------------------------------------- commit 9d62f0d1086ad5c112b41a0ddae10c20e8ffb77e Author: Simon Marlow Date: Tue Jul 26 08:01:58 2016 -0700 Accept better stats for T9675 >--------------------------------------------------------------- 9d62f0d1086ad5c112b41a0ddae10c20e8ffb77e testsuite/tests/perf/compiler/all.T | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index 2e4d43d..4efc409 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -664,7 +664,7 @@ test('T9675', # 2016-04-06 18043224 (x86/Linux, 64-bit machine) ]), compiler_stats_num_field('peak_megabytes_allocated', # Note [residency] - [(wordsize(64), 144, 15), + [(wordsize(64), 121, 15), # 2014-10-13 66 # 2014-10-13 58 seq the DmdEnv in seqDmdType as well # 2014-10-13 49 different machines giving different results... @@ -674,6 +674,7 @@ test('T9675', # 2015-12-04 88 new pattern checker (D1535) # 2015-12-11 113 TypeInType (see #11196) # 2016-04-14 144 Final demand analyzer run + # 2016-07-26 121 Unboxed sums? (wordsize(32), 56, 15) # 2015-07-11 56 (x86/Linux, 64-bit machine) use +RTS -G1 ]), From git at git.haskell.org Tue Jul 26 23:11:09 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 26 Jul 2016 23:11:09 +0000 (UTC) Subject: [commit: ghc] master: Compute boot-defined TyCon names from ModIface. (8f63ba3) Message-ID: <20160726231109.B63033A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8f63ba30b170c7063640b789ce703f68dca2c21b/ghc >--------------------------------------------------------------- commit 8f63ba30b170c7063640b789ce703f68dca2c21b Author: Edward Z. Yang Date: Sat Jul 2 18:08:55 2016 -0700 Compute boot-defined TyCon names from ModIface. Summary: Three things in this commit: 1. Get rid of sb_ids; we are not going to use them to avoid infinite unfoldings in hs-boot files. 2. Compute sb_tcs from ModIface rather than ModDetails. This means that the typechecker can look at this field without forcing the boot ModDetails, which would be bad if the ModDetails is not available yet (due to knot tying.) 3. A big honking comment explaining what is going on here. Signed-off-by: Edward Z. Yang Reviewers: simonpj, austin, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2380 >--------------------------------------------------------------- 8f63ba30b170c7063640b789ce703f68dca2c21b compiler/iface/TcIface.hs | 31 ++++++++++++----- compiler/rename/RnSource.hs | 77 +++++++++++++++++++++++++++++++++-------- compiler/typecheck/TcRnTypes.hs | 8 ++--- 3 files changed, 89 insertions(+), 27 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 8f63ba30b170c7063640b789ce703f68dca2c21b From git at git.haskell.org Wed Jul 27 15:25:38 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 27 Jul 2016 15:25:38 +0000 (UTC) Subject: [commit: ghc] master: Add mblocks_allocated to GC stats API (b0a5144) Message-ID: <20160727152538.658253A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b0a5144348d6abad18e771ad2cf3134a5724b969/ghc >--------------------------------------------------------------- commit b0a5144348d6abad18e771ad2cf3134a5724b969 Author: Bartosz Nitka Date: Wed Jul 27 08:24:40 2016 -0700 Add mblocks_allocated to GC stats API This exposes mblocks_allocated in the GCStats struct. Test Plan: it builds Reviewers: bgamari, simonmar, austin, hvr, erikd Reviewed By: erikd Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2429 >--------------------------------------------------------------- b0a5144348d6abad18e771ad2cf3134a5724b969 includes/rts/storage/GC.h | 1 + libraries/base/GHC/Stats.hsc | 2 ++ rts/Stats.c | 1 + 3 files changed, 4 insertions(+) diff --git a/includes/rts/storage/GC.h b/includes/rts/storage/GC.h index 50fc5eb..6dc483f 100644 --- a/includes/rts/storage/GC.h +++ b/includes/rts/storage/GC.h @@ -237,6 +237,7 @@ typedef struct _GCStats { StgWord64 current_bytes_slop; StgWord64 max_bytes_slop; StgWord64 peak_megabytes_allocated; + StgWord64 mblocks_allocated; StgWord64 par_tot_bytes_copied; StgWord64 par_max_bytes_copied; StgDouble mutator_cpu_seconds; diff --git a/libraries/base/GHC/Stats.hsc b/libraries/base/GHC/Stats.hsc index 73e2de9..a8b43ef 100644 --- a/libraries/base/GHC/Stats.hsc +++ b/libraries/base/GHC/Stats.hsc @@ -72,6 +72,7 @@ data GCStats = GCStats , peakMegabytesAllocated :: !Int64 -- | CPU time spent running mutator threads. This does not include -- any profiling overhead or initialization. + , mblocksAllocated :: !Int64 -- ^ Number of allocated megablocks , mutatorCpuSeconds :: !Double -- | Wall clock time spent running mutator threads. This does not @@ -131,6 +132,7 @@ getGCStats = do currentBytesSlop <- (# peek GCStats, current_bytes_slop) p maxBytesSlop <- (# peek GCStats, max_bytes_slop) p peakMegabytesAllocated <- (# peek GCStats, peak_megabytes_allocated ) p + mblocksAllocated <- (# peek GCStats, mblocks_allocated) p {- initCpuSeconds <- (# peek GCStats, init_cpu_seconds) p initWallSeconds <- (# peek GCStats, init_wall_seconds) p diff --git a/rts/Stats.c b/rts/Stats.c index e422a36..d10738a 100644 --- a/rts/Stats.c +++ b/rts/Stats.c @@ -883,6 +883,7 @@ extern void getGCStats( GCStats *s ) s->max_bytes_used = max_residency*sizeof(W_); s->cumulative_bytes_used = cumulative_residency*(StgWord64)sizeof(W_); s->peak_megabytes_allocated = (StgWord64)(peak_mblocks_allocated * MBLOCK_SIZE / (1024L * 1024L)); + s->mblocks_allocated = (StgWord64)mblocks_allocated; s->bytes_copied = GC_tot_copied*(StgWord64)sizeof(W_); s->max_bytes_slop = max_slop*(StgWord64)sizeof(W_); s->current_bytes_used = current_residency*(StgWord64)sizeof(W_); From git at git.haskell.org Wed Jul 27 15:26:41 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 27 Jul 2016 15:26:41 +0000 (UTC) Subject: [commit: ghc] master: Move stat_startGCSync (e98edbd) Message-ID: <20160727152641.DCEEC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e98edbd1b8947dcb4a47d20fc854c0a9a6954bea/ghc >--------------------------------------------------------------- commit e98edbd1b8947dcb4a47d20fc854c0a9a6954bea Author: Bartosz Nitka Date: Wed Jul 27 08:25:59 2016 -0700 Move stat_startGCSync @simonmar told me that it makes more sense this way. Test Plan: it still builds Reviewers: bgamari, austin, simonmar, erikd Reviewed By: simonmar, erikd Subscribers: thomie, simonmar Differential Revision: https://phabricator.haskell.org/D2428 >--------------------------------------------------------------- e98edbd1b8947dcb4a47d20fc854c0a9a6954bea rts/Schedule.c | 2 ++ rts/sm/GC.c | 2 -- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/rts/Schedule.c b/rts/Schedule.c index d9ab913..c3911af 100644 --- a/rts/Schedule.c +++ b/rts/Schedule.c @@ -1646,6 +1646,8 @@ scheduleDoGC (Capability **pcap, Task *task USED_IF_THREADS, } while (was_syncing); } + stat_startGCSync(gc_threads[cap->no]); + #ifdef DEBUG unsigned int old_n_capabilities = n_capabilities; #endif diff --git a/rts/sm/GC.c b/rts/sm/GC.c index 7796f30..a6a1a9a 100644 --- a/rts/sm/GC.c +++ b/rts/sm/GC.c @@ -1099,8 +1099,6 @@ waitForGcThreads (Capability *cap USED_IF_THREADS) uint32_t i, j; rtsBool retry = rtsTrue; - stat_startGCSync(gc_threads[cap->no]); - while(retry) { for (i=0; i < n_threads; i++) { if (i == me || gc_threads[i]->idle) continue; From git at git.haskell.org Thu Jul 28 15:15:12 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 28 Jul 2016 15:15:12 +0000 (UTC) Subject: [commit: ghc] master: Make Unique a newtype (d3feb16) Message-ID: <20160728151512.BB65D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d3feb16a91bb285ce677fb79381f36e9fcdc0979/ghc >--------------------------------------------------------------- commit d3feb16a91bb285ce677fb79381f36e9fcdc0979 Author: Ömer Sinan Ağacan Date: Thu Jul 28 15:13:54 2016 +0000 Make Unique a newtype Reviewers: austin, bgamari Reviewed By: bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2432 >--------------------------------------------------------------- d3feb16a91bb285ce677fb79381f36e9fcdc0979 compiler/basicTypes/Unique.hs | 4 +--- 1 file changed, 1 insertion(+), 3 deletions(-) diff --git a/compiler/basicTypes/Unique.hs b/compiler/basicTypes/Unique.hs index 545ea9f..c42b825 100644 --- a/compiler/basicTypes/Unique.hs +++ b/compiler/basicTypes/Unique.hs @@ -87,12 +87,10 @@ The @Chars@ are ``tag letters'' that identify the @UniqueSupply at . Fast comparison is everything on @Uniques@: -} ---why not newtype Int? - -- | The type of unique identifiers that are used in many places in GHC -- for fast ordering and equality tests. You should generate these with -- the functions from the 'UniqSupply' module -data Unique = MkUnique {-# UNPACK #-} !Int +newtype Unique = MkUnique Int {- Now come the functions which construct uniques from their pieces, and vice versa. From git at git.haskell.org Fri Jul 29 16:28:43 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 29 Jul 2016 16:28:43 +0000 (UTC) Subject: [commit: ghc] wip/ttypeable: Kill redundant comment (eee52b8) Message-ID: <20160729162843.732763A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttypeable Link : http://ghc.haskell.org/trac/ghc/changeset/eee52b86426da311295bb4169d7d5029948edf21/ghc >--------------------------------------------------------------- commit eee52b86426da311295bb4169d7d5029948edf21 Author: Ben Gamari Date: Fri Jul 8 17:07:12 2016 +0200 Kill redundant comment >--------------------------------------------------------------- eee52b86426da311295bb4169d7d5029948edf21 libraries/base/Data/Typeable/Internal.hs | 6 ------ 1 file changed, 6 deletions(-) diff --git a/libraries/base/Data/Typeable/Internal.hs b/libraries/base/Data/Typeable/Internal.hs index e73fee6..9e22c22 100644 --- a/libraries/base/Data/Typeable/Internal.hs +++ b/libraries/base/Data/Typeable/Internal.hs @@ -292,12 +292,6 @@ eqTypeRep a b | typeRepFingerprint a == typeRepFingerprint b = Just (unsafeCoerce# HRefl) | otherwise = Nothing -{- ********************************************************************* -* * - The Typeable class -* * -********************************************************************* -} - ------------------------------------------------------------- -- -- The Typeable class and friends From git at git.haskell.org Fri Jul 29 16:28:46 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 29 Jul 2016 16:28:46 +0000 (UTC) Subject: [commit: ghc] wip/ttypeable: Note need for mkTrApp (76caca2) Message-ID: <20160729162846.1F3053A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttypeable Link : http://ghc.haskell.org/trac/ghc/changeset/76caca2429bde59fcd9c3637b7ade72e5d44d4ab/ghc >--------------------------------------------------------------- commit 76caca2429bde59fcd9c3637b7ade72e5d44d4ab Author: Ben Gamari Date: Fri Jul 8 23:10:45 2016 +0200 Note need for mkTrApp >--------------------------------------------------------------- 76caca2429bde59fcd9c3637b7ade72e5d44d4ab libraries/base/Data/Typeable/Internal.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/libraries/base/Data/Typeable/Internal.hs b/libraries/base/Data/Typeable/Internal.hs index 9e22c22..25c7399 100644 --- a/libraries/base/Data/Typeable/Internal.hs +++ b/libraries/base/Data/Typeable/Internal.hs @@ -225,7 +225,9 @@ mkTrCon tc kind = TrTyCon fpr tc kind fpr = fingerprintFingerprints [fpr_tc, fpr_k] -- | Construct a representation for a type application. --- TODO: Is this necessary? +-- +-- Note that this is known-key to the compiler, which uses it in desugar +-- 'Typeable' evidence. mkTrApp :: forall k1 k2 (a :: k1 -> k2) (b :: k1). TypeRep (a :: k1 -> k2) -> TypeRep (b :: k1) From git at git.haskell.org Fri Jul 29 16:28:48 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 29 Jul 2016 16:28:48 +0000 (UTC) Subject: [commit: ghc] wip/ttypeable: Make TRApp bidirectional (b3a9a72) Message-ID: <20160729162848.C01FC3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttypeable Link : http://ghc.haskell.org/trac/ghc/changeset/b3a9a72894d776b26ee14fbe82e728f041db1dbf/ghc >--------------------------------------------------------------- commit b3a9a72894d776b26ee14fbe82e728f041db1dbf Author: Ben Gamari Date: Sun Jul 10 10:51:23 2016 +0200 Make TRApp bidirectional >--------------------------------------------------------------- b3a9a72894d776b26ee14fbe82e728f041db1dbf libraries/base/Data/Typeable/Internal.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/libraries/base/Data/Typeable/Internal.hs b/libraries/base/Data/Typeable/Internal.hs index 25c7399..8213c12 100644 --- a/libraries/base/Data/Typeable/Internal.hs +++ b/libraries/base/Data/Typeable/Internal.hs @@ -247,6 +247,7 @@ pattern TRApp :: forall k2 (t :: k2). () => forall k1 (a :: k1 -> k2) (b :: k1). (t ~ a b) => TypeRep a -> TypeRep b -> TypeRep t pattern TRApp f x <- TrApp _ f x + where TRApp f x = mkTrApp f x -- | Use a 'TypeRep' as 'Typeable' evidence. withTypeable :: forall a r. TypeRep a -> (Typeable a => r) -> r From git at git.haskell.org Fri Jul 29 16:28:51 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 29 Jul 2016 16:28:51 +0000 (UTC) Subject: [commit: ghc] wip/ttypeable: Add TRArrow pattern synonym (f03c84a) Message-ID: <20160729162851.6D8C13A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttypeable Link : http://ghc.haskell.org/trac/ghc/changeset/f03c84a652cb7e0a4269b3ab7d4ff4fb48ac87ef/ghc >--------------------------------------------------------------- commit f03c84a652cb7e0a4269b3ab7d4ff4fb48ac87ef Author: Ben Gamari Date: Sun Jul 10 10:51:33 2016 +0200 Add TRArrow pattern synonym >--------------------------------------------------------------- f03c84a652cb7e0a4269b3ab7d4ff4fb48ac87ef libraries/base/Data/Typeable/Internal.hs | 8 ++++++-- 1 file changed, 6 insertions(+), 2 deletions(-) diff --git a/libraries/base/Data/Typeable/Internal.hs b/libraries/base/Data/Typeable/Internal.hs index 8213c12..702616f 100644 --- a/libraries/base/Data/Typeable/Internal.hs +++ b/libraries/base/Data/Typeable/Internal.hs @@ -186,13 +186,17 @@ instance Ord TypeRepX where TypeRepX a `compare` TypeRepX b = typeRepFingerprint a `compare` typeRepFingerprint b +--pattern TRArrow :: TypeRep (->) +pattern TRArrow <- (eqTypeRep trArrow -> Just HRefl) + where TRArrow = trArrow + pattern TRFun :: forall fun. () => forall arg res. (fun ~ (arg -> res)) => TypeRep arg -> TypeRep res -> TypeRep fun -pattern TRFun arg res <- TrApp _ (TrApp _ (eqTypeRep trArrow -> Just HRefl) arg) res where - TRFun arg res = mkTrApp (mkTrApp trArrow arg) res +pattern TRFun arg res <- TRApp (TRApp TRArrow arg) res + where TRFun arg res = mkTrApp (mkTrApp trArrow arg) res decomposeFun :: forall fun r. TypeRep fun From git at git.haskell.org Fri Jul 29 16:28:54 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 29 Jul 2016 16:28:54 +0000 (UTC) Subject: [commit: ghc] wip/ttypeable: Fix up type printer (d5c09aa) Message-ID: <20160729162854.1AA623A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttypeable Link : http://ghc.haskell.org/trac/ghc/changeset/d5c09aa1e59db3044b8ef086f1db2a348c954ef4/ghc >--------------------------------------------------------------- commit d5c09aa1e59db3044b8ef086f1db2a348c954ef4 Author: Ben Gamari Date: Sun Jul 10 10:51:56 2016 +0200 Fix up type printer >--------------------------------------------------------------- d5c09aa1e59db3044b8ef086f1db2a348c954ef4 libraries/base/Data/Typeable/Internal.hs | 10 +++++++--- 1 file changed, 7 insertions(+), 3 deletions(-) diff --git a/libraries/base/Data/Typeable/Internal.hs b/libraries/base/Data/Typeable/Internal.hs index 702616f..6e5242b 100644 --- a/libraries/base/Data/Typeable/Internal.hs +++ b/libraries/base/Data/Typeable/Internal.hs @@ -333,13 +333,17 @@ instance Show (TypeRep (a :: k)) where showsPrec = showTypeable showTypeable :: Int -> TypeRep (a :: k) -> ShowS -showTypeable p rep = +showTypeable p rep + | Just HRefl <- star `eqTypeRep` rep = + showTypeable' 9 rep + + | otherwise = showParen (p > 9) $ - showTypeable' 8 rep . showString " :: " . showTypeable' 8 (typeRepKind rep) + showTypeable' 9 rep . showString " :: " . showTypeable' 8 (typeRepKind rep) showTypeable' :: Int -> TypeRep (a :: k) -> ShowS showTypeable' _ rep - | Just HRefl <- rep `eqTypeRep` (typeRep :: TypeRep *) = + | Just HRefl <- rep `eqTypeRep` (typeRep :: TypeRep Type) = showChar '*' | isListTyCon tc, [ty] <- tys = showChar '[' . shows ty . showChar ']' From git at git.haskell.org Fri Jul 29 16:28:56 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 29 Jul 2016 16:28:56 +0000 (UTC) Subject: [commit: ghc] wip/ttypeable: submodule changes (b1c0eee) Message-ID: <20160729162856.BC7AE3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttypeable Link : http://ghc.haskell.org/trac/ghc/changeset/b1c0eee272d1ec115907c8b0c62ca0316b292540/ghc >--------------------------------------------------------------- commit b1c0eee272d1ec115907c8b0c62ca0316b292540 Author: Ben Gamari Date: Sun Jul 10 10:54:02 2016 +0200 submodule changes >--------------------------------------------------------------- b1c0eee272d1ec115907c8b0c62ca0316b292540 libraries/hpc | 2 +- libraries/unix | 2 +- utils/haddock | 2 +- 3 files changed, 3 insertions(+), 3 deletions(-) diff --git a/libraries/hpc b/libraries/hpc index 0741f65..956887d 160000 --- a/libraries/hpc +++ b/libraries/hpc @@ -1 +1 @@ -Subproject commit 0741f656fdadc14960f55e1970080d4699371055 +Subproject commit 956887d4a15de3e68aae82b14bfa1630c8149649 diff --git a/libraries/unix b/libraries/unix index 861ad25..40820da 160000 --- a/libraries/unix +++ b/libraries/unix @@ -1 +1 @@ -Subproject commit 861ad256e0a5337a1a685b1cd50ae91ee9374cab +Subproject commit 40820da5fb35c53aed53c211277c3e6077c1ddf9 diff --git a/utils/haddock b/utils/haddock index 375a8d8..008e61d 160000 --- a/utils/haddock +++ b/utils/haddock @@ -1 +1 @@ -Subproject commit 375a8d8c7203857863992483df9f9d24ec93ecab +Subproject commit 008e61d0c4b10713751c2a1de4958acc75367396 From git at git.haskell.org Fri Jul 29 16:28:59 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 29 Jul 2016 16:28:59 +0000 (UTC) Subject: [commit: ghc] wip/ttypeable: TcInteract: Fix something (1ba46de) Message-ID: <20160729162859.6630A3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttypeable Link : http://ghc.haskell.org/trac/ghc/changeset/1ba46deb84b22b56b3808b8ed8092950a438c747/ghc >--------------------------------------------------------------- commit 1ba46deb84b22b56b3808b8ed8092950a438c747 Author: Ben Gamari Date: Fri Jul 15 00:59:57 2016 +0200 TcInteract: Fix something >--------------------------------------------------------------- 1ba46deb84b22b56b3808b8ed8092950a438c747 compiler/typecheck/TcInteract.hs | 0 1 file changed, 0 insertions(+), 0 deletions(-) From git at git.haskell.org Fri Jul 29 16:29:02 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 29 Jul 2016 16:29:02 +0000 (UTC) Subject: [commit: ghc] wip/ttypeable: Fix showTypeable (c251172) Message-ID: <20160729162902.182C03A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttypeable Link : http://ghc.haskell.org/trac/ghc/changeset/c251172f6c0a76f5e89499da6409caf859aa32fa/ghc >--------------------------------------------------------------- commit c251172f6c0a76f5e89499da6409caf859aa32fa Author: Ben Gamari Date: Fri Jul 15 01:00:20 2016 +0200 Fix showTypeable >--------------------------------------------------------------- c251172f6c0a76f5e89499da6409caf859aa32fa libraries/base/Data/Typeable/Internal.hs | 11 +++++------ 1 file changed, 5 insertions(+), 6 deletions(-) diff --git a/libraries/base/Data/Typeable/Internal.hs b/libraries/base/Data/Typeable/Internal.hs index 6e5242b..6237d25 100644 --- a/libraries/base/Data/Typeable/Internal.hs +++ b/libraries/base/Data/Typeable/Internal.hs @@ -334,7 +334,7 @@ instance Show (TypeRep (a :: k)) where showTypeable :: Int -> TypeRep (a :: k) -> ShowS showTypeable p rep - | Just HRefl <- star `eqTypeRep` rep = + | Just HRefl <- star `eqTypeRep` typeRepKind rep = showTypeable' 9 rep | otherwise = @@ -351,14 +351,13 @@ showTypeable' _ rep showChar '(' . showArgs (showChar ',') tys . showChar ')' where (tc, tys) = splitApps rep showTypeable' p (TrTyCon _ tycon _) = showsPrec p tycon - --showsPrec p (TRFun x r) = - -- showParen (p > 8) $ - -- showsPrec 9 x . showString " -> " . showsPrec 8 r +--showTypeable' p (TRFun x r) = +-- showParen (p > 8) $ +-- showsPrec 9 x . showString " -> " . showsPrec 8 r showTypeable' p (TrApp _ (TrApp _ (TrTyCon _ tycon _) x) r) | isArrowTyCon tycon = showParen (p > 8) $ - showsPrec 9 x . showString " -> " . showsPrec p r - + showsPrec 9 x . showString " -> " . showsPrec 8 r showTypeable' p (TrApp _ f x) | otherwise = showParen (p > 9) $ From git at git.haskell.org Fri Jul 29 16:29:04 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 29 Jul 2016 16:29:04 +0000 (UTC) Subject: [commit: ghc] wip/ttypeable: Fix serialization (49145b7) Message-ID: <20160729162904.B6AE63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttypeable Link : http://ghc.haskell.org/trac/ghc/changeset/49145b7403af9fd6bcfd86d3661688bab1c07100/ghc >--------------------------------------------------------------- commit 49145b7403af9fd6bcfd86d3661688bab1c07100 Author: Ben Gamari Date: Sun Jul 17 21:09:57 2016 +0200 Fix serialization >--------------------------------------------------------------- 49145b7403af9fd6bcfd86d3661688bab1c07100 compiler/utils/Binary.hs | 2 +- libraries/ghci/GHCi/TH/Binary.hs | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/utils/Binary.hs b/compiler/utils/Binary.hs index 2282230..466e0eb 100644 --- a/compiler/utils/Binary.hs +++ b/compiler/utils/Binary.hs @@ -609,7 +609,7 @@ getTypeRepX bh = do 2 -> return $ TypeRepX (typeRep :: TypeRep (->)) 3 -> do con <- get bh :: IO TyCon TypeRepX rep_k <- getTypeRepX bh - case rep_k `eqTypeRep` (typeRep :: TypeRep Type) of + case typeRepKind rep_k `eqTypeRep` (typeRep :: TypeRep Type) of Just HRefl -> pure $ TypeRepX $ mkTrCon con rep_k Nothing -> failure "Kind mismatch in constructor application" [ " Type constructor: " ++ show con diff --git a/libraries/ghci/GHCi/TH/Binary.hs b/libraries/ghci/GHCi/TH/Binary.hs index e8a7a77..5e052f7 100644 --- a/libraries/ghci/GHCi/TH/Binary.hs +++ b/libraries/ghci/GHCi/TH/Binary.hs @@ -112,7 +112,7 @@ getTypeRepX = do 2 -> return $ TypeRepX (typeRep :: TypeRep (->)) 3 -> do con <- get :: Get TyCon TypeRepX rep_k <- getTypeRepX - case rep_k `eqTypeRep` (typeRep :: TypeRep Type) of + case typeRepKind rep_k `eqTypeRep` (typeRep :: TypeRep Type) of Just HRefl -> pure $ TypeRepX $ mkTrCon con rep_k Nothing -> failure "Kind mismatch" [ "Type constructor: " ++ show con From git at git.haskell.org Fri Jul 29 16:29:07 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 29 Jul 2016 16:29:07 +0000 (UTC) Subject: [commit: ghc] wip/ttypeable: Clarify comments (de38917) Message-ID: <20160729162907.6033E3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttypeable Link : http://ghc.haskell.org/trac/ghc/changeset/de38917d527202fa80306a42ebec0442ef746928/ghc >--------------------------------------------------------------- commit de38917d527202fa80306a42ebec0442ef746928 Author: Ben Gamari Date: Sun Jul 17 22:02:55 2016 +0200 Clarify comments >--------------------------------------------------------------- de38917d527202fa80306a42ebec0442ef746928 compiler/prelude/TysPrim.hs | 7 ++++--- compiler/typecheck/TcTypeable.hs | 4 ++-- 2 files changed, 6 insertions(+), 5 deletions(-) diff --git a/compiler/prelude/TysPrim.hs b/compiler/prelude/TysPrim.hs index 04a0677..47defa2 100644 --- a/compiler/prelude/TysPrim.hs +++ b/compiler/prelude/TysPrim.hs @@ -158,10 +158,11 @@ primTyCons ] -- | The names of the 'TyCon's which we define 'Typeable' bindings for --- explicitly in "Data.Typeable.Internal" --- and should not generate bindings for in "GHC.Types". +-- explicitly in "Data.Typeable.Internal" and should not generate representation +-- bindings for in "GHC.Types". -- --- See Note [Mutually recursive representations of primitive types] +-- See Note [Mutually recursive representations of primitive types] in +-- "Data.Typeable.Internal" and Note [Grand plan for Typeable] in "TcTypeable". primTypeableTyCons :: NameEnv TyConRepName primTypeableTyCons = mkNameEnv [ (tYPETyConName, trTYPEName) diff --git a/compiler/typecheck/TcTypeable.hs b/compiler/typecheck/TcTypeable.hs index 061d22f..0502f51 100644 --- a/compiler/typecheck/TcTypeable.hs +++ b/compiler/typecheck/TcTypeable.hs @@ -167,9 +167,9 @@ mkTypeableTyConBinds tycons ; gbl_env <- tcExtendGlobalValEnv tycon_rep_ids getGblEnv ; return (gbl_env `addTypecheckedBinds` tc_binds) } --- | Generate bindings for the type representation of a wired-in TyCon defined +-- | Generate bindings for the type representation of a wired-in 'TyCon's defined -- by the virtual "GHC.Prim" module. This is where we inject the representation --- bindings for primitive types into "GHC.Types" +-- bindings for these primitive types into "GHC.Types" -- -- See Note [Grand plan for Typeable] in this module. mkPrimTypeableBinds :: TcM TcGblEnv From git at git.haskell.org Fri Jul 29 16:29:10 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 29 Jul 2016 16:29:10 +0000 (UTC) Subject: [commit: ghc] wip/ttypeable: Binary: Simple serialization test works (7f51d71) Message-ID: <20160729162910.08C203A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttypeable Link : http://ghc.haskell.org/trac/ghc/changeset/7f51d7161c1021ab675f55c8bb2a8c050b30ea25/ghc >--------------------------------------------------------------- commit 7f51d7161c1021ab675f55c8bb2a8c050b30ea25 Author: Ben Gamari Date: Sun Jul 17 23:55:02 2016 +0200 Binary: Simple serialization test works >--------------------------------------------------------------- 7f51d7161c1021ab675f55c8bb2a8c050b30ea25 compiler/utils/Binary.hs | 9 ++++++--- libraries/ghci/GHCi/TH/Binary.hs | 9 ++++++--- 2 files changed, 12 insertions(+), 6 deletions(-) diff --git a/compiler/utils/Binary.hs b/compiler/utils/Binary.hs index 466e0eb..ea4219e 100644 --- a/compiler/utils/Binary.hs +++ b/compiler/utils/Binary.hs @@ -82,7 +82,7 @@ import Data.Time import Type.Reflection import Type.Reflection.Unsafe import Data.Kind (Type) -import GHC.Exts (RuntimeRep) +import GHC.Exts (TYPE, RuntimeRep) #else import Data.Typeable #endif @@ -580,11 +580,13 @@ instance Binary TyCon where #if MIN_VERSION_base(4,10,0) putTypeRep :: BinHandle -> TypeRep a -> IO () --- Special handling for Type, (->), and RuntimeRep due to recursive kind +-- Special handling for TYPE, (->), and RuntimeRep due to recursive kind -- relations. -- See Note [Mutually recursive representations of primitive types] putTypeRep bh rep | Just HRefl <- rep `eqTypeRep` (typeRep :: TypeRep Type) + = put_ bh (5 :: Word8) + | Just HRefl <- rep `eqTypeRep` (typeRep :: TypeRep TYPE) = put_ bh (0 :: Word8) | Just HRefl <- rep `eqTypeRep` (typeRep :: TypeRep RuntimeRep) = put_ bh (1 :: Word8) @@ -604,7 +606,8 @@ getTypeRepX :: BinHandle -> IO TypeRepX getTypeRepX bh = do tag <- get bh :: IO Word8 case tag of - 0 -> return $ TypeRepX (typeRep :: TypeRep Type) + 5 -> return $ TypeRepX (typeRep :: TypeRep Type) + 0 -> return $ TypeRepX (typeRep :: TypeRep TYPE) 1 -> return $ TypeRepX (typeRep :: TypeRep RuntimeRep) 2 -> return $ TypeRepX (typeRep :: TypeRep (->)) 3 -> do con <- get bh :: IO TyCon diff --git a/libraries/ghci/GHCi/TH/Binary.hs b/libraries/ghci/GHCi/TH/Binary.hs index 5e052f7..5710555 100644 --- a/libraries/ghci/GHCi/TH/Binary.hs +++ b/libraries/ghci/GHCi/TH/Binary.hs @@ -14,7 +14,7 @@ import qualified Data.ByteString as B import Type.Reflection import Type.Reflection.Unsafe import Data.Kind (Type) -import GHC.Exts (RuntimeRep) +import GHC.Exts (TYPE, RuntimeRep) #else import Data.Typeable #endif @@ -83,11 +83,13 @@ instance Binary TyCon where get = mkTyCon <$> get <*> get <*> get putTypeRep :: TypeRep a -> Put --- Special handling for Type, (->), and RuntimeRep due to recursive kind +-- Special handling for TYPE, (->), and RuntimeRep due to recursive kind -- relations. -- See Note [Mutually recursive representations of primitive types] putTypeRep rep | Just HRefl <- rep `eqTypeRep` (typeRep :: TypeRep Type) + = put (5 :: Word8) + | Just HRefl <- rep `eqTypeRep` (typeRep :: TypeRep TYPE) = put (0 :: Word8) | Just HRefl <- rep `eqTypeRep` (typeRep :: TypeRep RuntimeRep) = put (1 :: Word8) @@ -107,7 +109,8 @@ getTypeRepX :: Get TypeRepX getTypeRepX = do tag <- get :: Get Word8 case tag of - 0 -> return $ TypeRepX (typeRep :: TypeRep Type) + 5 -> return $ TypeRepX (typeRep :: TypeRep Type) + 0 -> return $ TypeRepX (typeRep :: TypeRep TYPE) 1 -> return $ TypeRepX (typeRep :: TypeRep RuntimeRep) 2 -> return $ TypeRepX (typeRep :: TypeRep (->)) 3 -> do con <- get :: Get TyCon From git at git.haskell.org Fri Jul 29 16:29:12 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 29 Jul 2016 16:29:12 +0000 (UTC) Subject: [commit: ghc] wip/ttypeable: Give unboxed tuples type representations (f248c70) Message-ID: <20160729162912.B5D573A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttypeable Link : http://ghc.haskell.org/trac/ghc/changeset/f248c7087fd378369608b04966fd9ac790bb76a9/ghc >--------------------------------------------------------------- commit f248c7087fd378369608b04966fd9ac790bb76a9 Author: Ben Gamari Date: Tue Jul 19 11:59:32 2016 +0200 Give unboxed tuples type representations This fixes #12409. Ultimately this was a bit of a toss-up between 1. keeping unboxed tuples unrepresentable and improving the error offered by the solver, and 2. allowing unboxed tuples to be representable Ultimately it seemed easier (and perhaps more useful) to do (2), so that's what this patch does. >--------------------------------------------------------------- f248c7087fd378369608b04966fd9ac790bb76a9 compiler/prelude/TysWiredIn.hs | 2 +- compiler/typecheck/TcTypeable.hs | 25 +++++++++++++++++++++---- compiler/types/TyCon.hs | 4 +++- 3 files changed, 25 insertions(+), 6 deletions(-) diff --git a/compiler/prelude/TysWiredIn.hs b/compiler/prelude/TysWiredIn.hs index 51f5555..556c1d2 100644 --- a/compiler/prelude/TysWiredIn.hs +++ b/compiler/prelude/TysWiredIn.hs @@ -771,7 +771,7 @@ mk_tuple Unboxed arity = (tycon, tuple_con) (\ks -> map tYPE ks) tc_res_kind = unboxedTupleKind tc_arity = arity * 2 - flavour = UnboxedAlgTyCon + flavour = UnboxedAlgTyCon (mkPrelTyConRepName tc_name) dc_tvs = binderVars tc_binders dc_arg_tys = mkTyVarTys (drop arity dc_tvs) diff --git a/compiler/typecheck/TcTypeable.hs b/compiler/typecheck/TcTypeable.hs index 0502f51..89d5586 100644 --- a/compiler/typecheck/TcTypeable.hs +++ b/compiler/typecheck/TcTypeable.hs @@ -14,6 +14,7 @@ import TcEnv import TcRnMonad import PrelNames import TysPrim ( primTyCons, primTypeableTyCons ) +import TysWiredIn ( tupleTyCon ) import Id import Type import TyCon @@ -25,6 +26,8 @@ import NameEnv import HsSyn import DynFlags import Bag +import BasicTypes ( Boxity(..) ) +import Constants ( mAX_TUPLE_SIZE ) import Fingerprint(Fingerprint(..), fingerprintString) import Outputable import FastString ( FastString, mkFastString ) @@ -197,6 +200,22 @@ mkPrimTypeableBinds } where +-- | This is the list of primitive 'TyCon's for which we must generate bindings +-- in "GHC.Types". This should include all types defined in "GHC.Prim". +-- +-- The majority of the types we need here are contained in 'primTyCons'. +-- However, not all of them: in particular unboxed tuples are absent since we +-- don't want to include them in the original name cache. See +-- Note [Built-in syntax and the OrigNameCache] in IfaceEnv for more. +ghcPrimTypeableTyCons :: [TyCon] +ghcPrimTypeableTyCons = filter (not . definedManually) $ concat + [ [funTyCon, tupleTyCon Unboxed 0] + , map (tupleTyCon Unboxed) [2..mAX_TUPLE_SIZE] + , primTyCons + ] + where + definedManually tc = tyConName tc `elemNameEnv` primTypeableTcCons + -- | Generate bindings for the type representation of the wired-in TyCons defined -- by the virtual "GHC.Prim" module. This differs from the usual -- @mkTypeableBinds@ path in that here we need to lie to 'mk_typeable_binds' @@ -209,10 +228,8 @@ ghcPrimTypeableBinds stuff = unionManyBags (map mkBind all_prim_tys) where all_prim_tys :: [TyCon] - all_prim_tys = [ tc' | tc <- funTyCon : primTyCons - , tc' <- tc : tyConATs tc - , not $ tyConName tc' `elemNameEnv` primTypeableTyCons - ] + all_prim_tys = [ tc' | tc <- ghcPrimTypeableTyCons + , tc' <- tc : tyConATs tc ] mkBind :: TyCon -> LHsBinds Id mkBind = mk_typeable_binds stuff diff --git a/compiler/types/TyCon.hs b/compiler/types/TyCon.hs index d825712..5869978 100644 --- a/compiler/types/TyCon.hs +++ b/compiler/types/TyCon.hs @@ -816,6 +816,7 @@ data AlgTyConFlav -- | An unboxed type constructor. Note that this carries no TyConRepName -- as it is not representable. | UnboxedAlgTyCon + TyConRepName -- | Type constructors representing a class dictionary. -- See Note [ATyCon for classes] in TyCoRep @@ -869,7 +870,7 @@ instance Outputable AlgTyConFlav where -- name, if any okParent :: Name -> AlgTyConFlav -> Bool okParent _ (VanillaAlgTyCon {}) = True -okParent _ (UnboxedAlgTyCon) = True +okParent _ (UnboxedAlgTyCon {}) = True okParent tc_name (ClassTyCon cls _) = tc_name == tyConName (classTyCon cls) okParent _ (DataFamInstTyCon _ fam_tc tys) = tyConArity fam_tc == length tys @@ -1079,6 +1080,7 @@ tyConRepName_maybe (PrimTyCon { primRepName = mb_rep_nm }) tyConRepName_maybe (AlgTyCon { algTcParent = parent }) | VanillaAlgTyCon rep_nm <- parent = Just rep_nm | ClassTyCon _ rep_nm <- parent = Just rep_nm + | UnboxedAlgTyCon rep_nm <- parent = Just rep_nm tyConRepName_maybe (FamilyTyCon { famTcFlav = DataFamilyTyCon rep_nm }) = Just rep_nm tyConRepName_maybe (PromotedDataCon { tcRepName = rep_nm }) From git at git.haskell.org Fri Jul 29 16:29:15 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 29 Jul 2016 16:29:15 +0000 (UTC) Subject: [commit: ghc] wip/ttypeable: testsuite/TypeRep: Add test for #12409 (ea5f19b) Message-ID: <20160729162915.62E5D3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttypeable Link : http://ghc.haskell.org/trac/ghc/changeset/ea5f19b01e9a91871a0ee7667fec4609e1a18b33/ghc >--------------------------------------------------------------- commit ea5f19b01e9a91871a0ee7667fec4609e1a18b33 Author: Ben Gamari Date: Tue Jul 19 10:57:48 2016 +0200 testsuite/TypeRep: Add test for #12409 >--------------------------------------------------------------- ea5f19b01e9a91871a0ee7667fec4609e1a18b33 testsuite/tests/typecheck/should_run/TypeRep.hs | 12 +++++++++++- 1 file changed, 11 insertions(+), 1 deletion(-) diff --git a/testsuite/tests/typecheck/should_run/TypeRep.hs b/testsuite/tests/typecheck/should_run/TypeRep.hs index 3ae9577..e466de5 100644 --- a/testsuite/tests/typecheck/should_run/TypeRep.hs +++ b/testsuite/tests/typecheck/should_run/TypeRep.hs @@ -1,5 +1,9 @@ {-# LANGUAGE DataKinds #-} +{-# LANGUAGE KindSignatures #-} +{-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE TypeInType #-} +{-# LANGUAGE UnboxedTuples #-} +{-# LANGUAGE MagicHash #-} {-# LANGUAGE TypeApplications #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE AllowAmbiguousTypes #-} @@ -30,6 +34,12 @@ main = do print $ rep @Bool print $ rep @Ordering print $ rep @(Int -> Int) + print $ rep @((Eq Int, Eq String) :: Constraint) + + -- Unboxed things (#12049) + print $ rep @Int# + print $ rep @(##) + print $ rep @(# Int#, Int #) -- Various instantiations of a kind-polymorphic type print $ rep @(Proxy (Eq Int)) @@ -45,4 +55,4 @@ main = do print $ rep @(Proxy 'PtrRepLifted) -- Something lifted and primitive - print $ rep @RealWorld + print $ rep @RealWorld -- #12132 From git at git.haskell.org Fri Jul 29 16:29:18 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 29 Jul 2016 16:29:18 +0000 (UTC) Subject: [commit: ghc] wip/ttypeable: testsuite: Add test of Typeable Binary instances (88ae3cd) Message-ID: <20160729162918.7DE303A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttypeable Link : http://ghc.haskell.org/trac/ghc/changeset/88ae3cda1d254522bc3767072e3f80d18a241fd0/ghc >--------------------------------------------------------------- commit 88ae3cda1d254522bc3767072e3f80d18a241fd0 Author: Ben Gamari Date: Fri Jul 22 13:13:36 2016 +0200 testsuite: Add test of Typeable Binary instances >--------------------------------------------------------------- 88ae3cda1d254522bc3767072e3f80d18a241fd0 .../typecheck/should_run/TestTypeableBinary.hs | 37 ++++++++++++++++++++++ .../typecheck/should_run/TestTypeableBinary.stdout | 15 +++++++++ testsuite/tests/typecheck/should_run/all.T | 1 + 3 files changed, 53 insertions(+) diff --git a/testsuite/tests/typecheck/should_run/TestTypeableBinary.hs b/testsuite/tests/typecheck/should_run/TestTypeableBinary.hs new file mode 100644 index 0000000..e427c13 --- /dev/null +++ b/testsuite/tests/typecheck/should_run/TestTypeableBinary.hs @@ -0,0 +1,37 @@ +{-# LANGUAGE MagicHash #-} +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE PolyKinds #-} + +import qualified Data.ByteString as BS +import Type.Reflection +import Data.Binary +import GHCi.TH.Binary () + +import GHC.Exts +import Data.Kind +import Data.Proxy + +testRoundtrip :: Typeable a => TypeRep a -> IO () +testRoundtrip rep + | rep /= rep' = putStrLn $ "bad: " ++ show rep ++ " /= " ++ show rep' + | otherwise = putStrLn $ "good: " ++ show rep + where + rep' = decode (encode rep) + +main :: IO () +main = do + testRoundtrip (typeRep :: TypeRep Int) + testRoundtrip (typeRep :: TypeRep Int#) + testRoundtrip (typeRep :: TypeRep IO) + testRoundtrip (typeRep :: TypeRep Maybe) + testRoundtrip (typeRep :: TypeRep TYPE) + testRoundtrip (typeRep :: TypeRep RuntimeRep) + testRoundtrip (typeRep :: TypeRep 'IntRep) + testRoundtrip (typeRep :: TypeRep (->)) + testRoundtrip (typeRep :: TypeRep (Proxy Int)) + testRoundtrip (typeRep :: TypeRep (Proxy Int#)) + testRoundtrip (typeRep :: TypeRep Type) + testRoundtrip (typeRep :: TypeRep (Int -> Int)) + testRoundtrip (typeRep :: TypeRep 5) + testRoundtrip (typeRep :: TypeRep "hello world") + testRoundtrip (typeRep :: TypeRep ('Just 5)) diff --git a/testsuite/tests/typecheck/should_run/TestTypeableBinary.stdout b/testsuite/tests/typecheck/should_run/TestTypeableBinary.stdout new file mode 100644 index 0000000..7e32096 --- /dev/null +++ b/testsuite/tests/typecheck/should_run/TestTypeableBinary.stdout @@ -0,0 +1,15 @@ +good: (Int) +good: Int# :: ((TYPE :: ((RuntimeRep) -> (*))) ('IntRep :: (RuntimeRep))) +good: IO :: ((*) -> (*)) +good: Maybe :: ((*) -> (*)) +good: TYPE :: ((RuntimeRep) -> (*)) +good: (RuntimeRep) +good: 'IntRep :: (RuntimeRep) +good: -> :: ((*) -> ((*) -> (*))) +good: ((Proxy :: ((*) -> (*))) (Int)) +good: ((Proxy :: (((TYPE :: ((RuntimeRep) -> (*))) ('IntRep :: (RuntimeRep))) -> (*))) (Int# :: ((TYPE :: ((RuntimeRep) -> (*))) ('IntRep :: (RuntimeRep))))) +good: (*) +good: ((Int) -> (Int)) +good: 5 :: (Nat) +good: "hello world" :: (Symbol) +good: ('Just :: ((Nat) -> ((Maybe :: ((*) -> (*))) (Nat)))) (5 :: (Nat)) :: ((Maybe :: ((*) -> (*))) (Nat)) diff --git a/testsuite/tests/typecheck/should_run/all.T b/testsuite/tests/typecheck/should_run/all.T index c2b277d..f51dbe3 100755 --- a/testsuite/tests/typecheck/should_run/all.T +++ b/testsuite/tests/typecheck/should_run/all.T @@ -117,3 +117,4 @@ test('TypeOf', normal, compile_and_run, ['']) test('TypeRep', normal, compile_and_run, ['']) test('T11120', normal, compile_and_run, ['']) test('KindInvariant', normal, ghci_script, ['KindInvariant.script']) +test('TestTypeableBinary', normal, compile_and_run, ['']) From git at git.haskell.org Fri Jul 29 16:29:21 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 29 Jul 2016 16:29:21 +0000 (UTC) Subject: [commit: ghc] wip/ttypeable: TcTypeable: Clarify comment (450f81b) Message-ID: <20160729162921.28C1F3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttypeable Link : http://ghc.haskell.org/trac/ghc/changeset/450f81b98a74331b19df3bc07666d60a23bad113/ghc >--------------------------------------------------------------- commit 450f81b98a74331b19df3bc07666d60a23bad113 Author: Ben Gamari Date: Fri Jul 22 13:16:05 2016 +0200 TcTypeable: Clarify comment >--------------------------------------------------------------- 450f81b98a74331b19df3bc07666d60a23bad113 compiler/typecheck/TcTypeable.hs | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/compiler/typecheck/TcTypeable.hs b/compiler/typecheck/TcTypeable.hs index 89d5586..a68d51c 100644 --- a/compiler/typecheck/TcTypeable.hs +++ b/compiler/typecheck/TcTypeable.hs @@ -214,7 +214,11 @@ ghcPrimTypeableTyCons = filter (not . definedManually) $ concat , primTyCons ] where - definedManually tc = tyConName tc `elemNameEnv` primTypeableTcCons + -- Some things, like TYPE, have mutually recursion kind relationships and + -- therefore have manually-defined representations. See Note [Mutually + -- recursive representations of primitive types] in Data.Typeable.Internal + -- and Note [Grand plan for Typeable] for details. + definedManually tc = tyConName tc `elemNameEnv` primTypeableTyCons -- | Generate bindings for the type representation of the wired-in TyCons defined -- by the virtual "GHC.Prim" module. This differs from the usual From git at git.haskell.org Fri Jul 29 16:29:23 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 29 Jul 2016 16:29:23 +0000 (UTC) Subject: [commit: ghc] wip/ttypeable: Update submodules (9813fca) Message-ID: <20160729162923.C8A4C3A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttypeable Link : http://ghc.haskell.org/trac/ghc/changeset/9813fca491168e993577869e95568027c97232fe/ghc >--------------------------------------------------------------- commit 9813fca491168e993577869e95568027c97232fe Author: Ben Gamari Date: Fri Jul 29 18:10:39 2016 +0200 Update submodules >--------------------------------------------------------------- 9813fca491168e993577869e95568027c97232fe libraries/array | 2 +- libraries/deepseq | 2 +- libraries/directory | 2 +- libraries/filepath | 2 +- libraries/haskeline | 2 +- libraries/hoopl | 2 +- libraries/hpc | 2 +- libraries/parallel | 2 +- libraries/process | 2 +- libraries/stm | 2 +- libraries/terminfo | 2 +- libraries/unix | 2 +- utils/haddock | 2 +- 13 files changed, 13 insertions(+), 13 deletions(-) diff --git a/libraries/array b/libraries/array index 6551ad9..776c11e 160000 --- a/libraries/array +++ b/libraries/array @@ -1 +1 @@ -Subproject commit 6551ad9edaca1634a8149ad9c27a72feb456d4e1 +Subproject commit 776c11e1da31d9433d309a507eeeb85f7b903028 diff --git a/libraries/deepseq b/libraries/deepseq index c3a0a16..161e313 160000 --- a/libraries/deepseq +++ b/libraries/deepseq @@ -1 +1 @@ -Subproject commit c3a0a16f17e593cb6a64b01a22015497738bfed6 +Subproject commit 161e313a0dbe3705992491aa948d1bb810c7fa5c diff --git a/libraries/directory b/libraries/directory index 33ce1ca..673ed69 160000 --- a/libraries/directory +++ b/libraries/directory @@ -1 +1 @@ -Subproject commit 33ce1ca6bef97b60957e4763b046eac9a982ead0 +Subproject commit 673ed6967fe2a55270fdba955379829c5df1f0a5 diff --git a/libraries/filepath b/libraries/filepath index f510e50..2055aff 160000 --- a/libraries/filepath +++ b/libraries/filepath @@ -1 +1 @@ -Subproject commit f510e50feefe9995334769dd5e26c79edbe6fdc1 +Subproject commit 2055aff234c47f6a6ea130436b86c1434cd03d50 diff --git a/libraries/haskeline b/libraries/haskeline index 8dd9e8b..006ab37 160000 --- a/libraries/haskeline +++ b/libraries/haskeline @@ -1 +1 @@ -Subproject commit 8dd9e8be13b364048f57cc276be6ad5fb66fad21 +Subproject commit 006ab377525b2bf3844fd1127bfe2df8a7af2e52 diff --git a/libraries/hoopl b/libraries/hoopl index b4477e8..c14a19e 160000 --- a/libraries/hoopl +++ b/libraries/hoopl @@ -1 +1 @@ -Subproject commit b4477e825a93373124ec5cf29b9850df9608f5bd +Subproject commit c14a19e866034f48fe3135dea82ccb0a8c0d7455 diff --git a/libraries/hpc b/libraries/hpc index 956887d..f5f2848 160000 --- a/libraries/hpc +++ b/libraries/hpc @@ -1 +1 @@ -Subproject commit 956887d4a15de3e68aae82b14bfa1630c8149649 +Subproject commit f5f28486446fdc691cfbb9c5611c0f78e8d010af diff --git a/libraries/parallel b/libraries/parallel index ec04d05..829ff3a 160000 --- a/libraries/parallel +++ b/libraries/parallel @@ -1 +1 @@ -Subproject commit ec04d059b13fc348789d87adfbabb9351f8574db +Subproject commit 829ff3ae248fe05b74bfea30e285dd0ff50424ea diff --git a/libraries/process b/libraries/process index 296cbce..a97ddce 160000 --- a/libraries/process +++ b/libraries/process @@ -1 +1 @@ -Subproject commit 296cbce6294316d6534b4449fc7ab0f0d3f5775b +Subproject commit a97ddce1a61d53e498addbbec10a694f31aa48b2 diff --git a/libraries/stm b/libraries/stm index fe88993..f549f65 160000 --- a/libraries/stm +++ b/libraries/stm @@ -1 +1 @@ -Subproject commit fe8899331e6ca7bdf80d57cf77dd597023ae4718 +Subproject commit f549f65a2fcc85b7ff8648bed2543e8b192ea27d diff --git a/libraries/terminfo b/libraries/terminfo index 140ca44..d9c6c52 160000 --- a/libraries/terminfo +++ b/libraries/terminfo @@ -1 +1 @@ -Subproject commit 140ca44db6fc734cfc0388e82f9e5270f31475d8 +Subproject commit d9c6c5257bf392fb4bca92ad0777a719b57a2794 diff --git a/libraries/unix b/libraries/unix index 40820da..f64a5a1 160000 --- a/libraries/unix +++ b/libraries/unix @@ -1 +1 @@ -Subproject commit 40820da5fb35c53aed53c211277c3e6077c1ddf9 +Subproject commit f64a5a190daf45fb26f09ae6fabb37a623923814 diff --git a/utils/haddock b/utils/haddock index 008e61d..d90131f 160000 --- a/utils/haddock +++ b/utils/haddock @@ -1 +1 @@ -Subproject commit 008e61d0c4b10713751c2a1de4958acc75367396 +Subproject commit d90131fb6d05ad67f3152994376e6fae2d4f8671 From git at git.haskell.org Fri Jul 29 16:29:26 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 29 Jul 2016 16:29:26 +0000 (UTC) Subject: [commit: ghc] wip/ttypeable: Temporarily override submodule upstream repo paths (5741ba5) Message-ID: <20160729162926.780053A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/ttypeable Link : http://ghc.haskell.org/trac/ghc/changeset/5741ba53f9e4663b2d8cac9218ccda69fc04f72c/ghc >--------------------------------------------------------------- commit 5741ba53f9e4663b2d8cac9218ccda69fc04f72c Author: Ben Gamari Date: Fri Jul 29 18:24:26 2016 +0200 Temporarily override submodule upstream repo paths >--------------------------------------------------------------- 5741ba53f9e4663b2d8cac9218ccda69fc04f72c .gitmodules | 26 +++++++++++++------------- 1 file changed, 13 insertions(+), 13 deletions(-) diff --git a/.gitmodules b/.gitmodules index 783c568..d2eda81 100644 --- a/.gitmodules +++ b/.gitmodules @@ -16,7 +16,7 @@ ignore = untracked [submodule "libraries/haskeline"] path = libraries/haskeline - url = ../packages/haskeline.git + url = git://github.com/bgamari/haskeline ignore = untracked [submodule "libraries/pretty"] path = libraries/pretty @@ -24,7 +24,7 @@ ignore = untracked [submodule "libraries/terminfo"] path = libraries/terminfo - url = ../packages/terminfo.git + url = git://github.com/bgamari/packages-terminfo ignore = untracked [submodule "libraries/transformers"] path = libraries/transformers @@ -56,43 +56,43 @@ ignore = untracked [submodule "libraries/array"] path = libraries/array - url = ../packages/array.git + url = git://github.com/bgamari/array ignore = none [submodule "libraries/deepseq"] path = libraries/deepseq - url = ../packages/deepseq.git + url = git://github.com/bgamari/deepseq ignore = none [submodule "libraries/directory"] path = libraries/directory - url = ../packages/directory.git + url = git://github.com/bgamari/directory ignore = none [submodule "libraries/filepath"] path = libraries/filepath - url = ../packages/filepath.git + url = git://github.com/bgamari/filepath ignore = none [submodule "libraries/hoopl"] path = libraries/hoopl - url = ../packages/hoopl.git + url = git://github.com/bgamari/hoopl ignore = none [submodule "libraries/hpc"] path = libraries/hpc - url = ../packages/hpc.git + url = git://github.com/bgamari/hpc ignore = none [submodule "libraries/process"] path = libraries/process - url = ../packages/process.git + url = git://github.com/bgamari/process ignore = none [submodule "libraries/unix"] path = libraries/unix - url = ../packages/unix.git + url = git://github.com/bgamari/unix ignore = none [submodule "libraries/parallel"] path = libraries/parallel - url = ../packages/parallel.git + url = git://github.com/bgamari/parallel ignore = none [submodule "libraries/stm"] path = libraries/stm - url = ../packages/stm.git + url = git://github.com/bgamari/packages-stm ignore = none [submodule "libraries/dph"] path = libraries/dph @@ -100,7 +100,7 @@ ignore = none [submodule "utils/haddock"] path = utils/haddock - url = ../haddock.git + url = git://github.com/bgamari/haddock ignore = none branch = ghc-head [submodule "nofib"] From git at git.haskell.org Sat Jul 30 07:24:40 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 30 Jul 2016 07:24:40 +0000 (UTC) Subject: [commit: ghc] master: Add atomic operations to package.conf.in (c06e3f4) Message-ID: <20160730072440.73A683A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c06e3f46d24ef69f3a3d794f5f604cb8c2a40cbc/ghc >--------------------------------------------------------------- commit c06e3f46d24ef69f3a3d794f5f604cb8c2a40cbc Author: alexbiehl Date: Sat Jul 30 17:22:54 2016 +1000 Add atomic operations to package.conf.in This patch resulted from the discussion in D2431 and should be merged first. @erikd and @trommler reported errors like ``` /home/erikd/Git/ghc-upstream/rts/dist/build/libHSrts_thr.a(PrimOps.thr_o ): In function `c14_info': (.text+0x2b8): undefined reference to `hs_cmpxchg32' /home/erikd/Git/ghc-upstream/rts/dist/build/libHSrts_thr.a(PrimOps.thr_o ): In function `c5e_info': (.text+0xac4): undefined reference to `hs_cmpxchg32' /home/erikd/Git/ghc-upstream/rts/dist/build/libHSrts_thr.a(PrimOps.thr_o ): In function `c8b_info': (.text+0x1198): undefined reference to `hs_cmpxchg32' /home/erikd/Git/ghc-upstream/rts/dist/build/libHSrts_thr.a(PrimOps.thr_o ): In function `c8b_info': (.text+0x122c): undefined reference to `hs_cmpxchg32' /home/erikd/Git/ghc-upstream/rts/dist/build/libHSrts_thr.a(PrimOps.thr_o ): In function `c8b_info': (.text+0x12ec): undefined reference to `hs_cmpxchg32' ``` on PowerPC. @simonmar suggests to add the specific exports to `rts/package.conf.in`. This patch does exactly that, including all other atomic ops as they probably (maybe someone can verify?) suffer from the same problem on PPC. Test Plan: Please make sure to build on PPC. Reviewers: erikd, austin, bgamari, simonmar, trommler Reviewed By: erikd, trommler Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2435 >--------------------------------------------------------------- c06e3f46d24ef69f3a3d794f5f604cb8c2a40cbc rts/package.conf.in | 108 ++++++++++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 108 insertions(+) diff --git a/rts/package.conf.in b/rts/package.conf.in index d2b728e..65aa5c3 100644 --- a/rts/package.conf.in +++ b/rts/package.conf.in @@ -122,6 +122,60 @@ ld-options: , "-Wl,-u,_base_GHCziConcziIO_ioManagerCapabilitiesChanged_closure" , "-Wl,-u,_base_GHCziConcziSync_runSparks_closure" , "-Wl,-u,_base_GHCziConcziSignal_runHandlersPtr_closure" + , "-Wl,-u,_hs_atomic_add8" + , "-Wl,-u,_hs_atomic_add16" + , "-Wl,-u,_hs_atomic_add32" +#if WORD_SIZE_IN_BITS == 64 + , "-Wl,-u,_hs_atomic_add64" +#endif + , "-Wl,-u,_hs_atomic_sub8" + , "-Wl,-u,_hs_atomic_sub16" + , "-Wl,-u,_hs_atomic_sub32" +#if WORD_SIZE_IN_BITS == 64 + , "-Wl,-u,_hs_atomic_sub64" +#endif + , "-Wl,-u,_hs_atomic_and8" + , "-Wl,-u,_hs_atomic_and16" + , "-Wl,-u,_hs_atomic_and32" +#if WORD_SIZE_IN_BITS == 64 + , "-Wl,-u,_hs_atomic_and64" +#endif + , "-Wl,-u,_hs_atomic_nand8" + , "-Wl,-u,_hs_atomic_nand16" + , "-Wl,-u,_hs_atomic_nand32" +#if WORD_SIZE_IN_BITS == 64 + , "-Wl,-u,_hs_atomic_nand64" +#endif + , "-Wl,-u,_hs_atomic_or8" + , "-Wl,-u,_hs_atomic_or16" + , "-Wl,-u,_hs_atomic_or32" +#if WORD_SIZE_IN_BITS == 64 + , "-Wl,-u,_hs_atomic_or64" +#endif + , "-Wl,-u,_hs_atomic_xor8" + , "-Wl,-u,_hs_atomic_xor16" + , "-Wl,-u,_hs_atomic_xor32" +#if WORD_SIZE_IN_BITS == 64 + , "-Wl,-u,_hs_atomic_xor64" +#endif + , "-Wl,-u,_hs_cmpxchg8" + , "-Wl,-u,_hs_cmpxchg16" + , "-Wl,-u,_hs_cmpxchg32" +#if WORD_SIZE_IN_BITS == 64 + , "-Wl,-u,_hs_cmpxchg64" +#endif + , "-Wl,-u,_hs_atomicread8" + , "-Wl,-u,_hs_atomicread16" + , "-Wl,-u,_hs_atomicread32" +#if WORD_SIZE_IN_BITS == 64 + , "-Wl,-u,_hs_atomicread64" +#endif + , "-Wl,-u,_hs_atomicwrite8" + , "-Wl,-u,_hs_atomicwrite16" + , "-Wl,-u,_hs_atomicwrite32" +#if WORD_SIZE_IN_BITS == 64 + , "-Wl,-u,_hs_atomicwrite64" +#endif #else "-Wl,-u,ghczmprim_GHCziTypes_Izh_static_info" , "-Wl,-u,ghczmprim_GHCziTypes_Czh_static_info" @@ -164,6 +218,60 @@ ld-options: , "-Wl,-u,base_GHCziConcziIO_ioManagerCapabilitiesChanged_closure" , "-Wl,-u,base_GHCziConcziSync_runSparks_closure" , "-Wl,-u,base_GHCziConcziSignal_runHandlersPtr_closure" + , "-Wl,-u,hs_atomic_add8" + , "-Wl,-u,hs_atomic_add16" + , "-Wl,-u,hs_atomic_add32" +#if WORD_SIZE_IN_BITS == 64 + , "-Wl,-u,hs_atomic_add64" +#endif + , "-Wl,-u,hs_atomic_sub8" + , "-Wl,-u,hs_atomic_sub16" + , "-Wl,-u,hs_atomic_sub32" +#if WORD_SIZE_IN_BITS == 64 + , "-Wl,-u,hs_atomic_sub64" +#endif + , "-Wl,-u,hs_atomic_and8" + , "-Wl,-u,hs_atomic_and16" + , "-Wl,-u,hs_atomic_and32" +#if WORD_SIZE_IN_BITS == 64 + , "-Wl,-u,hs_atomic_and64" +#endif + , "-Wl,-u,hs_atomic_nand8" + , "-Wl,-u,hs_atomic_nand16" + , "-Wl,-u,hs_atomic_nand32" +#if WORD_SIZE_IN_BITS == 64 + , "-Wl,-u,hs_atomic_nand64" +#endif + , "-Wl,-u,hs_atomic_or8" + , "-Wl,-u,hs_atomic_or16" + , "-Wl,-u,hs_atomic_or32" +#if WORD_SIZE_IN_BITS == 64 + , "-Wl,-u,hs_atomic_or64" +#endif + , "-Wl,-u,hs_atomic_xor8" + , "-Wl,-u,hs_atomic_xor16" + , "-Wl,-u,hs_atomic_xor32" +#if WORD_SIZE_IN_BITS == 64 + , "-Wl,-u,hs_atomic_xor64" +#endif + , "-Wl,-u,hs_cmpxchg8" + , "-Wl,-u,hs_cmpxchg16" + , "-Wl,-u,hs_cmpxchg32" +#if WORD_SIZE_IN_BITS == 64 + , "-Wl,-u,hs_cmpxchg64" +#endif + , "-Wl,-u,hs_atomicread8" + , "-Wl,-u,hs_atomicread16" + , "-Wl,-u,hs_atomicread32" +#if WORD_SIZE_IN_BITS == 64 + , "-Wl,-u,hs_atomicread64" +#endif + , "-Wl,-u,hs_atomicwrite8" + , "-Wl,-u,hs_atomicwrite16" + , "-Wl,-u,hs_atomicwrite32" +#if WORD_SIZE_IN_BITS == 64 + , "-Wl,-u,hs_atomicwrite64" +#endif #endif /* Pick up static libraries in preference over dynamic if in earlier search From git at git.haskell.org Sat Jul 30 09:46:54 2016 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 30 Jul 2016 09:46:54 +0000 (UTC) Subject: [commit: ghc] wip/12368: dmdFix: Ensure that top-level binds are processes at least twice (b0b2f56) Message-ID: <20160730094654.BA0C63A300@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/12368 Link : http://ghc.haskell.org/trac/ghc/changeset/b0b2f56e7e29024afeaa6e633c0de208fc6552c2/ghc >--------------------------------------------------------------- commit b0b2f56e7e29024afeaa6e633c0de208fc6552c2 Author: Joachim Breitner Date: Sat Jul 30 05:46:06 2016 -0400 dmdFix: Ensure that top-level binds are processes at least twice even if we abort the iteration. I’m not sure if this is the final code I want to submit, but I’m pushing this onto a branch to see if it validates. >--------------------------------------------------------------- b0b2f56e7e29024afeaa6e633c0de208fc6552c2 compiler/stranal/DmdAnal.hs | 10 +++++++++- 1 file changed, 9 insertions(+), 1 deletion(-) diff --git a/compiler/stranal/DmdAnal.hs b/compiler/stranal/DmdAnal.hs index 22e1faa..9bdc233 100644 --- a/compiler/stranal/DmdAnal.hs +++ b/compiler/stranal/DmdAnal.hs @@ -496,12 +496,20 @@ dmdFix top_lvl env orig_pairs -- See Note [Safe abortion in the fixed-point iteration] abort :: (AnalEnv, DmdEnv, [(Id,CoreExpr)]) abort = (env, lazy_fv', zapped_pairs) - where (lazy_fv, pairs') = step True (zapIdStrictness orig_pairs) + where (lazy_fv, pairs') = abortingStep orig_pairs -- Note [Lazy and unleasheable free variables] non_lazy_fvs = plusVarEnvList $ map (strictSigDmdEnv . idStrictness . fst) pairs' lazy_fv' = lazy_fv `plusVarEnv` mapVarEnv (const topDmd) non_lazy_fvs zapped_pairs = zapIdStrictness pairs' + -- We always need two passes over everything. If this is top-level, then + -- dmdFix is required to do at least two passes. + abortingStep :: [(Id, CoreExpr)] -> (DmdEnv, [(Id, CoreExpr)]) + abortingStep pairs0 | isTopLevel top_lvl = + let (_, pairs1) = step True (zapIdStrictness pairs0) + in step False (zapIdStrictness pairs1) + abortingStep pairs0 = step True (zapIdStrictness pairs0) + -- The fixed-point varies the idStrictness field of the binders, and terminates if that -- annotation does not change any more. loop :: Int -> [(Id,CoreExpr)] -> (AnalEnv, DmdEnv, [(Id,CoreExpr)])