From git at git.haskell.org Sun Dec 1 10:07:17 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 1 Dec 2013 10:07:17 +0000 (UTC) Subject: [commit: ghc] master: Fix loopification with profiling and enable it by default (#8275) (adb9964) Message-ID: <20131201100717.2DCF82406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/adb9964e2f97338501411282c0bb6a9f47a56b1b/ghc >--------------------------------------------------------------- commit adb9964e2f97338501411282c0bb6a9f47a56b1b Author: Patrick Palka Date: Fri Nov 29 13:40:42 2013 -0500 Fix loopification with profiling and enable it by default (#8275) >--------------------------------------------------------------- adb9964e2f97338501411282c0bb6a9f47a56b1b compiler/codeGen/StgCmmBind.hs | 6 ++---- compiler/main/DynFlags.hs | 1 + 2 files changed, 3 insertions(+), 4 deletions(-) diff --git a/compiler/codeGen/StgCmmBind.hs b/compiler/codeGen/StgCmmBind.hs index 4762c5a..16477c8 100644 --- a/compiler/codeGen/StgCmmBind.hs +++ b/compiler/codeGen/StgCmmBind.hs @@ -31,7 +31,6 @@ import StgCmmForeign (emitPrimCall) import MkGraph import CoreSyn ( AltCon(..) ) import SMRep -import BlockId import Cmm import CmmInfo import CmmUtils @@ -481,8 +480,7 @@ closureCodeBody top_lvl bndr cl_info cc args arity body fv_details -- Emit new label that might potentially be a header -- of a self-recursive tail call. See Note -- [Self-recursive tail calls] in StgCmmExpr - ; u <- newUnique - ; let loop_header_id = mkBlockId u + ; loop_header_id <- newLabelC ; emitLabel loop_header_id -- Extend reader monad with information that -- self-recursive tail calls can be optimized into local @@ -495,7 +493,7 @@ closureCodeBody top_lvl bndr cl_info cc args arity body fv_details tickyEnterFun cl_info ; enterCostCentreFun cc (CmmMachOp (mo_wordSub dflags) - [ CmmReg nodeReg + [ CmmReg (CmmLocal node) -- not nodeReg, see #8275 , mkIntExpr dflags (funTag dflags cl_info) ]) ; fv_bindings <- mapM bind_fv fv_details -- Load free vars out of closure *after* diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index 7c07a36..05a72d6 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -2957,6 +2957,7 @@ optLevelFlags , ([0,1,2], Opt_LlvmTBAA) , ([1,2], Opt_CmmSink) , ([1,2], Opt_CmmElimCommonBlocks) + , ([1,2], Opt_Loopification) , ([0,1,2], Opt_DmdTxDictSel) From git at git.haskell.org Sun Dec 1 10:29:10 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 1 Dec 2013 10:29:10 +0000 (UTC) Subject: [commit: ghc] master: Document solution to #8275 (6d24076) Message-ID: <20131201102911.614FF2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6d24076be9aff562cd449aa1d39b8eb14638bcd6/ghc >--------------------------------------------------------------- commit 6d24076be9aff562cd449aa1d39b8eb14638bcd6 Author: Jan Stolarek Date: Sun Dec 1 11:28:50 2013 +0100 Document solution to #8275 >--------------------------------------------------------------- 6d24076be9aff562cd449aa1d39b8eb14638bcd6 compiler/codeGen/StgCmmBind.hs | 15 +++++++++++++-- 1 file changed, 13 insertions(+), 2 deletions(-) diff --git a/compiler/codeGen/StgCmmBind.hs b/compiler/codeGen/StgCmmBind.hs index 16477c8..11b411d 100644 --- a/compiler/codeGen/StgCmmBind.hs +++ b/compiler/codeGen/StgCmmBind.hs @@ -493,7 +493,7 @@ closureCodeBody top_lvl bndr cl_info cc args arity body fv_details tickyEnterFun cl_info ; enterCostCentreFun cc (CmmMachOp (mo_wordSub dflags) - [ CmmReg (CmmLocal node) -- not nodeReg, see #8275 + [ CmmReg (CmmLocal node) -- See [NodeReg clobbered with loopification] , mkIntExpr dflags (funTag dflags cl_info) ]) ; fv_bindings <- mapM bind_fv fv_details -- Load free vars out of closure *after* @@ -504,6 +504,18 @@ closureCodeBody top_lvl bndr cl_info cc args arity body fv_details } +-- Note [NodeReg clobbered with loopification] +-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +-- +-- Previously we used to pass nodeReg (aka R1) here. With profiling, upon +-- entering a closure, enterFunCCS was called with R1 passed to it. But since R1 +-- may get clobbered inside the body of a closure, and since a self-recursive +-- tail call does not restore R1, a subsequent call to enterFunCCS received a +-- possibly bogus value from R1. The solution is to not pass nodeReg (aka R1) to +-- enterFunCCS. Instead, we pass node, the callee-saved temporary that stores +-- the original value of R1. This way R1 may get modified but loopification will +-- not care. + -- A function closure pointer may be tagged, so we -- must take it into account when accessing the free variables. bind_fv :: (NonVoid Id, VirtualHpOffset) -> FCode (LocalReg, WordOff) @@ -780,4 +792,3 @@ closureDescription dflags mod_name name else pprModule mod_name <> char '.' <> ppr name) <> char '>') -- showSDocDump, because we want to see the unique on the Name. - From git at git.haskell.org Sun Dec 1 22:48:10 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 1 Dec 2013 22:48:10 +0000 (UTC) Subject: [commit: ghc] master: Don't explicitly refer to nodeReg in ldvEnterClosure (6178f6e) Message-ID: <20131201224810.D4EB82406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6178f6e162a3a2f2e9f7103d7ca94bbed16b39ec/ghc >--------------------------------------------------------------- commit 6178f6e162a3a2f2e9f7103d7ca94bbed16b39ec Author: Patrick Palka Date: Sun Dec 1 12:44:14 2013 -0500 Don't explicitly refer to nodeReg in ldvEnterClosure >--------------------------------------------------------------- 6178f6e162a3a2f2e9f7103d7ca94bbed16b39ec compiler/codeGen/StgCmmBind.hs | 4 ++-- compiler/codeGen/StgCmmProf.hs | 11 ++++++----- 2 files changed, 8 insertions(+), 7 deletions(-) diff --git a/compiler/codeGen/StgCmmBind.hs b/compiler/codeGen/StgCmmBind.hs index 11b411d..41e549e 100644 --- a/compiler/codeGen/StgCmmBind.hs +++ b/compiler/codeGen/StgCmmBind.hs @@ -476,7 +476,7 @@ closureCodeBody top_lvl bndr cl_info cc args arity body fv_details ; dflags <- getDynFlags ; let node_points = nodeMustPointToIt dflags lf_info node' = if node_points then Just node else Nothing - ; when node_points (ldvEnterClosure cl_info) + ; when node_points (ldvEnterClosure cl_info (CmmLocal node)) -- Emit new label that might potentially be a header -- of a self-recursive tail call. See Note -- [Self-recursive tail calls] in StgCmmExpr @@ -561,7 +561,7 @@ thunkCode cl_info fv_details _cc node arity body = do { dflags <- getDynFlags ; let node_points = nodeMustPointToIt dflags (closureLFInfo cl_info) node' = if node_points then Just node else Nothing - ; ldvEnterClosure cl_info -- NB: Node always points when profiling + ; ldvEnterClosure cl_info (CmmLocal node) -- NB: Node always points when profiling -- Heap overflow check ; entryHeapCheck cl_info node' arity [] $ do diff --git a/compiler/codeGen/StgCmmProf.hs b/compiler/codeGen/StgCmmProf.hs index 5044d76..e8a2a10 100644 --- a/compiler/codeGen/StgCmmProf.hs +++ b/compiler/codeGen/StgCmmProf.hs @@ -328,11 +328,12 @@ ldvRecordCreate closure = do dflags <- getDynFlags -- The closure is not IND or IND_OLDGEN because neither is considered for LDV -- profiling. -- -ldvEnterClosure :: ClosureInfo -> FCode () -ldvEnterClosure closure_info = do dflags <- getDynFlags - let tag = funTag dflags closure_info - ldvEnter (cmmOffsetB dflags (CmmReg nodeReg) (-tag)) - -- don't forget to substract node's tag +ldvEnterClosure :: ClosureInfo -> CmmReg -> FCode () +ldvEnterClosure closure_info node_reg = do + dflags <- getDynFlags + let tag = funTag dflags closure_info + -- don't forget to substract node's tag + ldvEnter (cmmOffsetB dflags (CmmReg node_reg) (-tag)) ldvEnter :: CmmExpr -> FCode () -- Argument is a closure pointer From git at git.haskell.org Sun Dec 1 22:48:12 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 1 Dec 2013 22:48:12 +0000 (UTC) Subject: [commit: ghc] master: Move the LDV code below the self-loop label (#8275) (ac31b79) Message-ID: <20131201224812.EB3782406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ac31b79924e9330c577ea63af9b0f10f4fc6c8f6/ghc >--------------------------------------------------------------- commit ac31b79924e9330c577ea63af9b0f10f4fc6c8f6 Author: Patrick Palka Date: Sun Dec 1 12:47:33 2013 -0500 Move the LDV code below the self-loop label (#8275) >--------------------------------------------------------------- ac31b79924e9330c577ea63af9b0f10f4fc6c8f6 compiler/codeGen/StgCmmBind.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/codeGen/StgCmmBind.hs b/compiler/codeGen/StgCmmBind.hs index 41e549e..64772c6 100644 --- a/compiler/codeGen/StgCmmBind.hs +++ b/compiler/codeGen/StgCmmBind.hs @@ -476,12 +476,12 @@ closureCodeBody top_lvl bndr cl_info cc args arity body fv_details ; dflags <- getDynFlags ; let node_points = nodeMustPointToIt dflags lf_info node' = if node_points then Just node else Nothing - ; when node_points (ldvEnterClosure cl_info (CmmLocal node)) -- Emit new label that might potentially be a header -- of a self-recursive tail call. See Note -- [Self-recursive tail calls] in StgCmmExpr ; loop_header_id <- newLabelC ; emitLabel loop_header_id + ; when node_points (ldvEnterClosure cl_info (CmmLocal node)) -- Extend reader monad with information that -- self-recursive tail calls can be optimized into local -- jumps From git at git.haskell.org Mon Dec 2 02:39:14 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Dec 2013 02:39:14 +0000 (UTC) Subject: [commit: ghc] master: Respect the ordering of -package directives (574ccfa) Message-ID: <20131202023914.B5A612406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/574ccfa231ca05d03d1da9d31e5bc81e74cc5e1e/ghc >--------------------------------------------------------------- commit 574ccfa231ca05d03d1da9d31e5bc81e74cc5e1e Author: Patrick Palka Date: Tue Nov 26 11:46:59 2013 -0500 Respect the ordering of -package directives >--------------------------------------------------------------- 574ccfa231ca05d03d1da9d31e5bc81e74cc5e1e compiler/main/Packages.lhs | 15 ++++++++------- 1 file changed, 8 insertions(+), 7 deletions(-) diff --git a/compiler/main/Packages.lhs b/compiler/main/Packages.lhs index aefb536..df5eddb 100644 --- a/compiler/main/Packages.lhs +++ b/compiler/main/Packages.lhs @@ -59,6 +59,7 @@ import System.FilePath as FilePath import qualified System.FilePath.Posix as FilePath.Posix import Control.Monad import Data.Char (isSpace) +import Data.Foldable (foldrM) import Data.List as List import Data.Map (Map) import qualified Data.Map as Map @@ -980,7 +981,7 @@ getPreloadPackagesAnd dflags pkgids = preload = preloadPackages state pairs = zip pkgids (repeat Nothing) in do - all_pkgs <- throwErr dflags (foldM (add_package pkg_map ipid_map) preload pairs) + all_pkgs <- throwErr dflags (foldrM (add_package pkg_map ipid_map) preload pairs) return (map (getPackageDetails state) all_pkgs) -- Takes a list of packages, and returns the list with dependencies included, @@ -1003,15 +1004,15 @@ closeDepsErr :: PackageConfigMap -> Map InstalledPackageId PackageId -> [(PackageId,Maybe PackageId)] -> MaybeErr MsgDoc [PackageId] -closeDepsErr pkg_map ipid_map ps = foldM (add_package pkg_map ipid_map) [] ps +closeDepsErr pkg_map ipid_map ps = foldrM (add_package pkg_map ipid_map) [] ps -- internal helper add_package :: PackageConfigMap -> Map InstalledPackageId PackageId - -> [PackageId] -> (PackageId,Maybe PackageId) + -> [PackageId] -> MaybeErr MsgDoc [PackageId] -add_package pkg_db ipid_map ps (p, mb_parent) +add_package pkg_db ipid_map (p, mb_parent) ps | p `elem` ps = return ps -- Check if we've already added this package | otherwise = case lookupPackage pkg_db p of @@ -1019,12 +1020,12 @@ add_package pkg_db ipid_map ps (p, mb_parent) missingDependencyMsg mb_parent) Just pkg -> do -- Add the package's dependents also - ps' <- foldM add_package_ipid ps (depends pkg) + ps' <- foldrM add_package_ipid ps (depends pkg) return (p : ps') where - add_package_ipid ps ipid@(InstalledPackageId str) + add_package_ipid ipid@(InstalledPackageId str) ps | Just pid <- Map.lookup ipid ipid_map - = add_package pkg_db ipid_map ps (pid, Just p) + = add_package pkg_db ipid_map (pid, Just p) ps | otherwise = Failed (missingPackageMsg str <> missingDependencyMsg mb_parent) From git at git.haskell.org Mon Dec 2 02:39:16 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Dec 2013 02:39:16 +0000 (UTC) Subject: [commit: ghc] master: Revert "Respect the ordering of -package directives" (fac831f) Message-ID: <20131202023916.C94CE2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/fac831fd1377bcce5ef7513ab35a83661877f14c/ghc >--------------------------------------------------------------- commit fac831fd1377bcce5ef7513ab35a83661877f14c Author: Patrick Palka Date: Sun Dec 1 21:37:32 2013 -0500 Revert "Respect the ordering of -package directives" This commit was accidentally pushed. This reverts commit 574ccfa231ca05d03d1da9d31e5bc81e74cc5e1e. >--------------------------------------------------------------- fac831fd1377bcce5ef7513ab35a83661877f14c compiler/main/Packages.lhs | 15 +++++++-------- 1 file changed, 7 insertions(+), 8 deletions(-) diff --git a/compiler/main/Packages.lhs b/compiler/main/Packages.lhs index df5eddb..aefb536 100644 --- a/compiler/main/Packages.lhs +++ b/compiler/main/Packages.lhs @@ -59,7 +59,6 @@ import System.FilePath as FilePath import qualified System.FilePath.Posix as FilePath.Posix import Control.Monad import Data.Char (isSpace) -import Data.Foldable (foldrM) import Data.List as List import Data.Map (Map) import qualified Data.Map as Map @@ -981,7 +980,7 @@ getPreloadPackagesAnd dflags pkgids = preload = preloadPackages state pairs = zip pkgids (repeat Nothing) in do - all_pkgs <- throwErr dflags (foldrM (add_package pkg_map ipid_map) preload pairs) + all_pkgs <- throwErr dflags (foldM (add_package pkg_map ipid_map) preload pairs) return (map (getPackageDetails state) all_pkgs) -- Takes a list of packages, and returns the list with dependencies included, @@ -1004,15 +1003,15 @@ closeDepsErr :: PackageConfigMap -> Map InstalledPackageId PackageId -> [(PackageId,Maybe PackageId)] -> MaybeErr MsgDoc [PackageId] -closeDepsErr pkg_map ipid_map ps = foldrM (add_package pkg_map ipid_map) [] ps +closeDepsErr pkg_map ipid_map ps = foldM (add_package pkg_map ipid_map) [] ps -- internal helper add_package :: PackageConfigMap -> Map InstalledPackageId PackageId - -> (PackageId,Maybe PackageId) -> [PackageId] + -> (PackageId,Maybe PackageId) -> MaybeErr MsgDoc [PackageId] -add_package pkg_db ipid_map (p, mb_parent) ps +add_package pkg_db ipid_map ps (p, mb_parent) | p `elem` ps = return ps -- Check if we've already added this package | otherwise = case lookupPackage pkg_db p of @@ -1020,12 +1019,12 @@ add_package pkg_db ipid_map (p, mb_parent) ps missingDependencyMsg mb_parent) Just pkg -> do -- Add the package's dependents also - ps' <- foldrM add_package_ipid ps (depends pkg) + ps' <- foldM add_package_ipid ps (depends pkg) return (p : ps') where - add_package_ipid ipid@(InstalledPackageId str) ps + add_package_ipid ps ipid@(InstalledPackageId str) | Just pid <- Map.lookup ipid ipid_map - = add_package pkg_db ipid_map (pid, Just p) ps + = add_package pkg_db ipid_map ps (pid, Just p) | otherwise = Failed (missingPackageMsg str <> missingDependencyMsg mb_parent) From simonpj at microsoft.com Mon Dec 2 10:28:29 2013 From: simonpj at microsoft.com (Simon Peyton-Jones) Date: Mon, 2 Dec 2013 10:28:29 +0000 Subject: [commit: ghc] master: Respect the ordering of -package directives (574ccfa) In-Reply-To: <20131202023914.B5A612406B@ghc.haskell.org> References: <20131202023914.B5A612406B@ghc.haskell.org> Message-ID: <59543203684B2244980D7E4057D5FBC1486D9865@DB3EX14MBXC308.europe.corp.microsoft.com> Patrick Thanks! When you do something subtle like change 'foldM' to 'foldrM', could you add a comment to point out the subtlety? After all, by definition this was something that someone else missed. Simon | -----Original Message----- | From: ghc-commits [mailto:ghc-commits-bounces at haskell.org] On Behalf Of | git at git.haskell.org | Sent: 02 December 2013 02:39 | To: ghc-commits at haskell.org | Subject: [commit: ghc] master: Respect the ordering of -package | directives (574ccfa) | | Repository : ssh://git at git.haskell.org/ghc | | On branch : master | Link : | http://ghc.haskell.org/trac/ghc/changeset/574ccfa231ca05d03d1da9d31e5bc | 81e74cc5e1e/ghc | | >--------------------------------------------------------------- | | commit 574ccfa231ca05d03d1da9d31e5bc81e74cc5e1e | Author: Patrick Palka | Date: Tue Nov 26 11:46:59 2013 -0500 | | Respect the ordering of -package directives | | | >--------------------------------------------------------------- | | 574ccfa231ca05d03d1da9d31e5bc81e74cc5e1e | compiler/main/Packages.lhs | 15 ++++++++------- | 1 file changed, 8 insertions(+), 7 deletions(-) | | diff --git a/compiler/main/Packages.lhs b/compiler/main/Packages.lhs | index aefb536..df5eddb 100644 | --- a/compiler/main/Packages.lhs | +++ b/compiler/main/Packages.lhs | @@ -59,6 +59,7 @@ import System.FilePath as FilePath | import qualified System.FilePath.Posix as FilePath.Posix | import Control.Monad | import Data.Char (isSpace) | +import Data.Foldable (foldrM) | import Data.List as List | import Data.Map (Map) | import qualified Data.Map as Map | @@ -980,7 +981,7 @@ getPreloadPackagesAnd dflags pkgids = | preload = preloadPackages state | pairs = zip pkgids (repeat Nothing) | in do | - all_pkgs <- throwErr dflags (foldM (add_package pkg_map ipid_map) | preload pairs) | + all_pkgs <- throwErr dflags (foldrM (add_package pkg_map ipid_map) | preload pairs) | return (map (getPackageDetails state) all_pkgs) | | -- Takes a list of packages, and returns the list with dependencies | included, | @@ -1003,15 +1004,15 @@ closeDepsErr :: PackageConfigMap | -> Map InstalledPackageId PackageId | -> [(PackageId,Maybe PackageId)] | -> MaybeErr MsgDoc [PackageId] | -closeDepsErr pkg_map ipid_map ps = foldM (add_package pkg_map | ipid_map) [] ps | +closeDepsErr pkg_map ipid_map ps = foldrM (add_package pkg_map | ipid_map) [] ps | | -- internal helper | add_package :: PackageConfigMap | -> Map InstalledPackageId PackageId | - -> [PackageId] | -> (PackageId,Maybe PackageId) | + -> [PackageId] | -> MaybeErr MsgDoc [PackageId] | -add_package pkg_db ipid_map ps (p, mb_parent) | +add_package pkg_db ipid_map (p, mb_parent) ps | | p `elem` ps = return ps -- Check if we've already added this | package | | otherwise = | case lookupPackage pkg_db p of | @@ -1019,12 +1020,12 @@ add_package pkg_db ipid_map ps (p, mb_parent) | missingDependencyMsg mb_parent) | Just pkg -> do | -- Add the package's dependents also | - ps' <- foldM add_package_ipid ps (depends pkg) | + ps' <- foldrM add_package_ipid ps (depends pkg) | return (p : ps') | where | - add_package_ipid ps ipid@(InstalledPackageId str) | + add_package_ipid ipid@(InstalledPackageId str) ps | | Just pid <- Map.lookup ipid ipid_map | - = add_package pkg_db ipid_map ps (pid, Just p) | + = add_package pkg_db ipid_map (pid, Just p) ps | | otherwise | = Failed (missingPackageMsg str <> missingDependencyMsg | mb_parent) | | | _______________________________________________ | ghc-commits mailing list | ghc-commits at haskell.org | http://www.haskell.org/mailman/listinfo/ghc-commits From git at git.haskell.org Mon Dec 2 11:12:03 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Dec 2013 11:12:03 +0000 (UTC) Subject: [commit: testsuite] master: Update testsuite for nicer Coercible message (522563a) Message-ID: <20131202111203.63F5624069@ghc.haskell.org> Repository : ssh://git at git.haskell.org/testsuite On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/522563a27b630b63d18e0ec6fa09c7b5eb6ab6c1/testsuite >--------------------------------------------------------------- commit 522563a27b630b63d18e0ec6fa09c7b5eb6ab6c1 Author: Joachim Breitner Date: Mon Dec 2 10:02:16 2013 +0000 Update testsuite for nicer Coercible message >--------------------------------------------------------------- 522563a27b630b63d18e0ec6fa09c7b5eb6ab6c1 tests/deriving/should_fail/T1496.stderr | 18 ++++----- tests/deriving/should_fail/T4846.stderr | 2 +- tests/deriving/should_fail/T7148.stderr | 42 +++++++------------- tests/deriving/should_fail/T7148a.stderr | 22 ++++------ tests/gadt/CasePrune.stderr | 11 ++--- tests/roles/should_fail/Roles10.stderr | 13 +++--- tests/typecheck/should_fail/TcCoercibleFail.stderr | 10 ++--- .../typecheck/should_fail/TcCoercibleFail3.stderr | 2 +- .../should_fail/TcCoercibleFailSafe.stderr | 2 +- 9 files changed, 48 insertions(+), 74 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 522563a27b630b63d18e0ec6fa09c7b5eb6ab6c1 From git at git.haskell.org Mon Dec 2 11:12:05 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Dec 2013 11:12:05 +0000 (UTC) Subject: [commit: ghc] master: With GND, report Coercible errors earliy (bd7a125) Message-ID: <20131202111205.9166F2406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/bd7a125b74e9e958bc88a450e9a4e5d1af3dc801/ghc >--------------------------------------------------------------- commit bd7a125b74e9e958bc88a450e9a4e5d1af3dc801 Author: Joachim Breitner Date: Mon Dec 2 09:45:12 2013 +0000 With GND, report Coercible errors earliy just like other type errors occurring during deriving. >--------------------------------------------------------------- bd7a125b74e9e958bc88a450e9a4e5d1af3dc801 compiler/typecheck/TcDeriv.lhs | 16 +++++++-- compiler/typecheck/TcGenDeriv.lhs | 66 +++++++++++++++++++++++-------------- 2 files changed, 54 insertions(+), 28 deletions(-) diff --git a/compiler/typecheck/TcDeriv.lhs b/compiler/typecheck/TcDeriv.lhs index 76a9011..9ce4f92 100644 --- a/compiler/typecheck/TcDeriv.lhs +++ b/compiler/typecheck/TcDeriv.lhs @@ -57,6 +57,7 @@ import ListSetOps import Outputable import FastString import Bag +import Pair import Control.Monad import Data.List @@ -1486,8 +1487,8 @@ mkNewTypeEqn orig dflags tvs -- dictionary - -- Next we figure out what superclass dictionaries to use - -- See Note [Newtype deriving superclasses] above + -- Next we figure out what superclass dictionaries to use + -- See Note [Newtype deriving superclasses] above cls_tyvars = classTyVars cls dfun_tvs = tyVarsOfTypes inst_tys @@ -1496,6 +1497,15 @@ mkNewTypeEqn orig dflags tvs sc_theta = substTheta (zipOpenTvSubst cls_tyvars inst_tys) (classSCTheta cls) + + -- Next we collect Coercible constaints between + -- the Class method types, instantiated with the representation and the + -- newtype type; precisely the constraints required for the + -- calls to coercible that we are going to generate. + coercible_constraints = + map (\(Pair t1 t2) -> mkCoerciblePred t1 t2) $ + mkCoerceClassMethEqn cls (varSetElemsKvsFirst dfun_tvs) inst_tys rep_inst_ty + -- If there are no tyvars, there's no need -- to abstract over the dictionaries we need -- Example: newtype T = MkT Int deriving( C ) @@ -1503,7 +1513,7 @@ mkNewTypeEqn orig dflags tvs -- instance C T -- rather than -- instance C Int => C T - all_preds = rep_pred : sc_theta -- NB: rep_pred comes first + all_preds = rep_pred : coercible_constraints ++ sc_theta -- NB: rep_pred comes first ------------------------------------------------------------------- -- Figuring out whether we can only do this newtype-deriving thing diff --git a/compiler/typecheck/TcGenDeriv.lhs b/compiler/typecheck/TcGenDeriv.lhs index d4af39f..f2e5413 100644 --- a/compiler/typecheck/TcGenDeriv.lhs +++ b/compiler/typecheck/TcGenDeriv.lhs @@ -30,6 +30,7 @@ module TcGenDeriv ( deepSubtypesContaining, foldDataConArgs, gen_Foldable_binds, gen_Traversable_binds, + mkCoerceClassMethEqn, gen_Newtype_binds, genAuxBinds, ordOpTbl, boxConTbl @@ -68,6 +69,7 @@ import Var import MonadUtils import Outputable import FastString +import Pair import Bag import Fingerprint import TcEnv (InstInfo) @@ -1907,44 +1909,58 @@ coercing from. See #8503 for more discussion. \begin{code} -gen_Newtype_binds :: SrcSpan - -> Class -- the class being derived - -> [TyVar] -- the tvs in the instance head - -> [Type] -- instance head parameters (incl. newtype) - -> Type -- the representation type (already eta-reduced) - -> LHsBinds RdrName -gen_Newtype_binds loc cls inst_tvs cls_tys rhs_ty - = listToBag $ map (L loc . mk_bind) $ classMethods cls +mkCoerceClassMethEqn :: Class -- the class being derived + -> [TyVar] -- the tvs in the instance head + -> [Type] -- instance head parameters (incl. newtype) + -> Type -- the representation type (already eta-reduced) + -> [Pair Type] +mkCoerceClassMethEqn cls inst_tvs cls_tys rhs_ty + = map mk_tys $ classMethods cls where cls_tvs = classTyVars cls in_scope = mkInScopeSet $ mkVarSet inst_tvs lhs_subst = mkTvSubst in_scope (zipTyEnv cls_tvs cls_tys) rhs_subst = mkTvSubst in_scope (zipTyEnv cls_tvs (changeLast cls_tys rhs_ty)) - coerce_RDR = getRdrName coerceId - - mk_bind :: Id -> HsBind RdrName - mk_bind id - = mkRdrFunBind (L loc meth_RDR) - [mkSimpleMatch [] rhs_expr] + mk_tys :: Id -> Pair Type + mk_tys id = Pair (substTy rhs_subst user_meth_ty) + (substTy lhs_subst user_meth_ty) where - meth_RDR = getRdrName id (_class_tvs, _class_constraint, user_meth_ty) = tcSplitSigmaTy (varType id) - (_quant_tvs, _quant_constraint, tau_meth_ty) = tcSplitSigmaTy user_meth_ty - - rhs_expr - = noLoc $ ExprWithTySig - (nlHsApp - (nlHsVar coerce_RDR) - (noLoc $ ExprWithTySig - (nlHsVar meth_RDR) - (toHsType $ substTy rhs_subst tau_meth_ty))) - (toHsType $ substTy lhs_subst user_meth_ty) changeLast :: [a] -> a -> [a] changeLast [] _ = panic "changeLast" changeLast [_] x = [x] changeLast (x:xs) x' = x : changeLast xs x' + + +gen_Newtype_binds :: SrcSpan + -> Class -- the class being derived + -> [TyVar] -- the tvs in the instance head + -> [Type] -- instance head parameters (incl. newtype) + -> Type -- the representation type (already eta-reduced) + -> LHsBinds RdrName +gen_Newtype_binds loc cls inst_tvs cls_tys rhs_ty + = listToBag $ zipWith mk_bind + (classMethods cls) + (mkCoerceClassMethEqn cls inst_tvs cls_tys rhs_ty) + where + coerce_RDR = getRdrName coerceId + mk_bind :: Id -> Pair Type -> LHsBind RdrName + mk_bind id (Pair tau_ty user_ty) + = L loc $ mkRdrFunBind (L loc meth_RDR) [mkSimpleMatch [] rhs_expr] + where + meth_RDR = getRdrName id + rhs_expr + = ( nlHsVar coerce_RDR + `nlHsApp` + (nlHsVar meth_RDR `nlExprWithTySig` toHsType tau_ty')) + `nlExprWithTySig` toHsType user_ty + -- Open the representation type here, so that it's forall'ed type + -- variables refer to the ones bound in the user_ty + (_, _, tau_ty') = tcSplitSigmaTy tau_ty + + nlExprWithTySig e s = noLoc (ExprWithTySig e s) \end{code} %************************************************************************ From git at git.haskell.org Mon Dec 2 11:12:01 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Dec 2013 11:12:01 +0000 (UTC) Subject: [commit: ghc] master: TcDeriv: s/isomorphism/coercible (5e86ea5) Message-ID: <20131202111201.1ABFA2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5e86ea5064e8e0dce9734a7f1629aa058e57fb3d/ghc >--------------------------------------------------------------- commit 5e86ea5064e8e0dce9734a7f1629aa058e57fb3d Author: Joachim Breitner Date: Mon Dec 2 09:22:23 2013 +0000 TcDeriv: s/isomorphism/coercible in comments and function names, to use less names for the same thing. >--------------------------------------------------------------- 5e86ea5064e8e0dce9734a7f1629aa058e57fb3d compiler/typecheck/TcDeriv.lhs | 38 +++++++++++++++++++------------------- 1 file changed, 19 insertions(+), 19 deletions(-) diff --git a/compiler/typecheck/TcDeriv.lhs b/compiler/typecheck/TcDeriv.lhs index 025ac07..76a9011 100644 --- a/compiler/typecheck/TcDeriv.lhs +++ b/compiler/typecheck/TcDeriv.lhs @@ -274,9 +274,9 @@ clause. The last arg is the new instance type. We must pass the superclasses; the newtype might be an instance of them in a different way than the representation type E.g. newtype Foo a = Foo a deriving( Show, Num, Eq ) -Then the Show instance is not done via isomorphism; it shows +Then the Show instance is not done via Coercible; it shows Foo 3 as "Foo 3" -The Num instance is derived via isomorphism, but the Show superclass +The Num instance is derived via Coercible, but the Show superclass dictionary must the Show instance for Foo, *not* the Show dictionary gotten from the Num dictionary. So we must build a whole new dictionary not just use the Num one. The instance we want is something like: @@ -977,7 +977,7 @@ mkPolyKindedTypeableEqn orig tvs cls tycon tc_args mtheta = ptext (sLit "Derived Typeable instance must be of form") <+> parens (ptext (sLit "Typeable") <+> ppr tycon) ----------------------- + inferConstraints :: Class -> [TcType] -> TyCon -> [TcType] -> TcM ThetaType @@ -1327,23 +1327,23 @@ checkFlag flag (dflags, _, _) [s] -> s other -> pprPanic "checkFlag" (ppr other) -std_class_via_iso :: Class -> Bool +std_class_via_coercible :: Class -> Bool -- These standard classes can be derived for a newtype --- using the isomorphism trick *even if no -XGeneralizedNewtypeDeriving +-- using the coercible trick *even if no -XGeneralizedNewtypeDeriving -- because giving so gives the same results as generating the boilerplate -std_class_via_iso clas +std_class_via_coercible clas = classKey clas `elem` [eqClassKey, ordClassKey, ixClassKey, boundedClassKey] -- Not Read/Show because they respect the type -- Not Enum, because newtypes are never in Enum -non_iso_class :: Class -> Bool --- *Never* derive Read, Show, Typeable, Data, Generic, Generic1 by isomorphism, +non_coercible_class :: Class -> Bool +-- *Never* derive Read, Show, Typeable, Data, Generic, Generic1 by Coercible, -- even with -XGeneralizedNewtypeDeriving --- Also, avoid Traversable, as the iso-derived instance and the "normal"-derived +-- Also, avoid Traversable, as the Coercible-derived instance and the "normal"-derived -- instance behave differently if there's a non-lawful Applicative out there. --- Besides, with roles, iso-deriving Traversable is ill-roled. -non_iso_class cls +-- Besides, with roles, Coercible-deriving Traversable is ill-roled. +non_coercible_class cls = classKey cls `elem` ([ readClassKey, showClassKey, dataClassKey , genClassKey, gen1ClassKey, typeableClassKey , traversableClassKey ] @@ -1402,7 +1402,7 @@ mkNewTypeEqn :: CtOrigin -> DynFlags -> [Var] -> Class mkNewTypeEqn orig dflags tvs cls cls_tys tycon tc_args rep_tycon rep_tc_args mtheta -- Want: instance (...) => cls (cls_tys ++ [tycon tc_args]) where ... - | might_derive_via_isomorphism && (newtype_deriving || std_class_via_iso cls) + | might_derive_via_coercible && (newtype_deriving || std_class_via_coercible cls) = do { traceTc "newtype deriving:" (ppr tycon <+> ppr rep_tys <+> ppr all_preds) ; dfun_name <- new_dfun_name cls tycon ; loc <- getSrcSpanM @@ -1419,12 +1419,12 @@ mkNewTypeEqn orig dflags tvs = case checkSideConditions dflags mtheta cls cls_tys rep_tycon rep_tc_args of CanDerive -> go_for_it -- Use the standard H98 method DerivableClassError msg -- Error with standard class - | might_derive_via_isomorphism -> bale_out (msg $$ suggest_nd) - | otherwise -> bale_out msg + | might_derive_via_coercible -> bale_out (msg $$ suggest_nd) + | otherwise -> bale_out msg NonDerivableClass -- Must use newtype deriving - | newtype_deriving -> bale_out cant_derive_err -- Too hard, even with newtype deriving - | might_derive_via_isomorphism -> bale_out (non_std $$ suggest_nd) -- Try newtype deriving! - | otherwise -> bale_out non_std + | newtype_deriving -> bale_out cant_derive_err -- Too hard, even with newtype deriving + | might_derive_via_coercible -> bale_out (non_std $$ suggest_nd) -- Try newtype deriving! + | otherwise -> bale_out non_std where newtype_deriving = xopt Opt_GeneralizedNewtypeDeriving dflags go_for_it = mk_data_eqn orig tvs cls tycon tc_args rep_tycon rep_tc_args mtheta @@ -1509,8 +1509,8 @@ mkNewTypeEqn orig dflags tvs -- Figuring out whether we can only do this newtype-deriving thing -- See Note [Determining whether newtype-deriving is appropriate] - might_derive_via_isomorphism - = not (non_iso_class cls) + might_derive_via_coercible + = not (non_coercible_class cls) && arity_ok && eta_ok && ats_ok From git at git.haskell.org Mon Dec 2 11:12:03 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Dec 2013 11:12:03 +0000 (UTC) Subject: [commit: ghc] master: Print nicer error message for Coercible errors (1791ea0) Message-ID: <20131202111203.4C44C2406F@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1791ea0abf446bc7221f713d715f4bf87dc6af47/ghc >--------------------------------------------------------------- commit 1791ea0abf446bc7221f713d715f4bf87dc6af47 Author: Joachim Breitner Date: Mon Dec 2 10:01:56 2013 +0000 Print nicer error message for Coercible errors It now reads Could not coerce from ?S a? to ?S (NT a)? and does not mention Coercible any more (as discussed in #8567). >--------------------------------------------------------------- 1791ea0abf446bc7221f713d715f4bf87dc6af47 compiler/typecheck/TcErrors.lhs | 19 ++++++++++++------- 1 file changed, 12 insertions(+), 7 deletions(-) diff --git a/compiler/typecheck/TcErrors.lhs b/compiler/typecheck/TcErrors.lhs index 3ccf456..83d38da 100644 --- a/compiler/typecheck/TcErrors.lhs +++ b/compiler/typecheck/TcErrors.lhs @@ -1002,8 +1002,7 @@ mk_dict_err ctxt (ct, (matches, unifiers, safe_haskell)) all_tyvars = all isTyVarTy tys cannot_resolve_msg safe_mod rdr_env has_ambig_tvs binds_msg ambig_msg - = vcat [ addArising orig (no_inst_herald <+> pprParendType pred $$ - coercible_msg safe_mod rdr_env) + = vcat [ addArising orig (no_inst_msg $$ coercible_explanation safe_mod rdr_env) , vcat (pp_givens givens) , ppWhen (has_ambig_tvs && not (null unifiers && null givens)) (vcat [ ambig_msg, binds_msg, potential_msg ]) @@ -1039,9 +1038,15 @@ mk_dict_err ctxt (ct, (matches, unifiers, safe_haskell)) SigSkol (InfSigCtxt {}) _ -> Nothing origin -> Just origin - no_inst_herald - | null givens && null matches = ptext (sLit "No instance for") - | otherwise = ptext (sLit "Could not deduce") + no_inst_msg + | clas == coercibleClass + = let (ty1, ty2) = getEqPredTys pred + in ptext (sLit "Could not coerce from") <+> quotes (ppr ty1) <+> + ptext (sLit "to") <+> quotes (ppr ty2) + | null givens && null matches + = ptext (sLit "No instance for") <+> pprParendType pred + | otherwise + = ptext (sLit "Could not deduce") <+> pprParendType pred drv_fixes = case orig of DerivOrigin -> [drv_fix] @@ -1120,7 +1125,7 @@ mk_dict_err ctxt (ct, (matches, unifiers, safe_haskell)) -- This function tries to reconstruct why a "Coercible ty1 ty2" constraint -- is left over. Therefore its logic has to stay in sync with -- getCoericbleInst in TcInteract. See Note [Coercible Instances] - coercible_msg safe_mod rdr_env + coercible_explanation safe_mod rdr_env | clas /= coercibleClass = empty | Just (tc1,tyArgs1) <- splitTyConApp_maybe ty1, Just (tc2,tyArgs2) <- splitTyConApp_maybe ty2, @@ -1162,7 +1167,7 @@ mk_dict_err ctxt (ct, (matches, unifiers, safe_haskell)) ptext $ sLit "and", quotes (ppr ty2), ptext $ sLit "are different types." ] where - (clas, ~[_k, ty1,ty2]) = getClassPredTys (ctPred ct) + (ty1, ty2) = getEqPredTys pred dataConMissing rdr_env tc = all (null . lookupGRE_Name rdr_env) (map dataConName (tyConDataCons tc)) From git at git.haskell.org Mon Dec 2 11:35:52 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Dec 2013 11:35:52 +0000 (UTC) Subject: [commit: testsuite] master: Bump T3064 perf values (c37e2fb) Message-ID: <20131202113552.D0AB72406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/testsuite On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c37e2fb1ebc88992c2704875b2154dffc6c41de0/testsuite >--------------------------------------------------------------- commit c37e2fb1ebc88992c2704875b2154dffc6c41de0 Author: Joachim Breitner Date: Mon Dec 2 11:36:03 2013 +0000 Bump T3064 perf values >--------------------------------------------------------------- c37e2fb1ebc88992c2704875b2154dffc6c41de0 tests/perf/compiler/all.T | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/tests/perf/compiler/all.T b/tests/perf/compiler/all.T index 347f492..abc9758 100644 --- a/tests/perf/compiler/all.T +++ b/tests/perf/compiler/all.T @@ -207,12 +207,13 @@ test('T3064', [(wordsize(32), 111189536, 10), # expected value: 56380288 (x86/Linux) (28/6/2011) # 111189536 (x86/Windows) (30/10/12) - (wordsize(64), 308300448, 5)]), + (wordsize(64), 329795912, 5)]), # (amd64/Linux) (28/06/2011): 73259544 # (amd64/Linux) (07/02/2013): 224798696 # (amd64/Linux) (02/08/2013): 236404384, increase from roles # (amd64/Linux) (11/09/2013): 290165632, increase from AMP warnings # (amd64/Linux) (22/11/2013): 308300448, GND via Coercible and counters for constraints solving + # (amd64/Linux) (02/12/2013): 329795912, Coercible refactor compiler_stats_num_field('max_bytes_used', [(wordsize(32), 5511604, 20), # expected value: 2247016 (x86/Linux) (28/6/2011): From git at git.haskell.org Mon Dec 2 11:35:56 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Dec 2013 11:35:56 +0000 (UTC) Subject: [commit: ghc] master: Handle Coercible (forall a. t) (forall a. t2) in TcInteract (e1e9faf) Message-ID: <20131202113556.2DD142406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e1e9fafcb799c6fdd1468b55b9362658d72fc382/ghc >--------------------------------------------------------------- commit e1e9fafcb799c6fdd1468b55b9362658d72fc382 Author: Joachim Breitner Date: Mon Dec 2 11:01:36 2013 +0000 Handle Coercible (forall a. t) (forall a. t2) in TcInteract >--------------------------------------------------------------- e1e9fafcb799c6fdd1468b55b9362658d72fc382 compiler/typecheck/TcCanonical.lhs | 18 +----------------- compiler/typecheck/TcInteract.lhs | 10 ++++++++++ 2 files changed, 11 insertions(+), 17 deletions(-) diff --git a/compiler/typecheck/TcCanonical.lhs b/compiler/typecheck/TcCanonical.lhs index eeb7cfe..6f8e3db 100644 --- a/compiler/typecheck/TcCanonical.lhs +++ b/compiler/typecheck/TcCanonical.lhs @@ -19,7 +19,7 @@ import VarEnv import OccName( OccName ) import Outputable import Control.Monad ( when ) -import TysWiredIn ( eqTyCon, coercibleClass ) +import TysWiredIn ( eqTyCon ) import DynFlags( DynFlags ) import VarSet import TcSMonad @@ -233,22 +233,6 @@ canClassNC ev cls tys = canClass ev cls tys `andWhenContinue` emitSuperclasses --- This case implements Coercible (forall a. body) (forall b. body) -canClass ev cls tys - -- See Note [Coercible instances] - | cls == coercibleClass - , [_k, ty1, ty2] <- tys - , tcIsForAllTy ty1 - , tcIsForAllTy ty2 - , let (tvs1,body1) = tcSplitForAllTys ty1 - (tvs2,body2) = tcSplitForAllTys ty2 - , CtWanted { ctev_loc = loc, ctev_evar = orig_ev } <- ev - , equalLength tvs1 tvs2 - = do { traceTcS "Creating implication for polytype coercible equality" $ ppr ev - ; ev_term <- deferTcSForAllEq Representational loc (tvs1,body1) (tvs2,body2) - ; setEvBind orig_ev ev_term - ; return Stop } - canClass ev cls tys = do { (xis, cos) <- flattenMany FMFullFlatten ev tys ; let co = mkTcTyConAppCo Nominal (classTyCon cls) cos diff --git a/compiler/typecheck/TcInteract.lhs b/compiler/typecheck/TcInteract.lhs index 466882f..989997a 100644 --- a/compiler/typecheck/TcInteract.lhs +++ b/compiler/typecheck/TcInteract.lhs @@ -1944,6 +1944,16 @@ getCoercibleInst loc ty1 ty2 = do | ty1 `tcEqType` ty2 = do return $ GenInst [] $ EvCoercion (TcRefl Representational ty1) + + | tcIsForAllTy ty1 + , tcIsForAllTy ty2 + , let (tvs1,body1) = tcSplitForAllTys ty1 + (tvs2,body2) = tcSplitForAllTys ty2 + , equalLength tvs1 tvs2 + = do + ev_term <- deferTcSForAllEq Representational loc (tvs1,body1) (tvs2,body2) + return $ GenInst [] ev_term + | Just (tc1,tyArgs1) <- splitTyConApp_maybe ty1, Just (tc2,tyArgs2) <- splitTyConApp_maybe ty2, tc1 == tc2, From git at git.haskell.org Mon Dec 2 11:35:58 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Dec 2013 11:35:58 +0000 (UTC) Subject: [commit: ghc] master: Bind monadic stuff in getCoercibleInst locally, not via parameters (249d47a) Message-ID: <20131202113558.421422406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/249d47a5f94a0e00d02e15689bf258b63461b83b/ghc >--------------------------------------------------------------- commit 249d47a5f94a0e00d02e15689bf258b63461b83b Author: Joachim Breitner Date: Mon Dec 2 10:56:31 2013 +0000 Bind monadic stuff in getCoercibleInst locally, not via parameters >--------------------------------------------------------------- 249d47a5f94a0e00d02e15689bf258b63461b83b compiler/typecheck/TcInteract.lhs | 137 +++++++++++++++++++------------------ 1 file changed, 71 insertions(+), 66 deletions(-) diff --git a/compiler/typecheck/TcInteract.lhs b/compiler/typecheck/TcInteract.lhs index 805afb6..466882f 100644 --- a/compiler/typecheck/TcInteract.lhs +++ b/compiler/typecheck/TcInteract.lhs @@ -1845,10 +1845,7 @@ matchClassInst _ clas [ ty ] _ matchClassInst _ clas [ _k, ty1, ty2 ] loc | clas == coercibleClass = do traceTcS "matchClassInst for" $ ppr clas <+> ppr ty1 <+> ppr ty2 <+> text "at depth" <+> ppr (ctLocDepth loc) - rdr_env <- getGlobalRdrEnvTcS - famenv <- getFamInstEnvs - safeMode <- safeLanguageOn `fmap` getDynFlags - ev <- getCoercibleInst safeMode famenv rdr_env loc ty1 ty2 + ev <- getCoercibleInst loc ty1 ty2 traceTcS "matchClassInst returned" $ ppr ev return ev @@ -1934,68 +1931,76 @@ matchClassInst inerts clas tys loc -- See Note [Coercible Instances] -- Changes to this logic should likely be reflected in coercible_msg in TcErrors. -getCoercibleInst :: Bool -> FamInstEnvs -> GlobalRdrEnv -> CtLoc -> TcType -> TcType -> TcS LookupInstResult -getCoercibleInst safeMode famenv rdr_env loc ty1 ty2 - | ty1 `tcEqType` ty2 - = do return $ GenInst [] - $ EvCoercion (TcRefl Representational ty1) - | Just (tc1,tyArgs1) <- splitTyConApp_maybe ty1, - Just (tc2,tyArgs2) <- splitTyConApp_maybe ty2, - tc1 == tc2, - nominalArgsAgree tc1 tyArgs1 tyArgs2, - not safeMode || all (dataConsInScope rdr_env) (tyConsOfTyCon tc1) - = do -- Mark all used data constructors as used - when safeMode $ mapM_ (markDataConsAsUsed rdr_env) (tyConsOfTyCon tc1) - -- We want evidence for all type arguments of role R - arg_stuff <- forM (zip3 (tyConRoles tc1) tyArgs1 tyArgs2) $ \(r,ta1,ta2) -> - case r of Nominal -> do - return - ( Nothing - , Nothing - , mkTcReflCo Nominal ta1 {- == ta2, due to nominalArgsAgree -} - ) - Representational -> do - ct_ev <- requestCoercible loc ta1 ta2 - local_var <- mkSysLocalM (fsLit "coev") $ mkCoerciblePred ta1 ta2 - return - ( freshGoal ct_ev - , Just (EvBind local_var (getEvTerm ct_ev)) - , mkTcCoVarCo local_var - ) - Phantom -> do - return - ( Nothing - , Nothing - , TcPhantomCo ta1 ta2) - let (arg_new, arg_binds, arg_cos) = unzip3 arg_stuff - binds = EvBinds (listToBag (catMaybes arg_binds)) - tcCo = TcLetCo binds (mkTcTyConAppCo Representational tc1 arg_cos) - return $ GenInst (catMaybes arg_new) (EvCoercion tcCo) - - | Just (tc,tyArgs) <- splitTyConApp_maybe ty1, - Just (concTy, ntCo) <- instNewTyConTF_maybe famenv tc tyArgs, - dataConsInScope rdr_env tc -- Do noot look at all tyConsOfTyCon - = do markDataConsAsUsed rdr_env tc - ct_ev <- requestCoercible loc concTy ty2 - local_var <- mkSysLocalM (fsLit "coev") $ mkCoerciblePred concTy ty2 - let binds = EvBinds (unitBag (EvBind local_var (getEvTerm ct_ev))) - tcCo = TcLetCo binds $ - coercionToTcCoercion ntCo `mkTcTransCo` mkTcCoVarCo local_var - return $ GenInst (freshGoals [ct_ev]) (EvCoercion tcCo) - - | Just (tc,tyArgs) <- splitTyConApp_maybe ty2, - Just (concTy, ntCo) <- instNewTyConTF_maybe famenv tc tyArgs, - dataConsInScope rdr_env tc -- Do noot look at all tyConsOfTyCon - = do markDataConsAsUsed rdr_env tc - ct_ev <- requestCoercible loc ty1 concTy - local_var <- mkSysLocalM (fsLit "coev") $ mkCoerciblePred ty1 concTy - let binds = EvBinds (unitBag (EvBind local_var (getEvTerm ct_ev))) - tcCo = TcLetCo binds $ - mkTcCoVarCo local_var `mkTcTransCo` mkTcSymCo (coercionToTcCoercion ntCo) - return $ GenInst (freshGoals [ct_ev]) (EvCoercion tcCo) - - | otherwise - = return NoInstance +getCoercibleInst :: CtLoc -> TcType -> TcType -> TcS LookupInstResult +getCoercibleInst loc ty1 ty2 = do + -- Get some global stuff in scope, for nice pattern-guard based code in `go` + rdr_env <- getGlobalRdrEnvTcS + famenv <- getFamInstEnvs + safeMode <- safeLanguageOn `fmap` getDynFlags + go safeMode famenv rdr_env + where + go :: Bool -> FamInstEnvs -> GlobalRdrEnv -> TcS LookupInstResult + go safeMode famenv rdr_env + | ty1 `tcEqType` ty2 + = do return $ GenInst [] + $ EvCoercion (TcRefl Representational ty1) + | Just (tc1,tyArgs1) <- splitTyConApp_maybe ty1, + Just (tc2,tyArgs2) <- splitTyConApp_maybe ty2, + tc1 == tc2, + nominalArgsAgree tc1 tyArgs1 tyArgs2, + not safeMode || all (dataConsInScope rdr_env) (tyConsOfTyCon tc1) + = do -- Mark all used data constructors as used + when safeMode $ mapM_ (markDataConsAsUsed rdr_env) (tyConsOfTyCon tc1) + -- We want evidence for all type arguments of role R + arg_stuff <- forM (zip3 (tyConRoles tc1) tyArgs1 tyArgs2) $ \(r,ta1,ta2) -> + case r of Nominal -> do + return + ( Nothing + , Nothing + , mkTcReflCo Nominal ta1 {- == ta2, due to nominalArgsAgree -} + ) + Representational -> do + ct_ev <- requestCoercible loc ta1 ta2 + local_var <- mkSysLocalM (fsLit "coev") $ mkCoerciblePred ta1 ta2 + return + ( freshGoal ct_ev + , Just (EvBind local_var (getEvTerm ct_ev)) + , mkTcCoVarCo local_var + ) + Phantom -> do + return + ( Nothing + , Nothing + , TcPhantomCo ta1 ta2) + let (arg_new, arg_binds, arg_cos) = unzip3 arg_stuff + binds = EvBinds (listToBag (catMaybes arg_binds)) + tcCo = TcLetCo binds (mkTcTyConAppCo Representational tc1 arg_cos) + return $ GenInst (catMaybes arg_new) (EvCoercion tcCo) + + | Just (tc,tyArgs) <- splitTyConApp_maybe ty1, + Just (concTy, ntCo) <- instNewTyConTF_maybe famenv tc tyArgs, + dataConsInScope rdr_env tc -- Do noot look at all tyConsOfTyCon + = do markDataConsAsUsed rdr_env tc + ct_ev <- requestCoercible loc concTy ty2 + local_var <- mkSysLocalM (fsLit "coev") $ mkCoerciblePred concTy ty2 + let binds = EvBinds (unitBag (EvBind local_var (getEvTerm ct_ev))) + tcCo = TcLetCo binds $ + coercionToTcCoercion ntCo `mkTcTransCo` mkTcCoVarCo local_var + return $ GenInst (freshGoals [ct_ev]) (EvCoercion tcCo) + + | Just (tc,tyArgs) <- splitTyConApp_maybe ty2, + Just (concTy, ntCo) <- instNewTyConTF_maybe famenv tc tyArgs, + dataConsInScope rdr_env tc -- Do noot look at all tyConsOfTyCon + = do markDataConsAsUsed rdr_env tc + ct_ev <- requestCoercible loc ty1 concTy + local_var <- mkSysLocalM (fsLit "coev") $ mkCoerciblePred ty1 concTy + let binds = EvBinds (unitBag (EvBind local_var (getEvTerm ct_ev))) + tcCo = TcLetCo binds $ + mkTcCoVarCo local_var `mkTcTransCo` mkTcSymCo (coercionToTcCoercion ntCo) + return $ GenInst (freshGoals [ct_ev]) (EvCoercion tcCo) + + | otherwise + = return NoInstance nominalArgsAgree :: TyCon -> [Type] -> [Type] -> Bool nominalArgsAgree tc tys1 tys2 = all ok $ zip3 (tyConRoles tc) tys1 tys2 From git at git.haskell.org Mon Dec 2 11:36:00 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Dec 2013 11:36:00 +0000 (UTC) Subject: [commit: ghc] master: Refactor deferTcSForAllEq: Do not bind, but return EvTerm (06facab) Message-ID: <20131202113600.78F992406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/06facab6e4269599a671b8aca36dd2317d58175c/ghc >--------------------------------------------------------------- commit 06facab6e4269599a671b8aca36dd2317d58175c Author: Joachim Breitner Date: Mon Dec 2 10:12:38 2013 +0000 Refactor deferTcSForAllEq: Do not bind, but return EvTerm >--------------------------------------------------------------- 06facab6e4269599a671b8aca36dd2317d58175c compiler/typecheck/TcCanonical.lhs | 6 ++++-- compiler/typecheck/TcSMonad.lhs | 9 ++++----- 2 files changed, 8 insertions(+), 7 deletions(-) diff --git a/compiler/typecheck/TcCanonical.lhs b/compiler/typecheck/TcCanonical.lhs index 392f12d..eeb7cfe 100644 --- a/compiler/typecheck/TcCanonical.lhs +++ b/compiler/typecheck/TcCanonical.lhs @@ -245,7 +245,8 @@ canClass ev cls tys , CtWanted { ctev_loc = loc, ctev_evar = orig_ev } <- ev , equalLength tvs1 tvs2 = do { traceTcS "Creating implication for polytype coercible equality" $ ppr ev - ; deferTcSForAllEq Representational (loc,orig_ev) (tvs1,body1) (tvs2,body2) + ; ev_term <- deferTcSForAllEq Representational loc (tvs1,body1) (tvs2,body2) + ; setEvBind orig_ev ev_term ; return Stop } canClass ev cls tys @@ -766,7 +767,8 @@ canEqNC ev s1@(ForAllTy {}) s2@(ForAllTy {}) canEqFailure ev s1 s2 else do { traceTcS "Creating implication for polytype equality" $ ppr ev - ; deferTcSForAllEq Nominal (loc,orig_ev) (tvs1,body1) (tvs2,body2) + ; ev_term <- deferTcSForAllEq Nominal loc (tvs1,body1) (tvs2,body2) + ; setEvBind orig_ev ev_term ; return Stop } } | otherwise = do { traceTcS "Ommitting decomposition of given polytype equality" $ diff --git a/compiler/typecheck/TcSMonad.lhs b/compiler/typecheck/TcSMonad.lhs index 06856d7..ba46248 100644 --- a/compiler/typecheck/TcSMonad.lhs +++ b/compiler/typecheck/TcSMonad.lhs @@ -1751,13 +1751,13 @@ matchFam tycon args -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ deferTcSForAllEq :: Role -- Nominal or Representational - -> (CtLoc,EvVar) -- Original wanted equality flavor + -> CtLoc -- Original wanted equality flavor -> ([TyVar],TcType) -- ForAll tvs1 body1 -> ([TyVar],TcType) -- ForAll tvs2 body2 - -> TcS () + -> TcS EvTerm -- Some of this functionality is repeated from TcUnify, -- consider having a single place where we create fresh implications. -deferTcSForAllEq role (loc,orig_ev) (tvs1,body1) (tvs2,body2) +deferTcSForAllEq role loc (tvs1,body1) (tvs2,body2) = do { (subst1, skol_tvs) <- wrapTcS $ TcM.tcInstSkolTyVars tvs1 ; let tys = mkTyVarTys skol_tvs phi1 = Type.substTy subst1 body1 @@ -1790,8 +1790,7 @@ deferTcSForAllEq role (loc,orig_ev) (tvs1,body1) (tvs2,body2) ; updTcSImplics (consBag imp) ; return (TcLetCo ev_binds new_co) } - ; setEvBind orig_ev $ - EvCoercion (foldr mkTcForAllCo coe_inside skol_tvs) + ; return $ EvCoercion (foldr mkTcForAllCo coe_inside skol_tvs) } \end{code} From git at git.haskell.org Mon Dec 2 11:36:02 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Dec 2013 11:36:02 +0000 (UTC) Subject: [commit: ghc] master: More links to [Coercible Instances] (b859c18) Message-ID: <20131202113602.74F352406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b859c188f231aa4d0f0c7515d748e6adf6efd6bc/ghc >--------------------------------------------------------------- commit b859c188f231aa4d0f0c7515d748e6adf6efd6bc Author: Joachim Breitner Date: Mon Dec 2 11:05:31 2013 +0000 More links to [Coercible Instances] >--------------------------------------------------------------- b859c188f231aa4d0f0c7515d748e6adf6efd6bc compiler/typecheck/TcInteract.lhs | 19 +++++++++++++------ 1 file changed, 13 insertions(+), 6 deletions(-) diff --git a/compiler/typecheck/TcInteract.lhs b/compiler/typecheck/TcInteract.lhs index 989997a..1324265 100644 --- a/compiler/typecheck/TcInteract.lhs +++ b/compiler/typecheck/TcInteract.lhs @@ -1941,10 +1941,12 @@ getCoercibleInst loc ty1 ty2 = do where go :: Bool -> FamInstEnvs -> GlobalRdrEnv -> TcS LookupInstResult go safeMode famenv rdr_env + -- Coercible a a (see case 1 in [Coercible Instances]) | ty1 `tcEqType` ty2 = do return $ GenInst [] $ EvCoercion (TcRefl Representational ty1) + -- Coercible (forall a. ty) (forall a. ty') (see case 2 in [Coercible Instances]) | tcIsForAllTy ty1 , tcIsForAllTy ty2 , let (tvs1,body1) = tcSplitForAllTys ty1 @@ -1954,6 +1956,7 @@ getCoercibleInst loc ty1 ty2 = do ev_term <- deferTcSForAllEq Representational loc (tvs1,body1) (tvs2,body2) return $ GenInst [] ev_term + -- Coercible (D ty1 ty2) (D ty1' ty2') (see case 3 in [Coercible Instances]) | Just (tc1,tyArgs1) <- splitTyConApp_maybe ty1, Just (tc2,tyArgs2) <- splitTyConApp_maybe ty2, tc1 == tc2, @@ -1987,6 +1990,7 @@ getCoercibleInst loc ty1 ty2 = do tcCo = TcLetCo binds (mkTcTyConAppCo Representational tc1 arg_cos) return $ GenInst (catMaybes arg_new) (EvCoercion tcCo) + -- Coercible NT a (see case 4 in [Coercible Instances]) | Just (tc,tyArgs) <- splitTyConApp_maybe ty1, Just (concTy, ntCo) <- instNewTyConTF_maybe famenv tc tyArgs, dataConsInScope rdr_env tc -- Do noot look at all tyConsOfTyCon @@ -1998,6 +2002,7 @@ getCoercibleInst loc ty1 ty2 = do coercionToTcCoercion ntCo `mkTcTransCo` mkTcCoVarCo local_var return $ GenInst (freshGoals [ct_ev]) (EvCoercion tcCo) + -- Coercible a NT (see case 4 in [Coercible Instances]) | Just (tc,tyArgs) <- splitTyConApp_maybe ty2, Just (concTy, ntCo) <- instNewTyConTF_maybe famenv tc tyArgs, dataConsInScope rdr_env tc -- Do noot look at all tyConsOfTyCon @@ -2009,6 +2014,7 @@ getCoercibleInst loc ty1 ty2 = do mkTcCoVarCo local_var `mkTcTransCo` mkTcSymCo (coercionToTcCoercion ntCo) return $ GenInst (freshGoals [ct_ev]) (EvCoercion tcCo) + -- Cannot solve this one | otherwise = return NoInstance @@ -2052,7 +2058,12 @@ air, in getCoercibleInst. The following ?instances? are present: 1. instance Coercible a a for any type a at any kind k. - 2. instance (Coercible t1_r t1'_r, Coercible t2_r t2_r',...) => + 2. instance (forall a. Coercible t1 t2) => Coercible (forall a. t1) (forall a. t2) + (which would be illegal to write like that in the source code, but we have + it nevertheless). + + + 3. instance (Coercible t1_r t1'_r, Coercible t2_r t2_r',...) => Coercible (C t1_r t2_r ... t1_p t2_p ... t1_n t2_n ...) (C t1_r' t2_r' ... t1_p' t2_p' ... t1_n t2_n ...) for a type constructor C where @@ -2070,7 +2081,7 @@ air, in getCoercibleInst. The following ?instances? are present: This is required as otherwise the previous check can be circumvented by just adding a local data type around C. - 3. instance Coercible r b => Coercible (NT t1 t2 ...) b + 4. instance Coercible r b => Coercible (NT t1 t2 ...) b instance Coercible a r => Coercible a (NT t1 t2 ...) for a newtype constructor NT (nor data family instance that resolves to a newtype) where @@ -2085,10 +2096,6 @@ air, in getCoercibleInst. The following ?instances? are present: newtype NT3 a b = NT3 (b -> a) Coercible (NT2 Int) (NT3 Int) -- cannot be derived - 4. instance (forall a. Coercible t1 t2) => Coercible (forall a. t1) (forall a. t2) - (which would be illegal to write like that in the source code, but we have - it nevertheless). - The type checker generates evidence in the form of EvCoercion, but the TcCoercion therein has role Representational, which are turned into Core coercions by dsEvTerm in DsBinds. From git at git.haskell.org Mon Dec 2 13:05:25 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Dec 2013 13:05:25 +0000 (UTC) Subject: [commit: testsuite] master: Update apirecomp001 output (8c9b01c) Message-ID: <20131202130525.1D6252406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/testsuite On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8c9b01c5a94aa86df56bac3b1df826d8e928b453/testsuite >--------------------------------------------------------------- commit 8c9b01c5a94aa86df56bac3b1df826d8e928b453 Author: Joachim Breitner Date: Mon Dec 2 13:04:55 2013 +0000 Update apirecomp001 output >--------------------------------------------------------------- 8c9b01c5a94aa86df56bac3b1df826d8e928b453 tests/ghc-api/apirecomp001/apirecomp001.stderr | 12 ++++++------ 1 file changed, 6 insertions(+), 6 deletions(-) diff --git a/tests/ghc-api/apirecomp001/apirecomp001.stderr b/tests/ghc-api/apirecomp001/apirecomp001.stderr index b7666b7..66f83c8 100644 --- a/tests/ghc-api/apirecomp001/apirecomp001.stderr +++ b/tests/ghc-api/apirecomp001/apirecomp001.stderr @@ -3,14 +3,14 @@ B.hs:4:1: Warning: Top-level binding with no type signature: answer_to_live_the_universe_and_everything :: Int -B.hs:5:12: Warning: +B.hs:5:13: Warning: Defaulting the following constraint(s) to type ?Integer? + (Num a0) arising from the literal ?1? at B.hs:5:13 (Enum a0) arising from the arithmetic sequence ?1 .. 23 * 2? at B.hs:5:12-20 - (Num a0) arising from the literal ?1? at B.hs:5:13 + In the expression: 1 In the first argument of ?length?, namely ?[1 .. 23 * 2]? In the first argument of ?(-)?, namely ?length [1 .. 23 * 2]? - In the expression: length [1 .. 23 * 2] - 4 A.hs:7:1: Warning: Top-level binding with no type signature: main :: IO () @@ -19,14 +19,14 @@ B.hs:4:1: Warning: Top-level binding with no type signature: answer_to_live_the_universe_and_everything :: Int -B.hs:5:12: Warning: +B.hs:5:13: Warning: Defaulting the following constraint(s) to type ?Integer? + (Num a0) arising from the literal ?1? at B.hs:5:13 (Enum a0) arising from the arithmetic sequence ?1 .. 23 * 2? at B.hs:5:12-20 - (Num a0) arising from the literal ?1? at B.hs:5:13 + In the expression: 1 In the first argument of ?length?, namely ?[1 .. 23 * 2]? In the first argument of ?(-)?, namely ?length [1 .. 23 * 2]? - In the expression: length [1 .. 23 * 2] - 4 A.hs:7:1: Warning: Top-level binding with no type signature: main :: IO () From git at git.haskell.org Mon Dec 2 13:33:40 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Dec 2013 13:33:40 +0000 (UTC) Subject: [commit: testsuite] master: Mark type-rep as broken until #5869 is fixed (7baefa8) Message-ID: <20131202133340.BF64C2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/testsuite On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7baefa874d858ec1dd8f875a46eb4be5a732875e/testsuite >--------------------------------------------------------------- commit 7baefa874d858ec1dd8f875a46eb4be5a732875e Author: Joachim Breitner Date: Mon Dec 2 13:06:29 2013 +0000 Mark type-rep as broken until #5869 is fixed >--------------------------------------------------------------- 7baefa874d858ec1dd8f875a46eb4be5a732875e tests/gadt/all.T | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/tests/gadt/all.T b/tests/gadt/all.T index d23d1fc..814b3e2 100644 --- a/tests/gadt/all.T +++ b/tests/gadt/all.T @@ -40,7 +40,7 @@ test('gadt23', test('gadt24', normal, compile, ['']) test('red-black', normal, compile, ['']) -test('type-rep', when(fast(), skip), compile_and_run, ['']) +test('type-rep', [ when(fast(), skip), expect_broken_for(8569, ['hpc','optasm','threaded2','dyn','optllvm']) ] , compile_and_run, ['']) test('equal', normal, compile, ['']) test('nbe', normal, compile, ['']) test('while', normal, compile_and_run, ['']) From git at git.haskell.org Mon Dec 2 13:33:42 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Dec 2013 13:33:42 +0000 (UTC) Subject: [commit: testsuite] master: Try to set flags for some tests involving TH right (4a8477b) Message-ID: <20131202133342.24C1E2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/testsuite On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4a8477b5ebf7acb7933370e392bfff29453821d8/testsuite >--------------------------------------------------------------- commit 4a8477b5ebf7acb7933370e392bfff29453821d8 Author: Joachim Breitner Date: Mon Dec 2 13:31:22 2013 +0000 Try to set flags for some tests involving TH right this tries to imporve upon 435c5955359d6e46a2fb905231678ac37ac0e71a. >--------------------------------------------------------------- 4a8477b5ebf7acb7933370e392bfff29453821d8 tests/plugins/all.T | 3 +-- tests/quasiquotation/all.T | 2 +- tests/rts/all.T | 2 +- 3 files changed, 3 insertions(+), 4 deletions(-) diff --git a/tests/plugins/all.T b/tests/plugins/all.T index 7e5f9b4..50406c3 100644 --- a/tests/plugins/all.T +++ b/tests/plugins/all.T @@ -34,7 +34,6 @@ test('plugins05', test('plugins06', [ extra_clean(['LinkerTicklingPlugin.hi', 'LinkerTicklingPlugin.o']), - unless(have_dynamic(),skip), only_ways([config.ghc_plugin_way]) ], - multimod_compile_and_run, ['plugins06', '-package ghc']) + multimod_compile_and_run, ['plugins06', '-package ghc ' + config.ghc_th_way_flags ]) diff --git a/tests/quasiquotation/all.T b/tests/quasiquotation/all.T index 5ccfc21..2173da6 100644 --- a/tests/quasiquotation/all.T +++ b/tests/quasiquotation/all.T @@ -11,7 +11,7 @@ test('T7918', [req_interp, extra_run_opts('"' + config.libdir + '"'), only_compiler_types(['ghc']), - only_ways(['normal']), + only_ways(config.ghc_th_way), unless(have_dynamic(),skip), extra_clean(['T7918A.hi', 'T7918A.o', 'T7918A.dyn_hi', 'T7918A.dyn_o', 'T7918B.hi', 'T7918B.o', 'T7918B.dyn_hi', 'T7918B.dyn_o'])], diff --git a/tests/rts/all.T b/tests/rts/all.T index d50798b..dfa0e89 100644 --- a/tests/rts/all.T +++ b/tests/rts/all.T @@ -185,7 +185,7 @@ test('ffishutdown', [ ignore_output, only_ways(['threaded1','threaded2']) ], com test('T7919', [extra_clean(['T7919A.o','T7919A.hi', 'T7919A.dyn_o','T7919A.dyn_hi']), when(fast(),skip) ], - compile_and_run, ['']) + compile_and_run, [config.ghc_th_way_flags]) test('T8035', normal, compile_and_run, ['']) From git at git.haskell.org Mon Dec 2 13:38:52 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Dec 2013 13:38:52 +0000 (UTC) Subject: [commit: testsuite] master: TH_import_loops fails for GHCi again (84b4e9b) Message-ID: <20131202133852.8F6D42406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/testsuite On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/84b4e9b4e2f1de48d573ec5035a687d318f7b651/testsuite >--------------------------------------------------------------- commit 84b4e9b4e2f1de48d573ec5035a687d318f7b651 Author: Joachim Breitner Date: Mon Dec 2 13:38:11 2013 +0000 TH_import_loops fails for GHCi again This reverts commit c0e50e9214b5ecb21435d7da70986d30d6128402 and is related to ticket #1012. >--------------------------------------------------------------- 84b4e9b4e2f1de48d573ec5035a687d318f7b651 tests/th/TH_import_loop/TH_import_loop.T | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/tests/th/TH_import_loop/TH_import_loop.T b/tests/th/TH_import_loop/TH_import_loop.T index 1e7cc56..8a4a180 100644 --- a/tests/th/TH_import_loop/TH_import_loop.T +++ b/tests/th/TH_import_loop/TH_import_loop.T @@ -4,7 +4,7 @@ setTestOpts(when(compiler_profiled(), skip)) test('TH_import_loop', [extra_clean(['ModuleA.o-boot', 'ModuleA.hi-boot', 'ModuleC.o', 'ModuleC.hi']), - expect_broken_for(1012, ['normal', 'hpc', 'optasm', 'threaded1', 'threaded2', 'dyn', 'optllvm'])], + expect_broken(1012)], multimod_compile_and_run, ['Main', '-v0']) From patrick at parcs.ath.cx Mon Dec 2 14:11:54 2013 From: patrick at parcs.ath.cx (Patrick Palka) Date: Mon, 2 Dec 2013 09:11:54 -0500 Subject: [commit: ghc] master: Respect the ordering of -package directives (574ccfa) In-Reply-To: <59543203684B2244980D7E4057D5FBC1486D9865@DB3EX14MBXC308.europe.corp.microsoft.com> References: <20131202023914.B5A612406B@ghc.haskell.org> <59543203684B2244980D7E4057D5FBC1486D9865@DB3EX14MBXC308.europe.corp.microsoft.com> Message-ID: On Mon, Dec 2, 2013 at 5:28 AM, Simon Peyton-Jones wrote: > Patrick > > Thanks! > > When you do something subtle like change 'foldM' to 'foldrM', could you add a comment to point out the subtlety? After all, by definition this was something that someone else missed. > > Simon Yes, will do. This commit was accidentally pushed and reverted shortly afterwards. Sorry about that. From git at git.haskell.org Mon Dec 2 15:44:14 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Dec 2013 15:44:14 +0000 (UTC) Subject: [commit: testsuite] master: Looks like plugin06 really only works with dynamic libraries enabled (cf499fe) Message-ID: <20131202154414.EC86A2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/testsuite On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/cf499fe916975ae9704aec8a39b2256491949ef3/testsuite >--------------------------------------------------------------- commit cf499fe916975ae9704aec8a39b2256491949ef3 Author: Joachim Breitner Date: Mon Dec 2 15:43:23 2013 +0000 Looks like plugin06 really only works with dynamic libraries enabled Otherwise we get ghc-stage2: panic! (the 'impossible' happened) (GHC version 7.7.20131202 for x86_64-unknown-linux): Static flags have not been initialised! Please call GHC.parseStaticFlags early enough. >--------------------------------------------------------------- cf499fe916975ae9704aec8a39b2256491949ef3 tests/plugins/all.T | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/tests/plugins/all.T b/tests/plugins/all.T index 50406c3..7e5f9b4 100644 --- a/tests/plugins/all.T +++ b/tests/plugins/all.T @@ -34,6 +34,7 @@ test('plugins05', test('plugins06', [ extra_clean(['LinkerTicklingPlugin.hi', 'LinkerTicklingPlugin.o']), + unless(have_dynamic(),skip), only_ways([config.ghc_plugin_way]) ], - multimod_compile_and_run, ['plugins06', '-package ghc ' + config.ghc_th_way_flags ]) + multimod_compile_and_run, ['plugins06', '-package ghc']) From git at git.haskell.org Mon Dec 2 17:35:44 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Dec 2013 17:35:44 +0000 (UTC) Subject: [commit: ghc] branch 'better-ho-cardinality' created Message-ID: <20131202173544.A179A2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : better-ho-cardinality Referencing: 20cc59419b5fae60eea9c81f56020ef15256dc84 From git at git.haskell.org Mon Dec 2 17:35:46 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Dec 2013 17:35:46 +0000 (UTC) Subject: [commit: ghc] better-ho-cardinality: Improve the handling of used-once stuff (20cc594) Message-ID: <20131202173546.C5C312406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : better-ho-cardinality Link : http://ghc.haskell.org/trac/ghc/changeset/20cc59419b5fae60eea9c81f56020ef15256dc84/ghc >--------------------------------------------------------------- commit 20cc59419b5fae60eea9c81f56020ef15256dc84 Author: Simon Peyton Jones Date: Fri Nov 22 17:13:05 2013 +0000 Improve the handling of used-once stuff Joachim and I are committing this onto a branch so that we can share it, but we expect to do a bit more work before merging it onto head. Nofib staus: - Most programs, no change - A few improve - A couple get worse (cacheprof, tak, rfib) Investigating the "get worse" set is what's holding up putting this on head. The major issue is this. Consider map (f g) ys where f's demand signature looks like f :: -> -> . So 'f' is not saturated. What demand do we place on g? Answer C(C1(U)) That is, the inner C1 should stay, even though f is not saturated. I found that this made a significant difference in the demand signatures inferred in GHC.IO, which uses lots of higher-order exception handlers. I also had to add used-once demand signatures for some of the 'catch' primops, so that we know their handlers are only called once. >--------------------------------------------------------------- 20cc59419b5fae60eea9c81f56020ef15256dc84 compiler/basicTypes/BasicTypes.lhs | 55 ++++++++ compiler/basicTypes/Demand.lhs | 251 ++++++++++++++++++------------------ compiler/basicTypes/Id.lhs | 64 ++++++--- compiler/basicTypes/IdInfo.lhs | 70 +++------- compiler/basicTypes/MkId.lhs | 3 +- compiler/coreSyn/CoreArity.lhs | 45 +++---- compiler/coreSyn/CoreUtils.lhs | 7 + compiler/coreSyn/PprCore.lhs | 33 +++-- compiler/prelude/PrelRules.lhs | 80 ++++++++++-- compiler/prelude/primops.txt.pp | 10 +- compiler/simplCore/OccurAnal.lhs | 63 +++++---- compiler/simplCore/SetLevels.lhs | 4 +- compiler/simplCore/SimplUtils.lhs | 19 ++- compiler/specialise/SpecConstr.lhs | 2 +- compiler/stranal/DmdAnal.lhs | 31 +++-- compiler/stranal/WorkWrap.lhs | 37 ++++-- compiler/stranal/WwLib.lhs | 64 ++++----- 17 files changed, 492 insertions(+), 346 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 20cc59419b5fae60eea9c81f56020ef15256dc84 From git at git.haskell.org Mon Dec 2 18:02:41 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Dec 2013 18:02:41 +0000 (UTC) Subject: [commit: testsuite] master: Test case about HyperStr and UseDemand (3cb91b3) Message-ID: <20131202180241.66CAC2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/testsuite On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3cb91b31449d4ddbe0cfba4e59e5da52cbd284bd/testsuite >--------------------------------------------------------------- commit 3cb91b31449d4ddbe0cfba4e59e5da52cbd284bd Author: Joachim Breitner Date: Mon Dec 2 18:02:10 2013 +0000 Test case about HyperStr and UseDemand which was used by SPJ to reduce my ignorance, so I want to ensure I do not break it. >--------------------------------------------------------------- 3cb91b31449d4ddbe0cfba4e59e5da52cbd284bd tests/stranal/sigs/HyperStrUse.hs | 9 +++++++++ tests/stranal/sigs/all.T | 1 + 2 files changed, 10 insertions(+) diff --git a/tests/stranal/sigs/HyperStrUse.hs b/tests/stranal/sigs/HyperStrUse.hs new file mode 100644 index 0000000..88ba3e3 --- /dev/null +++ b/tests/stranal/sigs/HyperStrUse.hs @@ -0,0 +1,9 @@ +{-# OPTIONS_GHC -fplugin StrAnalAnnotation #-} +module HyperStrUse where + +import StrAnalAnnotation (StrAnal(StrAnal)) + +f :: (Int, Int) -> Bool -> Int +f (x,y) True = error (show x) +f (x,y) False = x +1 +{-# ANN f (StrAnal "m") #-} diff --git a/tests/stranal/sigs/all.T b/tests/stranal/sigs/all.T index 74ddd9f..4080eb9 100644 --- a/tests/stranal/sigs/all.T +++ b/tests/stranal/sigs/all.T @@ -17,4 +17,5 @@ setTestOpts(only_ways(['optasm'])) test('StrAnalExample', normal, compile, ['--make -package ghc -v0 ' + config.ghc_th_way_flags]) test('T8569', expect_broken(8569), compile, ['--make -package ghc -v0 ' + config.ghc_th_way_flags]) +test('HyperStrUse', normal, compile, ['--make -package ghc -v0 ' + config.ghc_th_way_flags]) From git at git.haskell.org Mon Dec 2 18:13:53 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Dec 2013 18:13:53 +0000 (UTC) Subject: [commit: ghc] master: Remove dead code orphaned by implementing GND with `coerce`. (3fecf81) Message-ID: <20131202181353.87ACC2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3fecf81ee414799847d43f9aa71d830b87facaa6/ghc >--------------------------------------------------------------- commit 3fecf81ee414799847d43f9aa71d830b87facaa6 Author: Richard Eisenberg Date: Tue Nov 26 09:52:12 2013 -0500 Remove dead code orphaned by implementing GND with `coerce`. >--------------------------------------------------------------- 3fecf81ee414799847d43f9aa71d830b87facaa6 compiler/deSugar/DsBinds.lhs | 3 --- compiler/typecheck/TcDeriv.lhs | 29 ----------------------------- compiler/typecheck/TcEvidence.lhs | 16 +--------------- compiler/typecheck/TcHsSyn.lhs | 1 - compiler/types/Coercion.lhs | 17 +---------------- 5 files changed, 2 insertions(+), 64 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 3fecf81ee414799847d43f9aa71d830b87facaa6 From git at git.haskell.org Mon Dec 2 18:13:55 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Dec 2013 18:13:55 +0000 (UTC) Subject: [commit: ghc] master: Rejig rejigConRes & friends, doing role checks in a second pass. (4067340) Message-ID: <20131202181355.A92E02406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/406734066ea536b5d11373335edb8c24d0aa0834/ghc >--------------------------------------------------------------- commit 406734066ea536b5d11373335edb8c24d0aa0834 Author: Richard Eisenberg Date: Sat Nov 30 16:05:47 2013 -0500 Rejig rejigConRes & friends, doing role checks in a second pass. This commit is just a refactoring, intended to make the use of rejigConRes (which sorts out the return types of GADT-like constructors) less delicate. The idea is that, if we perform role checking in a second top-level pass, we can use checkValidDataCon to check for valid return types. Previously, checking roles would force the rejigConRes thunk before we knew that rejigConRes was safe to call! >--------------------------------------------------------------- 406734066ea536b5d11373335edb8c24d0aa0834 compiler/typecheck/TcEvidence.lhs | 1 - compiler/typecheck/TcInstDcls.lhs | 26 +-- compiler/typecheck/TcTyClsDecls.lhs | 442 ++++++++++++++++++----------------- compiler/typecheck/TcTyDecls.lhs | 5 +- 4 files changed, 240 insertions(+), 234 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 406734066ea536b5d11373335edb8c24d0aa0834 From git at git.haskell.org Mon Dec 2 18:13:57 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Dec 2013 18:13:57 +0000 (UTC) Subject: [commit: ghc] master: Fix location of spliced-in role annotations. (b84fff3) Message-ID: <20131202181357.E4A462406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b84fff3d975e4b6b9a6b89ba43f405ed708dec12/ghc >--------------------------------------------------------------- commit b84fff3d975e4b6b9a6b89ba43f405ed708dec12 Author: Richard Eisenberg Date: Mon Dec 2 13:02:08 2013 -0500 Fix location of spliced-in role annotations. >--------------------------------------------------------------- b84fff3d975e4b6b9a6b89ba43f405ed708dec12 compiler/hsSyn/Convert.lhs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/hsSyn/Convert.lhs b/compiler/hsSyn/Convert.lhs index e789d17..216ab22 100644 --- a/compiler/hsSyn/Convert.lhs +++ b/compiler/hsSyn/Convert.lhs @@ -271,7 +271,7 @@ cvtDec (ClosedTypeFamilyD tc tyvars mkind eqns) cvtDec (TH.RoleAnnotD tc roles) = do { tc' <- tconNameL tc ; let roles' = map (noLoc . cvtRole) roles - ; return $ noLoc $ Hs.RoleAnnotD (RoleAnnotDecl tc' roles') } + ; returnL $ Hs.RoleAnnotD (RoleAnnotDecl tc' roles') } ---------------- cvtTySynEqn :: Located RdrName -> TySynEqn -> CvtM (LTyFamInstEqn RdrName) cvtTySynEqn tc (TySynEqn lhs rhs) From git at git.haskell.org Mon Dec 2 18:14:11 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Dec 2013 18:14:11 +0000 (UTC) Subject: [commit: testsuite] master: Wibbles to output caused by change in checking role annotations (6741cfd) Message-ID: <20131202181411.6FDC32406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/testsuite On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6741cfd2829b5baebe5e3bd8919f0d52bd01553d/testsuite >--------------------------------------------------------------- commit 6741cfd2829b5baebe5e3bd8919f0d52bd01553d Author: Richard Eisenberg Date: Mon Dec 2 13:12:36 2013 -0500 Wibbles to output caused by change in checking role annotations >--------------------------------------------------------------- 6741cfd2829b5baebe5e3bd8919f0d52bd01553d tests/gadt/gadt11.stderr | 2 +- tests/indexed-types/should_fail/T8368.stderr | 2 +- tests/roles/should_fail/Roles11.stderr | 4 ++-- tests/roles/should_fail/Roles5.stderr | 2 ++ tests/roles/should_fail/Roles6.stderr | 11 +---------- tests/th/TH_Roles1.stderr | 1 + tests/typecheck/should_fail/T7175.stderr | 2 +- tests/typecheck/should_fail/tcfail155.stderr | 2 +- tests/typecheck/should_fail/tcfail176.stderr | 2 +- 9 files changed, 11 insertions(+), 17 deletions(-) diff --git a/tests/gadt/gadt11.stderr b/tests/gadt/gadt11.stderr index c2e63f0..b753bd9 100644 --- a/tests/gadt/gadt11.stderr +++ b/tests/gadt/gadt11.stderr @@ -1,6 +1,6 @@ gadt11.hs:12:3: Data constructor ?L2? returns type ?T1 Bool? - instead of an instance of its parent type ?T2? + instead of an instance of its parent type ?T2 a? In the definition of data constructor ?L2? In the data declaration for ?T2? diff --git a/tests/indexed-types/should_fail/T8368.stderr b/tests/indexed-types/should_fail/T8368.stderr index b767489..2ff63d7 100644 --- a/tests/indexed-types/should_fail/T8368.stderr +++ b/tests/indexed-types/should_fail/T8368.stderr @@ -1,6 +1,6 @@ T8368.hs:9:3: Data constructor ?MkFam? returns type ?Foo? - instead of an instance of its parent type ?Fam? + instead of an instance of its parent type ?Fam a? In the definition of data constructor ?MkFam? In the data instance declaration for ?Fam? diff --git a/tests/roles/should_fail/Roles11.stderr b/tests/roles/should_fail/Roles11.stderr index ee15f99..55ef3bd 100644 --- a/tests/roles/should_fail/Roles11.stderr +++ b/tests/roles/should_fail/Roles11.stderr @@ -1,5 +1,5 @@ -Roles11.hs:6:1: +Roles11.hs:5:1: Role mismatch on variable a: Annotation says representational but role nominal is required - In the data declaration for ?T2? + while checking a role annotation for ?T2? diff --git a/tests/roles/should_fail/Roles5.stderr b/tests/roles/should_fail/Roles5.stderr index c4907c8..20172ff 100644 --- a/tests/roles/should_fail/Roles5.stderr +++ b/tests/roles/should_fail/Roles5.stderr @@ -2,10 +2,12 @@ Roles5.hs:7:1: Illegal role annotation for T; did you intend to use RoleAnnotations? + while checking a role annotation for ?T? Roles5.hs:8:1: Illegal role annotation for C; did you intend to use RoleAnnotations? + while checking a role annotation for ?C? Roles5.hs:9:1: Illegal role annotation for S; diff --git a/tests/roles/should_fail/Roles6.stderr b/tests/roles/should_fail/Roles6.stderr index 3cca04d..9f09ab3 100644 --- a/tests/roles/should_fail/Roles6.stderr +++ b/tests/roles/should_fail/Roles6.stderr @@ -1,15 +1,6 @@ -Roles6.hs:5:1: - Role mismatch on variable a: - Annotation says nominal but role representational is required - In the data declaration for ?Foo? - -Roles6.hs:5:1: - Role mismatch on variable b: - Annotation says representational but role nominal is required - In the data declaration for ?Foo? - Roles6.hs:7:1: Wrong number of roles listed in role annotation; Expected 2, got 3: type role Foo nominal representational phantom + while checking a role annotation for ?Foo? diff --git a/tests/th/TH_Roles1.stderr b/tests/th/TH_Roles1.stderr index 47105b2..f819da1 100644 --- a/tests/th/TH_Roles1.stderr +++ b/tests/th/TH_Roles1.stderr @@ -2,3 +2,4 @@ TH_Roles1.hs:7:4: Illegal role annotation for T; did you intend to use RoleAnnotations? + while checking a role annotation for ?T? diff --git a/tests/typecheck/should_fail/T7175.stderr b/tests/typecheck/should_fail/T7175.stderr index f6adfff..e65918c 100644 --- a/tests/typecheck/should_fail/T7175.stderr +++ b/tests/typecheck/should_fail/T7175.stderr @@ -1,6 +1,6 @@ T7175.hs:8:4: Data constructor ?G1C? returns type ?F Int? - instead of an instance of its parent type ?G1? + instead of an instance of its parent type ?G1 a? In the definition of data constructor ?G1C? In the data declaration for ?G1? diff --git a/tests/typecheck/should_fail/tcfail155.stderr b/tests/typecheck/should_fail/tcfail155.stderr index 15d6d69..58426f4 100644 --- a/tests/typecheck/should_fail/tcfail155.stderr +++ b/tests/typecheck/should_fail/tcfail155.stderr @@ -1,6 +1,6 @@ tcfail155.hs:8:6: Data constructor ?P? returns type ?L2? - instead of an instance of its parent type ?T? + instead of an instance of its parent type ?T a? In the definition of data constructor ?P? In the data declaration for ?T? diff --git a/tests/typecheck/should_fail/tcfail176.stderr b/tests/typecheck/should_fail/tcfail176.stderr index c19885a..cb829b4 100644 --- a/tests/typecheck/should_fail/tcfail176.stderr +++ b/tests/typecheck/should_fail/tcfail176.stderr @@ -1,6 +1,6 @@ tcfail176.hs:7:21: Data constructor ?Bug? returns type ?Maybe a? - instead of an instance of its parent type ?Bug? + instead of an instance of its parent type ?Bug a? In the definition of data constructor ?Bug? In the newtype declaration for ?Bug? From git at git.haskell.org Mon Dec 2 19:17:35 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Dec 2013 19:17:35 +0000 (UTC) Subject: [commit: ghc] master: Move FunDeps to typecheck (90588c1) Message-ID: <20131202191735.DCD722406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/90588c1f70fa3bf1ae32aa9a25f93800580126d8/ghc >--------------------------------------------------------------- commit 90588c1f70fa3bf1ae32aa9a25f93800580126d8 Author: Joachim Breitner Date: Mon Dec 2 17:53:23 2013 +0000 Move FunDeps to typecheck That?s where all its users are... >--------------------------------------------------------------- 90588c1f70fa3bf1ae32aa9a25f93800580126d8 compiler/{types => typecheck}/FunDeps.lhs | 0 1 file changed, 0 insertions(+), 0 deletions(-) diff --git a/compiler/types/FunDeps.lhs b/compiler/typecheck/FunDeps.lhs similarity index 100% rename from compiler/types/FunDeps.lhs rename to compiler/typecheck/FunDeps.lhs From git at git.haskell.org Mon Dec 2 19:17:37 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Dec 2013 19:17:37 +0000 (UTC) Subject: [commit: ghc] master: Note [HyperStr and Use demands] (cb17c1f) Message-ID: <20131202191738.1AE432406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/cb17c1fd7d45f18029be8e8e5e07e4d8fc4f36a9/ghc >--------------------------------------------------------------- commit cb17c1fd7d45f18029be8e8e5e07e4d8fc4f36a9 Author: Joachim Breitner Date: Mon Dec 2 18:03:52 2013 +0000 Note [HyperStr and Use demands] This note is a summary of an explanation by SPJ to me. >--------------------------------------------------------------- cb17c1fd7d45f18029be8e8e5e07e4d8fc4f36a9 compiler/basicTypes/Demand.lhs | 14 ++++++++++++++ 1 file changed, 14 insertions(+) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 796c7cd..8afc4f8 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -86,6 +86,7 @@ import DataCon ( splitDataProductType_maybe ) data StrDmd = HyperStr -- Hyper-strict -- Bottom of the lattice + -- Note [HyperStr and Use demands] | SCall StrDmd -- Call demand -- Used only for values of function type @@ -1451,6 +1452,19 @@ strictifyDictDmd ty dmd = case absd dmd of _ -> dmd -- unused or not a dictionary \end{code} +Note [HyperStr and Use demands] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + +The information "HyperStr" needs to be in the strictness signature, and not in +the demand signature, becuase we still want to know about the demand on things. Consider + + f (x,y) True = error (show x) + f (x,y) False = x+1 + +The signature of f should be m. If we were not +distinguishing the uses on x and y in the True case, we could either not figure +out how deeply we can unpack x, or that we do not have to pass y. + %************************************************************************ %* * From git at git.haskell.org Mon Dec 2 22:07:07 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 2 Dec 2013 22:07:07 +0000 (UTC) Subject: [commit: ghc] master: Some popular typos in comments (0fe399c) Message-ID: <20131202220709.37E762406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0fe399c965138ef9e25a1f20392c40d09885ae7c/ghc >--------------------------------------------------------------- commit 0fe399c965138ef9e25a1f20392c40d09885ae7c Author: Gabor Greif Date: Mon Dec 2 23:05:43 2013 +0100 Some popular typos in comments >--------------------------------------------------------------- 0fe399c965138ef9e25a1f20392c40d09885ae7c compiler/basicTypes/Demand.lhs | 2 +- compiler/ghci/RtClosureInspect.hs | 2 +- compiler/typecheck/TcDeriv.lhs | 2 +- compiler/typecheck/TcInteract.lhs | 4 ++-- 4 files changed, 5 insertions(+), 5 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 8afc4f8..42590c9 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -1456,7 +1456,7 @@ Note [HyperStr and Use demands] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ The information "HyperStr" needs to be in the strictness signature, and not in -the demand signature, becuase we still want to know about the demand on things. Consider +the demand signature, because we still want to know about the demand on things. Consider f (x,y) True = error (show x) f (x,y) False = x+1 diff --git a/compiler/ghci/RtClosureInspect.hs b/compiler/ghci/RtClosureInspect.hs index 277e45f..eb1c644 100644 --- a/compiler/ghci/RtClosureInspect.hs +++ b/compiler/ghci/RtClosureInspect.hs @@ -694,7 +694,7 @@ cvObtainTerm hsc_env max_depth force old_ty hval = runTR hsc_env $ do dflags = hsc_dflags hsc_env go :: Int -> Type -> Type -> HValue -> TcM Term - -- I belive that my_ty should not have any enclosing + -- I believe that my_ty should not have any enclosing -- foralls, nor any free RuntimeUnk skolems; -- that is partly what the quantifyType stuff achieved -- diff --git a/compiler/typecheck/TcDeriv.lhs b/compiler/typecheck/TcDeriv.lhs index 6789f44..73137b0 100644 --- a/compiler/typecheck/TcDeriv.lhs +++ b/compiler/typecheck/TcDeriv.lhs @@ -618,7 +618,7 @@ deriveTyData tvs tc tc_args (L loc deriv_pred) -- The "deriv_pred" is a LHsType to take account of the fact that for -- newtype deriving we allow deriving (forall a. C [a]). - -- Typeable is special, becuase Typeable :: forall k. k -> Constraint + -- Typeable is special, because Typeable :: forall k. k -> Constraint -- so the argument kind 'k' is not decomposable by splitKindFunTys -- as is the case for all other derivable type classes ; if className cls == typeableClassName diff --git a/compiler/typecheck/TcInteract.lhs b/compiler/typecheck/TcInteract.lhs index 1324265..f2289b1 100644 --- a/compiler/typecheck/TcInteract.lhs +++ b/compiler/typecheck/TcInteract.lhs @@ -634,7 +634,7 @@ xi_w). Note [Carefully solve the right CFunEqCan] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ---- OLD COMMENT, NOW NOT NEEDED - ---- becuase we now allow multiple + ---- because we now allow multiple ---- wanted FunEqs with the same head Consider the constraints c1 :: F Int ~ a -- Arising from an application line 5 @@ -1555,7 +1555,7 @@ Note [Cached solved FunEqs] When trying to solve, say (FunExpensive big-type ~ ty), it's important to see if we have reduced (FunExpensive big-type) before, lest we simply repeat it. Hence the lookup in inert_solved_funeqs. Moreover -we must use `canRewriteOrSame` becuase both uses might (say) be Wanteds, +we must use `canRewriteOrSame` because both uses might (say) be Wanteds, and we *still* want to save the re-computation. Note [MATCHING-SYNONYMS] From git at git.haskell.org Tue Dec 3 10:26:42 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Dec 2013 10:26:42 +0000 (UTC) Subject: [commit: packages/process] master: Make `cleanupProcess` resistant to SIGPIPE (776a260) Message-ID: <20131203102642.E8DB02406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/776a260be009cc27cfeacf298934d544c4e87408/process >--------------------------------------------------------------- commit 776a260be009cc27cfeacf298934d544c4e87408 Author: Herbert Valerio Riedel Date: Sun Dec 1 11:15:44 2013 +0100 Make `cleanupProcess` resistant to SIGPIPE Otherwise, `cleanupProcess` may exit prematurely if trying to flush out data to the process' stdin handle even though the endpoint has already vanished, and fail to complete the cleanup process. See also 228297ec53e9ee7a1a6a3c5964ca7e89a6474c9b and #2233. Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- 776a260be009cc27cfeacf298934d544c4e87408 System/Process.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/System/Process.hs b/System/Process.hs index f8b0b7f..7f76666 100644 --- a/System/Process.hs +++ b/System/Process.hs @@ -259,7 +259,7 @@ cleanupProcess (mb_stdin, mb_stdout, mb_stderr, ph) = do -- Note, it's important that other threads that might be reading/writing -- these handles also get killed off, since otherwise they might be holding -- the handle lock and prevent us from closing, leading to deadlock. - maybe (return ()) hClose mb_stdin + maybe (return ()) (ignoreSigPipe . hClose) mb_stdin maybe (return ()) hClose mb_stdout maybe (return ()) hClose mb_stderr -- terminateProcess does not guarantee that it terminates the process. From git at git.haskell.org Tue Dec 3 10:26:44 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Dec 2013 10:26:44 +0000 (UTC) Subject: [commit: packages/process] master: Add Haddock note to `call{Command, Process}` wrt execptions (#2233) (edda1be) Message-ID: <20131203102644.E43C92406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/edda1be660d07b461da75b2dfacc3d5820b4d084/process >--------------------------------------------------------------- commit edda1be660d07b461da75b2dfacc3d5820b4d084 Author: Herbert Valerio Riedel Date: Sun Dec 1 11:21:19 2013 +0100 Add Haddock note to `call{Command,Process}` wrt execptions (#2233) This also tweaks Haddock comments & markup in "System.Process" while at it. Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- edda1be660d07b461da75b2dfacc3d5820b4d084 System/Process.hs | 69 ++++++++++++++++++++++++++++++++--------------------- 1 file changed, 42 insertions(+), 27 deletions(-) diff --git a/System/Process.hs b/System/Process.hs index 7f76666..26dab2a 100644 --- a/System/Process.hs +++ b/System/Process.hs @@ -121,21 +121,25 @@ import Hugs.System -- | Construct a 'CreateProcess' record for passing to 'createProcess', -- representing a raw command with arguments. -- --- The @FilePath@ names the executable, and is interpreted according +-- The 'FilePath' argument names the executable, and is interpreted according -- to the platform's standard policy for searching for -- executables. Specifically: -- --- * on Unix systems the @execvp@ semantics is used, where if the --- filename does not contain a slash (@/@) then the @PATH@ --- environment variable is searched for the executable. +-- * on Unix systems the +-- +-- semantics is used, where if the executable filename does not +-- contain a slash (@/@) then the @PATH@ environment variable is +-- searched for the executable. -- -- * on Windows systems the Win32 @CreateProcess@ semantics is used. -- Briefly: if the filename does not contain a path, then the -- directory containing the parent executable is searched, followed --- by the current directory, then some some standard locations, and +-- by the current directory, then some standard locations, and -- finally the current @PATH at . An @.exe@ extension is added if the -- filename does not already have an extension. For full details --- see the documentation for the Windows @SearchPath@ API. +-- see the +-- +-- for the Windows @SearchPath@ API. proc :: FilePath -> [String] -> CreateProcess proc cmd args = CreateProcess { cmdspec = RawCommand cmd args, @@ -174,16 +178,16 @@ The details of how to create the process are passed in the fill in the fields with default values which can be overriden as needed. -'createProcess' returns @(mb_stdin_hdl, mb_stdout_hdl, mb_stderr_hdl, p)@, +'createProcess' returns @(/mb_stdin_hdl/, /mb_stdout_hdl/, /mb_stderr_hdl/, /ph/)@, where - * if @std_in == CreatePipe@, then @mb_stdin_hdl@ will be @Just h@, - where @h@ is the write end of the pipe connected to the child + * if @'std_in' == 'CreatePipe'@, then @/mb_stdin_hdl/@ will be @Just /h/@, + where @/h/@ is the write end of the pipe connected to the child process's @stdin at . - * otherwise, @mb_stdin_hdl == Nothing@ + * otherwise, @/mb_stdin_hdl/ == Nothing@ -Similarly for @mb_stdout_hdl@ and @mb_stderr_hdl at . +Similarly for @/mb_stdout_hdl/@ and @/mb_stderr_hdl/@. For example, to execute a simple @ls@ command: @@ -263,7 +267,7 @@ cleanupProcess (mb_stdin, mb_stdout, mb_stderr, ph) = do maybe (return ()) hClose mb_stdout maybe (return ()) hClose mb_stderr -- terminateProcess does not guarantee that it terminates the process. - -- Indeed on unix it's SIGTERM, which asks nicely but does not guarantee + -- Indeed on Unix it's SIGTERM, which asks nicely but does not guarantee -- that it stops. If it doesn't stop, we don't want to hang, so we wait -- asynchronously using forkIO. _ <- forkIO (waitForProcess ph >> return ()) @@ -300,6 +304,11 @@ spawnCommand cmd = do -- arguments, and wait for it to finish. If the command returns a non-zero -- exit code, an exception is raised. -- +-- If an asynchronous exception is thrown to the thread executing +-- @callProcess at . The forked process will be terminated and +-- @callProcess@ will wait (block) until the process has been +-- terminated. +-- -- /Since: 1.2.0.0/ callProcess :: FilePath -> [String] -> IO () callProcess cmd args = do @@ -313,6 +322,11 @@ callProcess cmd args = do -- | Creates a new process to run the specified shell command. If the -- command returns a non-zero exit code, an exception is raised. -- +-- If an asynchronous exception is thrown to the thread executing +-- @callCommand at . The forked process will be terminated and +-- @callCommand@ will wait (block) until the process has been +-- terminated. +-- -- /Since: 1.2.0.0/ callCommand :: String -> IO () callCommand cmd = do @@ -366,7 +380,7 @@ processFailedException fun cmd args exit_code = -- -- In addition, in 'delegate_ctlc' mode, 'waitForProcess' and -- 'getProcessExitCode' will throw a 'UserInterrupt' exception if the process --- terminated with @ExitFailure (-SIGINT)@. Typically you will not want to +-- terminated with @'ExitFailure' (-SIGINT)@. Typically you will not want to -- catch this exception, but let it propagate, giving a normal orderly shutdown. -- One detail to be aware of is that the 'UserInterrupt' exception is thrown -- /synchronously/ in the thread that calls 'waitForProcess', whereas normally @@ -374,10 +388,10 @@ processFailedException fun cmd args exit_code = -- thread. -- -- For even more detail on this topic, see --- . +-- . -- ----------------------------------------------------------------------------- --- + -- | @readProcess@ forks an external process, reads its standard output -- strictly, blocking until the process terminates, and returns the output -- string. @@ -531,9 +545,9 @@ ignoreSigPipe = id -- ---------------------------------------------------------------------------- -- showCommandForUser --- | Given a program @p@ and arguments @args@, --- @showCommandForUser p args@ returns a string suitable for pasting --- into sh (on POSIX OSs) or cmd.exe (on Windows). +-- | Given a program @/p/@ and arguments @/args/@, +-- @showCommandForUser /p/ /args/@ returns a string suitable for pasting +-- into @\/bin\/sh@ (on Unix systems) or @CMD.EXE@ (on Windows). showCommandForUser :: FilePath -> [String] -> String showCommandForUser cmd args = unwords (map translate (cmd : args)) @@ -843,16 +857,17 @@ runInteractiveProcess1 fun cmd = do Computation @system cmd@ returns the exit code produced when the operating system runs the shell command @cmd at . -This computation may fail with +This computation may fail with one of the following +'System.IO.Error.IOErrorType' exceptions: - * @PermissionDenied@: The process has insufficient privileges to - perform the operation. +[@PermissionDenied@] +The process has insufficient privileges to perform the operation. - * @ResourceExhausted@: Insufficient resources are available to - perform the operation. +[@ResourceExhausted@] +Insufficient resources are available to perform the operation. - * @UnsupportedOperation@: The implementation does not support - system calls. +[@UnsupportedOperation@] +The implementation does not support system calls. On Windows, 'system' passes the command to the Windows command interpreter (@CMD.EXE@ or @COMMAND.COM@), hence Unixy shell tricks @@ -873,8 +888,8 @@ system str = do --TODO: in a later release {-# DEPRECATED rawSystem "Use 'callProcess' (or 'spawnProcess' and 'waitForProcess') instead" #-} {-| -The computation @'rawSystem' cmd args@ runs the operating system command - at cmd@ in such a way that it receives as arguments the @args@ strings +The computation @'rawSystem' /cmd/ /args/@ runs the operating system command +@/cmd/@ in such a way that it receives as arguments the @/args/@ strings exactly as given, with no funny escaping or shell meta-syntax expansion. It will therefore behave more portably between operating systems than 'system'. From git at git.haskell.org Tue Dec 3 10:26:46 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Dec 2013 10:26:46 +0000 (UTC) Subject: [commit: packages/process] master: Minor update to changelog file (b2f1133) Message-ID: <20131203102646.EAC602406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/process On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b2f11335b5fcc0e5b421f16da78f11c558eba574/process >--------------------------------------------------------------- commit b2f11335b5fcc0e5b421f16da78f11c558eba574 Author: Herbert Valerio Riedel Date: Sun Dec 1 11:25:04 2013 +0100 Minor update to changelog file Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- b2f11335b5fcc0e5b421f16da78f11c558eba574 changelog | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/changelog b/changelog index 15b04e8..1409eea 100644 --- a/changelog +++ b/changelog @@ -1,4 +1,4 @@ -1.2.0.0 Nov 2013 +1.2.0.0 Dec 2013 * Update to Cabal 1.10 format * Remove NHC specific code @@ -11,5 +11,5 @@ a signal. * Deprecate `module System.Cmd` * On non-Windows, the child thread now comunicates any errors back - to the parent thread via pipes. + to the parent thread via pipes. * Fix deadlocks in `readProcess` and `readProcessWithExitCode` From git at git.haskell.org Tue Dec 3 13:27:58 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Dec 2013 13:27:58 +0000 (UTC) Subject: [commit: ghc] master: Refactor: Origin of inferred Thetas (51bebb7) Message-ID: <20131203132759.1A09B2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/51bebb7c324d2572d5a299f950c09dc4d21cd271/ghc >--------------------------------------------------------------- commit 51bebb7c324d2572d5a299f950c09dc4d21cd271 Author: Joachim Breitner Date: Mon Dec 2 19:16:08 2013 +0000 Refactor: Origin of inferred Thetas When doing non-standalone deriving, annotate each individual unsimplified constraint with its own CtOrigin. This is just the refactoring, so the CtOrigin is still CtDeriv in each case. >--------------------------------------------------------------- 51bebb7c324d2572d5a299f950c09dc4d21cd271 compiler/typecheck/TcDeriv.lhs | 260 ++++++++++++++++++++++++---------------- compiler/typecheck/TcMType.lhs | 22 ++-- 2 files changed, 168 insertions(+), 114 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 51bebb7c324d2572d5a299f950c09dc4d21cd271 From git at git.haskell.org Tue Dec 3 13:28:01 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Dec 2013 13:28:01 +0000 (UTC) Subject: [commit: ghc] master: Elaborate "deriving" error messages (4025d66) Message-ID: <20131203132801.505AD2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4025d66cc795b728f745aec23fc5c2267d1839f0/ghc >--------------------------------------------------------------- commit 4025d66cc795b728f745aec23fc5c2267d1839f0 Author: Joachim Breitner Date: Tue Dec 3 10:42:55 2013 +0000 Elaborate "deriving" error messages If "deriving (C)" fails, it will now, if possible, indicate which particular field of which constructor has caused the failure. (This fixes #8576) >--------------------------------------------------------------- 4025d66cc795b728f745aec23fc5c2267d1839f0 compiler/typecheck/TcDeriv.lhs | 10 ++++++---- compiler/typecheck/TcErrors.lhs | 5 +++-- compiler/typecheck/TcRnTypes.lhs | 8 +++++++- 3 files changed, 16 insertions(+), 7 deletions(-) diff --git a/compiler/typecheck/TcDeriv.lhs b/compiler/typecheck/TcDeriv.lhs index 5931652..49111a9 100644 --- a/compiler/typecheck/TcDeriv.lhs +++ b/compiler/typecheck/TcDeriv.lhs @@ -1049,11 +1049,13 @@ inferConstraints cls inst_tys rep_tc rep_tc_args where -- Constraints arising from the arguments of each constructor con_arg_constraints cls' get_constrained_tys - = [ mkPredOrigin DerivOrigin (mkClassPred cls' [arg_ty]) + = [ mkPredOrigin (DerivOriginDC data_con arg_n) (mkClassPred cls' [arg_ty]) | data_con <- tyConDataCons rep_tc, - arg_ty <- ASSERT( isVanillaDataCon data_con ) - get_constrained_tys $ - dataConInstOrigArgTys data_con all_rep_tc_args, + (arg_n, arg_ty) <- + ASSERT( isVanillaDataCon data_con ) + zip [1..] $ + get_constrained_tys $ + dataConInstOrigArgTys data_con all_rep_tc_args, not (isUnLiftedType arg_ty) ] -- No constraints for unlifted types -- See Note [Deriving and unboxed types] diff --git a/compiler/typecheck/TcErrors.lhs b/compiler/typecheck/TcErrors.lhs index 83d38da..e0be85f 100644 --- a/compiler/typecheck/TcErrors.lhs +++ b/compiler/typecheck/TcErrors.lhs @@ -1049,8 +1049,9 @@ mk_dict_err ctxt (ct, (matches, unifiers, safe_haskell)) = ptext (sLit "Could not deduce") <+> pprParendType pred drv_fixes = case orig of - DerivOrigin -> [drv_fix] - _ -> [] + DerivOrigin -> [drv_fix] + DerivOriginDC {} -> [drv_fix] + _ -> [] drv_fix = hang (ptext (sLit "use a standalone 'deriving instance' declaration,")) 2 (ptext (sLit "so you can specify the instance context yourself")) diff --git a/compiler/typecheck/TcRnTypes.lhs b/compiler/typecheck/TcRnTypes.lhs index 9fc2ceb..1b38378 100644 --- a/compiler/typecheck/TcRnTypes.lhs +++ b/compiler/typecheck/TcRnTypes.lhs @@ -90,7 +90,7 @@ import TcEvidence import Type import Class ( Class ) import TyCon ( TyCon ) -import DataCon ( DataCon, dataConUserType ) +import DataCon ( DataCon, dataConUserType, dataConOrigArgTys ) import TcType import Annotations import InstEnv @@ -1779,6 +1779,8 @@ data CtOrigin | ScOrigin -- Typechecking superclasses of an instance declaration | DerivOrigin -- Typechecking deriving + | DerivOriginDC DataCon Int + -- Checking constraings arising from this data an and field index | StandAloneDerivOrigin -- Typechecking stand-alone deriving | DefaultOrigin -- Typechecking a default decl | DoOrigin -- Arising from a do expression @@ -1816,6 +1818,10 @@ pprO TupleOrigin = ptext (sLit "a tuple") pprO NegateOrigin = ptext (sLit "a use of syntactic negation") pprO ScOrigin = ptext (sLit "the superclasses of an instance declaration") pprO DerivOrigin = ptext (sLit "the 'deriving' clause of a data type declaration") +pprO (DerivOriginDC dc n) = hsep [ ptext (sLit "the"), speakNth n, + ptext (sLit "field of"), quotes (ppr dc), + parens (ptext (sLit "type") <+> quotes (ppr ty)) ] + where ty = dataConOrigArgTys dc !! (n-1) pprO StandAloneDerivOrigin = ptext (sLit "a 'deriving' declaration") pprO DefaultOrigin = ptext (sLit "a 'default' declaration") pprO DoOrigin = ptext (sLit "a do statement") From git at git.haskell.org Tue Dec 3 13:28:14 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Dec 2013 13:28:14 +0000 (UTC) Subject: [commit: testsuite] master: Update output: New error messages as per #8576 (b3b88db) Message-ID: <20131203132814.D4C782406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/testsuite On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b3b88db924f39d83586f41cf35608bc4809b2a9a/testsuite >--------------------------------------------------------------- commit b3b88db924f39d83586f41cf35608bc4809b2a9a Author: Joachim Breitner Date: Tue Dec 3 10:42:19 2013 +0000 Update output: New error messages as per #8576 >--------------------------------------------------------------- b3b88db924f39d83586f41cf35608bc4809b2a9a tests/deriving/should_fail/T2851.stderr | 2 +- tests/deriving/should_fail/drvfail-functor2.stderr | 2 +- tests/deriving/should_fail/drvfail001.stderr | 2 +- tests/deriving/should_fail/drvfail002.stderr | 2 +- tests/deriving/should_fail/drvfail003.stderr | 2 +- tests/deriving/should_fail/drvfail007.stderr | 2 +- tests/deriving/should_fail/drvfail013.stderr | 2 +- tests/typecheck/should_fail/tcfail046.stderr | 4 ++-- tests/typecheck/should_fail/tcfail118.stderr | 2 +- tests/typecheck/should_fail/tcfail169.stderr | 2 +- 10 files changed, 11 insertions(+), 11 deletions(-) diff --git a/tests/deriving/should_fail/T2851.stderr b/tests/deriving/should_fail/T2851.stderr index 70802ab..c7a3bf5 100644 --- a/tests/deriving/should_fail/T2851.stderr +++ b/tests/deriving/should_fail/T2851.stderr @@ -1,7 +1,7 @@ T2851.hs:9:15: No instance for (Show (F a)) - arising from the 'deriving' clause of a data type declaration + arising from the first field of ?D? (type ?F a?) Possible fix: use a standalone 'deriving instance' declaration, so you can specify the instance context yourself diff --git a/tests/deriving/should_fail/drvfail-functor2.stderr b/tests/deriving/should_fail/drvfail-functor2.stderr index 8691b38..322125c 100644 --- a/tests/deriving/should_fail/drvfail-functor2.stderr +++ b/tests/deriving/should_fail/drvfail-functor2.stderr @@ -24,7 +24,7 @@ drvfail-functor2.hs:20:14: drvfail-functor2.hs:26:14: No instance for (Functor NoFunctor) - arising from the 'deriving' clause of a data type declaration + arising from the first field of ?UseNoFunctor? (type ?NoFunctor a?) Possible fix: use a standalone 'deriving instance' declaration, so you can specify the instance context yourself diff --git a/tests/deriving/should_fail/drvfail001.stderr b/tests/deriving/should_fail/drvfail001.stderr index 8c0be37..3f3d4ec 100644 --- a/tests/deriving/should_fail/drvfail001.stderr +++ b/tests/deriving/should_fail/drvfail001.stderr @@ -1,7 +1,7 @@ drvfail001.hs:16:33: No instance for (Show (f (f a))) - arising from the 'deriving' clause of a data type declaration + arising from the first field of ?ZeroS? (type ?f (f a)?) Possible fix: use a standalone 'deriving instance' declaration, so you can specify the instance context yourself diff --git a/tests/deriving/should_fail/drvfail002.stderr b/tests/deriving/should_fail/drvfail002.stderr index 20d54c6..8064cb6 100644 --- a/tests/deriving/should_fail/drvfail002.stderr +++ b/tests/deriving/should_fail/drvfail002.stderr @@ -1,7 +1,7 @@ drvfail002.hs:19:23: No instance for (X T c) - arising from the 'deriving' clause of a data type declaration + arising from the first field of ?S? (type ?T?) Possible fix: use a standalone 'deriving instance' declaration, so you can specify the instance context yourself diff --git a/tests/deriving/should_fail/drvfail003.stderr b/tests/deriving/should_fail/drvfail003.stderr index f329420..a2493f3 100644 --- a/tests/deriving/should_fail/drvfail003.stderr +++ b/tests/deriving/should_fail/drvfail003.stderr @@ -1,7 +1,7 @@ drvfail003.hs:16:56: No instance for (Show (v (v a))) - arising from the 'deriving' clause of a data type declaration + arising from the first field of ?End? (type ?v (v a)?) Possible fix: use a standalone 'deriving instance' declaration, so you can specify the instance context yourself diff --git a/tests/deriving/should_fail/drvfail007.stderr b/tests/deriving/should_fail/drvfail007.stderr index d47c14e..c9d998e 100644 --- a/tests/deriving/should_fail/drvfail007.stderr +++ b/tests/deriving/should_fail/drvfail007.stderr @@ -1,7 +1,7 @@ drvfail007.hs:4:38: No instance for (Eq (Int -> Int)) - arising from the 'deriving' clause of a data type declaration + arising from the first field of ?Foo? (type ?Int -> Int?) Possible fix: use a standalone 'deriving instance' declaration, so you can specify the instance context yourself diff --git a/tests/deriving/should_fail/drvfail013.stderr b/tests/deriving/should_fail/drvfail013.stderr index 29d8ba6..4b2350f 100644 --- a/tests/deriving/should_fail/drvfail013.stderr +++ b/tests/deriving/should_fail/drvfail013.stderr @@ -9,7 +9,7 @@ drvfail013.hs:4:70: drvfail013.hs:6:70: No instance for (Eq (m (Maybe a))) - arising from the 'deriving' clause of a data type declaration + arising from the first field of ?MaybeT'? (type ?m (Maybe a)?) Possible fix: use a standalone 'deriving instance' declaration, so you can specify the instance context yourself diff --git a/tests/typecheck/should_fail/tcfail046.stderr b/tests/typecheck/should_fail/tcfail046.stderr index e3a8f16..b029915 100644 --- a/tests/typecheck/should_fail/tcfail046.stderr +++ b/tests/typecheck/should_fail/tcfail046.stderr @@ -1,7 +1,7 @@ tcfail046.hs:10:50: No instance for (Eq (Process a)) - arising from the 'deriving' clause of a data type declaration + arising from the first field of ?Do? (type ?Process a?) Possible fix: use a standalone 'deriving instance' declaration, so you can specify the instance context yourself @@ -9,7 +9,7 @@ tcfail046.hs:10:50: tcfail046.hs:22:25: No instance for (Eq (Process a)) - arising from the 'deriving' clause of a data type declaration + arising from the first field of ?Create? (type ?Process a?) Possible fix: use a standalone 'deriving instance' declaration, so you can specify the instance context yourself diff --git a/tests/typecheck/should_fail/tcfail118.stderr b/tests/typecheck/should_fail/tcfail118.stderr index ec21d1f..01f6654 100644 --- a/tests/typecheck/should_fail/tcfail118.stderr +++ b/tests/typecheck/should_fail/tcfail118.stderr @@ -1,7 +1,7 @@ tcfail118.hs:10:29: Overlapping instances for Eq Foo - arising from the 'deriving' clause of a data type declaration + arising from the first field of ?Bar? (type ?Foo?) Matching instances: instance Eq Foo -- Defined at tcfail118.hs:11:25 instance Eq Foo -- Defined at tcfail118.hs:13:10 diff --git a/tests/typecheck/should_fail/tcfail169.stderr b/tests/typecheck/should_fail/tcfail169.stderr index 1e0262d..e1ac2db 100644 --- a/tests/typecheck/should_fail/tcfail169.stderr +++ b/tests/typecheck/should_fail/tcfail169.stderr @@ -1,7 +1,7 @@ tcfail169.hs:7:51: No instance for (Show (Succ a)) - arising from the 'deriving' clause of a data type declaration + arising from the second field of ?Cons? (type ?Seq (Succ a)?) Possible fix: use a standalone 'deriving instance' declaration, so you can specify the instance context yourself From git at git.haskell.org Tue Dec 3 13:30:37 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Dec 2013 13:30:37 +0000 (UTC) Subject: [commit: ghc] branch 'wip/T8592' created Message-ID: <20131203133037.3F9202406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/T8592 Referencing: 84e0b8d78eeef1d10c6ae26c9c8a15702070f887 From git at git.haskell.org Tue Dec 3 13:30:39 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Dec 2013 13:30:39 +0000 (UTC) Subject: [commit: ghc] wip/T8592: Use PredOrigin in FunDeps.lhs (84e0b8d) Message-ID: <20131203133039.84B8C2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8592 Link : http://ghc.haskell.org/trac/ghc/changeset/84e0b8d78eeef1d10c6ae26c9c8a15702070f887/ghc >--------------------------------------------------------------- commit 84e0b8d78eeef1d10c6ae26c9c8a15702070f887 Author: Joachim Breitner Date: Tue Dec 3 12:19:14 2013 +0000 Use PredOrigin in FunDeps.lhs >--------------------------------------------------------------- 84e0b8d78eeef1d10c6ae26c9c8a15702070f887 compiler/typecheck/FunDeps.lhs | 32 +++++++++++++++----------------- compiler/typecheck/TcDeriv.lhs | 11 ----------- compiler/typecheck/TcInteract.lhs | 17 ++++++++--------- compiler/typecheck/TcRnTypes.lhs | 35 ++++++++++++++++++++++++++++++++++- 4 files changed, 57 insertions(+), 38 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 84e0b8d78eeef1d10c6ae26c9c8a15702070f887 From git at git.haskell.org Tue Dec 3 16:12:27 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Dec 2013 16:12:27 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Merge remote-tracking branch 'origin/master' into better-ho-cardinality (84d4165) Message-ID: <20131203161227.8CCA42406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/84d4165af88d22db38424591e8984ef6e7b885c0/ghc >--------------------------------------------------------------- commit 84d4165af88d22db38424591e8984ef6e7b885c0 Merge: 20cc594 4025d66 Author: Joachim Breitner Date: Tue Dec 3 14:04:03 2013 +0000 Merge remote-tracking branch 'origin/master' into better-ho-cardinality >--------------------------------------------------------------- 84d4165af88d22db38424591e8984ef6e7b885c0 compiler/basicTypes/Demand.lhs | 14 + compiler/cmm/CmmInfo.hs | 17 ++ compiler/cmm/CmmPipeline.hs | 9 +- compiler/cmm/CmmUtils.hs | 9 + compiler/codeGen/StgCmmBind.hs | 23 +- compiler/codeGen/StgCmmLayout.hs | 86 +++++- compiler/codeGen/StgCmmProf.hs | 11 +- compiler/coreSyn/CoreUtils.lhs | 4 +- compiler/coreSyn/MkCore.lhs | 19 +- compiler/deSugar/Desugar.lhs | 34 +-- compiler/deSugar/DsArrows.lhs | 2 +- compiler/deSugar/DsBinds.lhs | 126 +++----- compiler/deSugar/DsExpr.lhs | 7 +- compiler/deSugar/Match.lhs | 10 +- compiler/ghc.mk | 165 ++++++++++- compiler/ghci/RtClosureInspect.hs | 62 ++-- compiler/hsSyn/Convert.lhs | 2 +- compiler/hsSyn/HsUtils.lhs | 16 +- compiler/main/DynFlags.hs | 1 + compiler/main/HscMain.hs | 55 ++-- compiler/main/HscTypes.lhs | 46 ++- compiler/main/InteractiveEval.hs | 118 ++++---- compiler/prelude/TysWiredIn.lhs-boot | 2 +- compiler/prelude/primops.txt.pp | 2 +- compiler/rename/RnSplice.lhs | 2 +- compiler/simplCore/CoreMonad.lhs | 16 +- compiler/{types => typecheck}/FunDeps.lhs | 0 compiler/typecheck/Inst.lhs | 3 +- compiler/typecheck/TcArrows.lhs | 7 +- compiler/typecheck/TcBinds.lhs | 2 +- compiler/typecheck/TcCanonical.lhs | 31 +- compiler/typecheck/TcDeriv.lhs | 352 +++++++++++++---------- compiler/typecheck/TcEnv.lhs | 109 +++++-- compiler/typecheck/TcErrors.lhs | 24 +- compiler/typecheck/TcEvidence.lhs | 321 +++++++++++---------- compiler/typecheck/TcExpr.lhs | 10 +- compiler/typecheck/TcGenDeriv.lhs | 66 +++-- compiler/typecheck/TcHsSyn.lhs | 55 ++-- compiler/typecheck/TcInstDcls.lhs | 26 +- compiler/typecheck/TcInteract.lhs | 197 ++++++++----- compiler/typecheck/TcMType.lhs | 24 +- compiler/typecheck/TcPat.lhs | 16 +- compiler/typecheck/TcRnDriver.lhs | 82 +++--- compiler/typecheck/TcRnTypes.lhs | 12 +- compiler/typecheck/TcSMonad.lhs | 30 +- compiler/typecheck/TcTyClsDecls.lhs | 442 +++++++++++++++-------------- compiler/typecheck/TcTyDecls.lhs | 5 +- compiler/typecheck/TcUnify.lhs | 18 +- compiler/typecheck/TcValidity.lhs | 2 +- compiler/types/Coercion.lhs | 19 +- compiler/types/Type.lhs | 36 ++- docs/users_guide/extending_ghc.xml | 2 +- docs/users_guide/glasgow_exts.xml | 13 +- rts/sm/GC.c | 5 +- rts/sm/Storage.c | 22 +- utils/deriveConstants/DeriveConstants.hs | 4 +- 56 files changed, 1630 insertions(+), 1163 deletions(-) From git at git.haskell.org Tue Dec 3 16:12:29 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Dec 2013 16:12:29 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Initial work on Nested CPR (9e0ec3c) Message-ID: <20131203161229.AD4CA2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/9e0ec3c4ed135805bb491dd6719f7ff3d381a752/ghc >--------------------------------------------------------------- commit 9e0ec3c4ed135805bb491dd6719f7ff3d381a752 Author: Simon Peyton Jones Date: Mon Nov 25 09:59:16 2013 +0000 Initial work on Nested CPR >--------------------------------------------------------------- 9e0ec3c4ed135805bb491dd6719f7ff3d381a752 compiler/basicTypes/Demand.lhs | 278 +++++++++++++++++++++++++++------------- compiler/basicTypes/MkId.lhs | 40 +++--- compiler/stranal/DmdAnal.lhs | 117 +++++++++++------ 3 files changed, 284 insertions(+), 151 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 9e0ec3c4ed135805bb491dd6719f7ff3d381a752 From git at git.haskell.org Tue Dec 3 16:12:31 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Dec 2013 16:12:31 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Further work on Nested CPR (20b5770) Message-ID: <20131203161231.CAB232406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/20b57703991c9b76d0c041b0b457883f6e6bc31c/ghc >--------------------------------------------------------------- commit 20b57703991c9b76d0c041b0b457883f6e6bc31c Author: Joachim Breitner Date: Mon Nov 25 17:48:27 2013 +0000 Further work on Nested CPR >--------------------------------------------------------------- 20b57703991c9b76d0c041b0b457883f6e6bc31c compiler/basicTypes/Demand.lhs | 128 ++++++++++++++++++++++++---------------- compiler/basicTypes/MkId.lhs | 4 +- compiler/stranal/DmdAnal.lhs | 29 +++++---- compiler/stranal/WwLib.lhs | 51 +++++++++------- 4 files changed, 125 insertions(+), 87 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 20b57703991c9b76d0c041b0b457883f6e6bc31c From git at git.haskell.org Tue Dec 3 16:12:33 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Dec 2013 16:12:33 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Reimplement mkWWcpr_help (0052efc) Message-ID: <20131203161233.E51212406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/0052efcdea5c5d7c32bae05adadd3cb9425732ee/ghc >--------------------------------------------------------------- commit 0052efcdea5c5d7c32bae05adadd3cb9425732ee Author: Joachim Breitner Date: Thu Nov 28 15:49:41 2013 +0000 Reimplement mkWWcpr_help to generate a flat unboxed tuple even for nested CPR. >--------------------------------------------------------------- 0052efcdea5c5d7c32bae05adadd3cb9425732ee compiler/stranal/WwLib.lhs | 113 +++++++++++++++++++++++--------------------- 1 file changed, 59 insertions(+), 54 deletions(-) diff --git a/compiler/stranal/WwLib.lhs b/compiler/stranal/WwLib.lhs index e7a32c2..b6b99e8 100644 --- a/compiler/stranal/WwLib.lhs +++ b/compiler/stranal/WwLib.lhs @@ -17,7 +17,7 @@ import Id ( Id, idType, mkSysLocal, idDemandInfo, setIdDemandInfo, import IdInfo ( vanillaIdInfo ) import DataCon import Demand -import MkCore ( mkRuntimeErrorApp, aBSENT_ERROR_ID ) +import MkCore ( mkRuntimeErrorApp, aBSENT_ERROR_ID, mkCoreLet ) import MkId ( voidArgId, voidPrimId ) import TysPrim ( voidPrimTy ) import TysWiredIn ( tupleCon ) @@ -131,7 +131,7 @@ mkWwBodies dflags fun_ty demands res_info one_shots ; (work_args, wrap_fn_str, work_fn_str) <- mkWWstr dflags wrap_args -- Do CPR w/w. See Note [Always do CPR w/w] - ; (wrap_fn_cpr, work_fn_cpr, cpr_res_ty) <- mkWWcpr False res_ty res_info + ; (wrap_fn_cpr, work_fn_cpr, cpr_res_ty) <- mkWWcpr res_ty res_info ; let (work_lam_args, work_call_args) = mkWorkerArgs dflags work_args all_one_shots cpr_res_ty ; return ([idDemandInfo v | v <- work_call_args, isId v], @@ -528,63 +528,68 @@ left-to-right traversal of the result structure. \begin{code} -mkWWcpr :: Bool -- is this a nested return? - -> Type -- function body type + +mkWWcpr :: Type -- function body type -> DmdResult -- CPR analysis results -> UniqSM (CoreExpr -> CoreExpr, -- New wrapper CoreExpr -> CoreExpr, -- New worker Type) -- Type of worker's body - -mkWWcpr inner body_ty res - = case returnsCPR_maybe inner res of - Nothing - -> return (id, id, body_ty) -- No CPR info - Just (con_tag, rs) - | Just stuff <- deepSplitCprType_maybe con_tag body_ty - -> mkWWcpr_help stuff rs +mkWWcpr body_ty res + = do (arg_vars, con_app, decon) <- mkWWcpr_help False body_ty res + wrap_wild_uniq <- getUniqueM + + let wrap_wild = mk_ww_local wrap_wild_uniq ubx_tup_ty + ubx_tup_con = tupleCon UnboxedTuple (length arg_vars) + ubx_tup_app = mkConApp2 ubx_tup_con (map idType arg_vars) arg_vars + ubx_tup_ty = exprType ubx_tup_app + + return ( \ wkr_call -> Case wkr_call wrap_wild (exprType con_app) [(DataAlt ubx_tup_con, arg_vars, con_app)] + , \ body -> decon body ubx_tup_app + , ubx_tup_ty ) + +mkWWcpr_help :: Bool -> -- This this an inner call? + Type -> + DmdResult -> + UniqSM ( [Var], -- variables for the arguments + CoreExpr, -- boxed constructors applied to all these variables + CoreExpr -> CoreExpr -> CoreExpr) + -- nested case expression, taking the boxed constructors in the first + -- argument apart, binds them to the variables above and feeds them + -- to the second argument +mkWWcpr_help inner ty res + = case returnsCPR_maybe inner res of + Just (con_tag, rs) + | Just (data_con, inst_tys, arg_tys, co) <- deepSplitCprType_maybe con_tag ty + -> do arg_uniqs <- getUniquesM + let arg_vars = zipWith mk_ww_local arg_uniqs arg_tys + arg_stuff <- sequence (zipWith (mkWWcpr_help True) arg_tys rs) + + let (nested_arg_varss, arg_cons, arg_decons) = unzip3 arg_stuff + nested_arg_vars = concat nested_arg_varss + nested_decon = foldr (.) id $ zipWith id arg_decons (map Var arg_vars) + + work_uniq <- getUniqueM + + return + ( nested_arg_vars + , mkConApp data_con (map Type inst_tys ++ arg_cons) `mkCast` mkSymCo co + , \e body -> mkUnpackCase e co work_uniq data_con arg_vars (nested_decon body) + ) | otherwise - -> WARN( True, text "mkWWcpr: non-algebraic or open body type" <+> ppr body_ty ) - return (id, id, body_ty) - -mkWWcpr_help :: (DataCon, [Type], [Type], Coercion) -> [DmdResult] - -> UniqSM (CoreExpr -> CoreExpr, CoreExpr -> CoreExpr, Type) - -mkWWcpr_help (data_con, inst_tys, arg_tys, co) rs - | [arg_ty1] <- arg_tys - , isUnLiftedType arg_ty1 - -- Special case when there is a single result of unlifted type - -- - -- Wrapper: case (..call worker..) of x -> C x - -- Worker: case ( ..body.. ) of C x -> x - = do { (work_uniq : arg_uniq : _) <- getUniquesM - ; let arg = mk_ww_local arg_uniq arg_ty1 - con_app = mkConApp2 data_con inst_tys [arg] `mkCast` mkSymCo co - - ; return ( \ wkr_call -> Case wkr_call arg (exprType con_app) [(DEFAULT, [], con_app)] - , \ body -> mkUnpackCase body co work_uniq data_con [arg] (Var arg) - , arg_ty1 ) } - - | otherwise -- The general case - -- Wrapper: case (..call worker..) of (# a, b #) -> C a b - -- Worker: case ( ...body... ) of C a b -> (# a, b #) - = do { work_uniq <- getUniqueM - ; bx_uniqs <- getUniquesM - ; ubx_uniqs <- getUniquesM - ; arg_stuff <- sequence (zipWith (mkWWcpr True) arg_tys rs) - ; let (arg_wraps, arg_works, ubx_arg_tys) = unzip3 arg_stuff - (bx_args) = zipWith mk_ww_local bx_uniqs arg_tys - (wrap_wild : ubx_args) = zipWith mk_ww_local ubx_uniqs (ubx_tup_ty : ubx_arg_tys) - ubx_tup_con = tupleCon UnboxedTuple (length arg_tys) - ubx_tup_ty = exprType ubx_tup_app - ubx_tup_app = mkConApp2 ubx_tup_con ubx_arg_tys [] `mkApps` - zipWith id arg_works (map varToCoreExpr bx_args) - con_app = (mkConApp2 data_con inst_tys [] `mkApps` - zipWith id arg_wraps (map varToCoreExpr ubx_args) - ) `mkCast` mkSymCo co - - ; return ( \ wkr_call -> Case wkr_call wrap_wild (exprType con_app) [(DataAlt ubx_tup_con, ubx_args, con_app)] - , \ body -> mkUnpackCase body co work_uniq data_con bx_args ubx_tup_app - , ubx_tup_ty ) } + -> pprPanic "mkWWcpr: non-algebraic or open body type" (ppr ty) + Nothing -> do + uniq <- getUniqueM + let var = mk_ww_local uniq ty + return ( [var] + , Var var + , \e body -> mkRename e var body + ) + +-- mkRename e v body +-- binds v to e in body. This will later be removed by the simplifiers +mkRename :: CoreExpr -> Var -> CoreExpr -> CoreExpr +mkRename e v body = ASSERT( idType v `eqType` exprType e) + mkCoreLet (NonRec v e) body mkUnpackCase :: CoreExpr -> Coercion -> Unique -> DataCon -> [Id] -> CoreExpr -> CoreExpr -- (mkUnpackCase e co uniq Con args body) From git at git.haskell.org Tue Dec 3 16:12:36 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Dec 2013 16:12:36 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Fix a lubDmdResult equation (da8665c) Message-ID: <20131203161236.075CE2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/da8665c1d9a2a76d5ca55fb512c24ae06b8a6e6e/ghc >--------------------------------------------------------------- commit da8665c1d9a2a76d5ca55fb512c24ae06b8a6e6e Author: Joachim Breitner Date: Tue Nov 26 10:17:57 2013 +0000 Fix a lubDmdResult equation >--------------------------------------------------------------- da8665c1d9a2a76d5ca55fb512c24ae06b8a6e6e compiler/basicTypes/Demand.lhs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 07a66e7..cdbc4e5 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -743,7 +743,7 @@ lubDmdResult :: DmdResult -> DmdResult -> DmdResult lubDmdResult Diverges (Dunno c2) = Dunno c2 lubDmdResult Diverges Diverges = Diverges lubDmdResult Diverges (Converges c2) = Dunno c2 -lubDmdResult (Converges c1) Diverges = Converges c1 +lubDmdResult (Converges c1) Diverges = Dunno c1 lubDmdResult (Converges c1) (Converges c2) = Converges (c1 `lubCPR` c2) lubDmdResult (Converges c1) (Dunno c2) = Dunno (c1 `lubCPR` c2) lubDmdResult (Dunno c1) Diverges = Dunno c1 From git at git.haskell.org Tue Dec 3 16:12:38 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Dec 2013 16:12:38 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Apply state hack only to information about arguments (938cf3d) Message-ID: <20131203161238.29D032406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/938cf3d4d6601ca2fce814b20eb75e03c514c341/ghc >--------------------------------------------------------------- commit 938cf3d4d6601ca2fce814b20eb75e03c514c341 Author: Joachim Breitner Date: Thu Nov 28 10:29:47 2013 +0000 Apply state hack only to information about arguments >--------------------------------------------------------------- 938cf3d4d6601ca2fce814b20eb75e03c514c341 compiler/basicTypes/Demand.lhs | 8 ++++++++ compiler/stranal/DmdAnal.lhs | 4 +++- compiler/stranal/WwLib.lhs | 2 +- 3 files changed, 12 insertions(+), 2 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index e3cd5d6..b3fe942 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -20,6 +20,7 @@ module Demand ( DmdType(..), dmdTypeDepth, lubDmdType, bothDmdEnv, bothDmdType, bothDmdTypeCase, topDmdType, botDmdType, mkDmdType, mkTopDmdType, + dmdTypeArgTop, DmdEnv, emptyDmdEnv, @@ -1141,6 +1142,13 @@ splitDmdTy :: DmdType -> (Demand, DmdType) splitDmdTy (DmdType fv (dmd:dmds) res_ty) = (dmd, DmdType fv dmds res_ty) splitDmdTy ty@(DmdType _ [] res_ty) = (resTypeArgDmd res_ty, ty) +-- We want to forget what we know about the arguments, but keep the information +-- of the result, see Note [IO State Hack] +dmdTypeArgTop :: DmdType -> DmdType +dmdTypeArgTop d@(DmdType _ _ res) + = let (DmdType env' ds' _) = d `lubDmdType` topDmdType + in DmdType env' ds' res + modifyEnv :: Bool -- No-op if False -> (Demand -> Demand) -- The zapper -> DmdEnv -> DmdEnv -- Env1 and Env2 diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index 8da502c..67e5663 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -307,9 +307,11 @@ dmdAnalAlt env dmd (con,bndrs,rhs) (rhs_ty, rhs') = dmdAnal env dmd rhs rhs_ty' = addDataConPatDmds con bndrs rhs_ty (alt_ty, bndrs') = annotateBndrs env rhs_ty' bndrs - final_alt_ty | io_hack_reqd = alt_ty `lubDmdType` topDmdType + final_alt_ty | io_hack_reqd = dmdTypeArgTop alt_ty | otherwise = alt_ty + -- Note [IO State Hack] + -- -- There's a hack here for I/O operations. Consider -- case foo x s of { (# s, r #) -> y } -- Is this strict in 'y'. Normally yes, but what if 'foo' is an I/O diff --git a/compiler/stranal/WwLib.lhs b/compiler/stranal/WwLib.lhs index 0b819dc..861a03b 100644 --- a/compiler/stranal/WwLib.lhs +++ b/compiler/stranal/WwLib.lhs @@ -503,7 +503,7 @@ deepSplitCprType_maybe :: ConTag -> Type -> Maybe (DataCon, [Type], [Type], Coer deepSplitCprType_maybe con_tag ty | let (co, ty1) = topNormaliseNewType_maybe ty `orElse` (mkReflCo Representational ty, ty) , Just (tc, tc_args) <- splitTyConApp_maybe ty1 - , isDataTyCon tc + , isDataTyCon tc || isUnboxedTupleTyCon tc , let cons = tyConDataCons tc con = ASSERT( cons `lengthAtLeast` con_tag ) cons !! (con_tag - fIRST_TAG) = Just (con, tc_args, dataConInstArgTys con tc_args, co) From git at git.haskell.org Tue Dec 3 16:12:40 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Dec 2013 16:12:40 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: More tracing (5b76053) Message-ID: <20131203161240.55AAD2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/5b760534a8258353242790ae8a3d471abe679595/ghc >--------------------------------------------------------------- commit 5b760534a8258353242790ae8a3d471abe679595 Author: Joachim Breitner Date: Thu Nov 28 18:49:04 2013 +0000 More tracing >--------------------------------------------------------------- 5b760534a8258353242790ae8a3d471abe679595 compiler/stranal/DmdAnal.lhs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index 67e5663..0f18ea9 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -639,7 +639,8 @@ dmdAnalRhs top_lvl rec_flag env id rhs = (fn_str, emptyDmdEnv, set_idStrictness env id fn_str, rhs) | otherwise - = (sig_ty, lazy_fv, id', mkLams bndrs' body') + = -- pprTrace "dmdAnalRhs" (vcat [ ppr id, ppr (idDemandInfo id), ppr rhs_dmd_ty, ppr sig_ty, ppr not_strict ]) + (sig_ty, lazy_fv, id', mkLams bndrs' body') where (bndrs, body) = collectBinders rhs env_body = foldl extendSigsWithLam env bndrs From git at git.haskell.org Tue Dec 3 16:12:41 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Dec 2013 16:12:41 +0000 (UTC) Subject: [commit: testsuite] branch 'wip/nested-cpr' created Message-ID: <20131203161241.ED0942406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/testsuite New branch : wip/nested-cpr Referencing: fd2e0cef1d734a04800614b385926ee21fc9533b From git at git.haskell.org Tue Dec 3 16:12:42 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Dec 2013 16:12:42 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Loop breakers are not allowed to have a Converges DmdResult (f4e5641) Message-ID: <20131203161242.5BB752406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/f4e5641e3ca2992dcb592b124f0ae3ee9b082d5b/ghc >--------------------------------------------------------------- commit f4e5641e3ca2992dcb592b124f0ae3ee9b082d5b Author: Joachim Breitner Date: Tue Nov 26 10:18:35 2013 +0000 Loop breakers are not allowed to have a Converges DmdResult >--------------------------------------------------------------- f4e5641e3ca2992dcb592b124f0ae3ee9b082d5b compiler/basicTypes/Demand.lhs | 18 +++++++++++------- compiler/stranal/DmdAnal.lhs | 5 ++++- 2 files changed, 15 insertions(+), 8 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index cdbc4e5..e3cd5d6 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -30,6 +30,7 @@ module Demand ( trimCPRInfo, returnsCPR, returnsCPR_maybe, StrictSig(..), mkStrictSig, topSig, botSig, cprProdSig, isTopSig, splitStrictSig, increaseStrictSigArity, + sigMayConverge, seqDemand, seqDemandList, seqDmdType, seqStrictSig, @@ -788,15 +789,11 @@ botRes = Diverges maxCPRDepth :: Int maxCPRDepth = 3 --- With nested CPR, DmdResult can be arbitrarily deep; consider --- data Rec1 = Foo Rec2 Rec2 --- data Rec2 = Bar Rec1 Rec1 --- --- x = Foo y y --- y = Bar x x +-- With nested CPR, DmdResult can be arbitrarily deep; consider e.g. the +-- DmdResult of repeat -- -- So we need to forget information at a certain depth. We do that at all points --- where we are constructing new RetCon constructors. +-- where we are building RetCon constructors. cutDmdResult :: Int -> DmdResult -> DmdResult cutDmdResult 0 _ = topRes cutDmdResult _ Diverges = Diverges @@ -807,6 +804,10 @@ cutCPRResult :: Int -> CPRResult -> CPRResult cutCPRResult _ NoCPR = NoCPR cutCPRResult n (RetCon tag rs) = RetCon tag (map (cutDmdResult (n-1)) rs) +-- Forget that something might converge for sure +divergeDmdResult :: DmdResult -> DmdResult +divergeDmdResult r = r `lubDmdResult` botRes + cprConRes :: ConTag -> [DmdType] -> CPRResult cprConRes tag arg_tys | opt_CprOff = NoCPR @@ -1354,6 +1355,9 @@ botSig = StrictSig botDmdType cprProdSig :: Arity -> StrictSig cprProdSig arity = StrictSig (cprProdDmdType arity) +sigMayConverge :: StrictSig -> StrictSig +sigMayConverge (StrictSig (DmdType env ds res)) = (StrictSig (DmdType env ds (divergeDmdResult res))) + argsOneShots :: StrictSig -> Arity -> [[OneShotInfo]] argsOneShots (StrictSig (DmdType _ arg_ds _)) n_val_args = go arg_ds diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index fb9ea7cc..8da502c 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -1097,7 +1097,10 @@ updSigEnv env sigs = env { ae_sigs = sigs } extendAnalEnv :: TopLevelFlag -> AnalEnv -> Id -> StrictSig -> AnalEnv extendAnalEnv top_lvl env var sig - = env { ae_sigs = extendSigEnv top_lvl (ae_sigs env) var sig } + = env { ae_sigs = extendSigEnv top_lvl (ae_sigs env) var sig' } + where + sig' | isWeakLoopBreaker (idOccInfo var) = sigMayConverge sig + | otherwise = sig extendSigEnv :: TopLevelFlag -> SigEnv -> Id -> StrictSig -> SigEnv extendSigEnv top_lvl sigs var sig = extendVarEnv sigs var (sig, top_lvl) From git at git.haskell.org Tue Dec 3 16:12:44 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Dec 2013 16:12:44 +0000 (UTC) Subject: [commit: testsuite] wip/nested-cpr: Update outputs per “Improve the handling of used-once stuff” (fd2e0ce) Message-ID: <20131203161244.176BE2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/testsuite On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/fd2e0cef1d734a04800614b385926ee21fc9533b/testsuite >--------------------------------------------------------------- commit fd2e0cef1d734a04800614b385926ee21fc9533b Author: Joachim Breitner Date: Tue Dec 3 15:27:28 2013 +0000 Update outputs per ?Improve the handling of used-once stuff? >--------------------------------------------------------------- fd2e0cef1d734a04800614b385926ee21fc9533b tests/deSugar/should_compile/T2431.stderr | 2 +- tests/numeric/should_compile/T7116.stdout | 16 ++++++++------ tests/perf/should_run/all.T | 3 ++- tests/simplCore/should_compile/T3717.stderr | 4 ++-- tests/simplCore/should_compile/T3772.stdout | 7 +++--- tests/simplCore/should_compile/T4908.stderr | 10 +++++---- tests/simplCore/should_compile/T4930.stderr | 10 +++++---- tests/simplCore/should_compile/T5366.stdout | 3 +-- tests/simplCore/should_compile/T7360.stderr | 13 +++++++---- tests/simplCore/should_compile/T7865.stdout | 4 ++-- tests/simplCore/should_compile/spec-inline.stderr | 24 ++++++++++----------- 11 files changed, 55 insertions(+), 41 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 fd2e0cef1d734a04800614b385926ee21fc9533b From git at git.haskell.org Tue Dec 3 16:12:44 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Dec 2013 16:12:44 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Do not generate workers with one element (# .. #) types (f559a15) Message-ID: <20131203161244.790B42406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/f559a1593c89117140d4806383c3c27fcfa3c481/ghc >--------------------------------------------------------------- commit f559a1593c89117140d4806383c3c27fcfa3c481 Author: Joachim Breitner Date: Thu Nov 28 16:06:18 2013 +0000 Do not generate workers with one element (# .. #) types >--------------------------------------------------------------- f559a1593c89117140d4806383c3c27fcfa3c481 compiler/stranal/WwLib.lhs | 28 ++++++++++++++++++---------- 1 file changed, 18 insertions(+), 10 deletions(-) diff --git a/compiler/stranal/WwLib.lhs b/compiler/stranal/WwLib.lhs index b6b99e8..0b819dc 100644 --- a/compiler/stranal/WwLib.lhs +++ b/compiler/stranal/WwLib.lhs @@ -536,16 +536,24 @@ mkWWcpr :: Type -- function body type Type) -- Type of worker's body mkWWcpr body_ty res = do (arg_vars, con_app, decon) <- mkWWcpr_help False body_ty res - wrap_wild_uniq <- getUniqueM - - let wrap_wild = mk_ww_local wrap_wild_uniq ubx_tup_ty - ubx_tup_con = tupleCon UnboxedTuple (length arg_vars) - ubx_tup_app = mkConApp2 ubx_tup_con (map idType arg_vars) arg_vars - ubx_tup_ty = exprType ubx_tup_app - - return ( \ wkr_call -> Case wkr_call wrap_wild (exprType con_app) [(DataAlt ubx_tup_con, arg_vars, con_app)] - , \ body -> decon body ubx_tup_app - , ubx_tup_ty ) + case arg_vars of + -- When we have to wrap only on argument, skip the (# .. #) + [arg_var] -> do + return ( \ wkr_call -> mkRename wkr_call arg_var con_app + , \ body -> decon body (Var arg_var) + , idType arg_var ) + + _ -> do + wrap_wild_uniq <- getUniqueM + + let wrap_wild = mk_ww_local wrap_wild_uniq ubx_tup_ty + ubx_tup_con = tupleCon UnboxedTuple (length arg_vars) + ubx_tup_app = mkConApp2 ubx_tup_con (map idType arg_vars) arg_vars + ubx_tup_ty = exprType ubx_tup_app + + return ( \ wkr_call -> Case wkr_call wrap_wild (exprType con_app) [(DataAlt ubx_tup_con, arg_vars, con_app)] + , \ body -> decon body ubx_tup_app + , ubx_tup_ty ) mkWWcpr_help :: Bool -> -- This this an inner call? Type -> From git at git.haskell.org Tue Dec 3 16:12:46 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Dec 2013 16:12:46 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Do not forget about Divergence of thunks (f523007) Message-ID: <20131203161246.9E20B2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/f5230074a530f12d3665f9c3e66fda6248574c4a/ghc >--------------------------------------------------------------- commit f5230074a530f12d3665f9c3e66fda6248574c4a Author: Joachim Breitner Date: Fri Nov 29 12:47:34 2013 +0000 Do not forget about Divergence of thunks >--------------------------------------------------------------- f5230074a530f12d3665f9c3e66fda6248574c4a compiler/basicTypes/Demand.lhs | 8 ++++++++ compiler/stranal/DmdAnal.lhs | 2 +- 2 files changed, 9 insertions(+), 1 deletion(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 7eda769..557a9bd 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -29,6 +29,7 @@ module Demand ( topRes, botRes, cprConRes, vanillaCprConRes, appIsBottom, isBottomingSig, pprIfaceStrictSig, returnsCPR, returnsCPR_maybe, + forgetCPR, StrictSig(..), mkStrictSig, topSig, botSig, cprProdSig, isTopSig, splitStrictSig, increaseStrictSigArity, sigMayConverge, @@ -809,6 +810,13 @@ cutCPRResult n (RetCon tag rs) = RetCon tag (map (cutDmdResult (n-1)) rs) divergeDmdResult :: DmdResult -> DmdResult divergeDmdResult r = r `lubDmdResult` botRes +-- Forget the CPR information, but remember if it converges or diverges +-- Used for non-strict thunks +forgetCPR :: DmdResult -> DmdResult +forgetCPR Diverges = Diverges +forgetCPR (Converges _) = Converges NoCPR +forgetCPR (Dunno _) = Dunno NoCPR + cprConRes :: ConTag -> [DmdType] -> CPRResult cprConRes tag arg_tys | opt_CprOff = NoCPR diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index 28fb5f3..2da9991 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -666,7 +666,7 @@ dmdAnalRhs top_lvl rec_flag env id rhs (lazy_fv, sig_fv) = splitFVs is_thunk rhs_fv1 -- Note [CPR for sum types] - rhs_res' | is_sum_type || (is_thunk && not_strict) = topRes + rhs_res' | is_sum_type || (is_thunk && not_strict) = forgetCPR rhs_res | otherwise = rhs_res -- See Note [CPR for thunks] From git at git.haskell.org Tue Dec 3 16:12:48 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Dec 2013 16:12:48 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Recover [CPR for sum types] (slightly differently) (48a9118) Message-ID: <20131203161249.8D4122406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/48a9118394e69e9113ee2967a7c69ef64c42a59a/ghc >--------------------------------------------------------------- commit 48a9118394e69e9113ee2967a7c69ef64c42a59a Author: Joachim Breitner Date: Thu Nov 28 11:17:16 2013 +0000 Recover [CPR for sum types] (slightly differently) >--------------------------------------------------------------- 48a9118394e69e9113ee2967a7c69ef64c42a59a compiler/basicTypes/Demand.lhs | 16 +--------------- compiler/stranal/DmdAnal.lhs | 13 +++++++------ 2 files changed, 8 insertions(+), 21 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index b3fe942..7eda769 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -28,7 +28,7 @@ module Demand ( isBotRes, isTopRes, resTypeArgDmd, topRes, botRes, cprConRes, vanillaCprConRes, appIsBottom, isBottomingSig, pprIfaceStrictSig, - trimCPRInfo, returnsCPR, returnsCPR_maybe, + returnsCPR, returnsCPR_maybe, StrictSig(..), mkStrictSig, topSig, botSig, cprProdSig, isTopSig, splitStrictSig, increaseStrictSigArity, sigMayConverge, @@ -831,20 +831,6 @@ isBotRes :: DmdResult -> Bool isBotRes Diverges = True isBotRes _ = False --- TODO: This currently ignores trim_sums. Evaluate if still required, and fix --- Note [CPR for sum types] -trimCPRInfo :: Bool -> Bool -> DmdResult -> DmdResult -trimCPRInfo trim_all _trim_sums res - = trimR res - where - trimR (Converges c) = Converges (trimC c) - trimR (Dunno c) = Dunno (trimC c) - trimR Diverges = Diverges - - trimC (RetCon n rs) | trim_all = NoCPR - | otherwise = RetCon n (map trimR rs) - trimC NoCPR = NoCPR - returnsCPR :: DmdResult -> Bool returnsCPR dr = isJust (returnsCPR_maybe False dr) diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index 0f18ea9..28fb5f3 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -652,9 +652,10 @@ dmdAnalRhs top_lvl rec_flag env id rhs -- See Note [NOINLINE and strictness] -- See Note [Product demands for function body] - body_dmd = case deepSplitProductType_maybe (exprType body) of - Nothing -> cleanEvalDmd - Just (dc, _, _, _) -> cleanEvalProdDmd (dataConRepArity dc) + (is_sum_type, body_dmd) + = case deepSplitProductType_maybe (exprType body) of + Nothing -> (True, cleanEvalDmd) + Just (dc, _, _, _) -> (False, cleanEvalProdDmd (dataConRepArity dc)) -- See Note [Lazy and unleashable free variables] -- See Note [Aggregated demand for cardinality] @@ -664,9 +665,9 @@ dmdAnalRhs top_lvl rec_flag env id rhs (lazy_fv, sig_fv) = splitFVs is_thunk rhs_fv1 - rhs_res' = trimCPRInfo trim_all trim_sums rhs_res - trim_all = is_thunk && not_strict - trim_sums = not (isTopLevel top_lvl) -- See Note [CPR for sum types] + -- Note [CPR for sum types] + rhs_res' | is_sum_type || (is_thunk && not_strict) = topRes + | otherwise = rhs_res -- See Note [CPR for thunks] is_thunk = not (exprIsHNF rhs) From git at git.haskell.org Tue Dec 3 16:12:50 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Dec 2013 16:12:50 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr's head updated: Do not forget about Divergence of thunks (f523007) Message-ID: <20131203161250.EC1322406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/nested-cpr' now includes: 4d1ea48 Implement shortcuts for slow calls (#6084) e9b0d36 Fix up shortcut for slow calls 9021737 Comments on slow-call-shortcutting 77e33bc -ddump-cmm: don't dump the proc point stage if we didn't do anything 6f7fa4e Refactor handleRunStatus some more, add comments and tidy up formatting a8ac471 Fix the deugger (fixing Trac #8557) f3a8416 More faff to get GHCi's top-level environment right 59e17d6 Fail (rather than addErr) if you use a bogus field in a pattern 9641641 Remove whitespace between macro identifiers and `(` 23efdd6 Update Notes for Coercible ceb600d Minor fix to example GHC plugin in the documentation 2e3c6a5 Update "stolen syntax" section (#8575) 9c3c152 Call busy_wait_nop() in the spin-wait loop in shutdown_gc_threads() de9f17e Update "stolen syntax" section (#8575) 4bbffb4 Fix documentation of FlexibleContexts (#8574) adb9964 Fix loopification with profiling and enable it by default (#8275) 6d24076 Document solution to #8275 6178f6e Don't explicitly refer to nodeReg in ldvEnterClosure ac31b79 Move the LDV code below the self-loop label (#8275) 574ccfa Respect the ordering of -package directives fac831f Revert "Respect the ordering of -package directives" 5e86ea5 TcDeriv: s/isomorphism/coercible bd7a125 With GND, report Coercible errors earliy 1791ea0 Print nicer error message for Coercible errors 06facab Refactor deferTcSForAllEq: Do not bind, but return EvTerm 249d47a Bind monadic stuff in getCoercibleInst locally, not via parameters e1e9faf Handle Coercible (forall a. t) (forall a. t2) in TcInteract b859c18 More links to [Coercible Instances] 3fecf81 Remove dead code orphaned by implementing GND with `coerce`. 4067340 Rejig rejigConRes & friends, doing role checks in a second pass. 20cc594 Improve the handling of used-once stuff b84fff3 Fix location of spliced-in role annotations. 90588c1 Move FunDeps to typecheck cb17c1f Note [HyperStr and Use demands] 0fe399c Some popular typos in comments 51bebb7 Refactor: Origin of inferred Thetas 4025d66 Elaborate "deriving" error messages 84d4165 Merge remote-tracking branch 'origin/master' into better-ho-cardinality 9e0ec3c Initial work on Nested CPR 20b5770 Further work on Nested CPR 0052efc Reimplement mkWWcpr_help f559a15 Do not generate workers with one element (# .. #) types da8665c Fix a lubDmdResult equation f4e5641 Loop breakers are not allowed to have a Converges DmdResult 938cf3d Apply state hack only to information about arguments 5b76053 More tracing 48a9118 Recover [CPR for sum types] (slightly differently) f523007 Do not forget about Divergence of thunks From git at git.haskell.org Tue Dec 3 16:51:21 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Dec 2013 16:51:21 +0000 (UTC) Subject: [commit: ghc] master: Export getHscEnv from HscMain (d14e5bf) Message-ID: <20131203165121.1F13F2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d14e5bf387860d338b3b693453ebe4126a4b2765/ghc >--------------------------------------------------------------- commit d14e5bf387860d338b3b693453ebe4126a4b2765 Author: Edsko de Vries Date: Sun Dec 1 13:55:07 2013 +0000 Export getHscEnv from HscMain >--------------------------------------------------------------- d14e5bf387860d338b3b693453ebe4126a4b2765 compiler/main/HscMain.hs | 3 +++ 1 file changed, 3 insertions(+) diff --git a/compiler/main/HscMain.hs b/compiler/main/HscMain.hs index a2d87a5..65dcc9d 100644 --- a/compiler/main/HscMain.hs +++ b/compiler/main/HscMain.hs @@ -73,7 +73,10 @@ module HscMain -- * Low-level exports for hooks , hscCompileCoreExpr' #endif + -- We want to make sure that we export enough to be able to redefine + -- hscFileFrontEnd in client code , hscParse', hscSimplify', hscDesugar', tcRnModule' + , getHscEnv , hscSimpleIface', hscNormalIface' , oneShotMsg , hscFileFrontEnd, genericHscFrontend, dumpIfaceStats From git at git.haskell.org Tue Dec 3 16:51:23 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Dec 2013 16:51:23 +0000 (UTC) Subject: [commit: ghc] master: Mask async exceptions in forkM_ (586bc85) Message-ID: <20131203165123.3194E2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/586bc85538cf12048137c2693da7c9fe3ca481ef/ghc >--------------------------------------------------------------- commit 586bc85538cf12048137c2693da7c9fe3ca481ef Author: Edsko de Vries Date: Thu Nov 28 16:38:26 2013 +0000 Mask async exceptions in forkM_ See #8006 for the reason why. This is not a fix as such; more of a workaround. >--------------------------------------------------------------- 586bc85538cf12048137c2693da7c9fe3ca481ef compiler/typecheck/TcRnMonad.lhs | 19 ++++++++++++++++++- compiler/utils/IOEnv.hs | 4 +++- 2 files changed, 21 insertions(+), 2 deletions(-) diff --git a/compiler/typecheck/TcRnMonad.lhs b/compiler/typecheck/TcRnMonad.lhs index cf8298f..d5a9383 100644 --- a/compiler/typecheck/TcRnMonad.lhs +++ b/compiler/typecheck/TcRnMonad.lhs @@ -1314,7 +1314,8 @@ forkM_maybe doc thing_inside -- does not get updated atomically (e.g. in newUnique and newUniqueSupply). = do { child_us <- newUniqueSupply ; child_env_us <- newMutVar child_us - ; unsafeInterleaveM $ updEnv (\env -> env { env_us = child_env_us }) $ + -- see Note [Masking exceptions in forkM_maybe] + ; unsafeInterleaveM $ uninterruptibleMaskM_ $ updEnv (\env -> env { env_us = child_env_us }) $ do { traceIf (text "Starting fork {" <+> doc) ; mb_res <- tryM $ updLclEnv (\env -> env { if_loc = if_loc env $$ doc }) $ @@ -1345,3 +1346,19 @@ forkM doc thing_inside -- pprPanic "forkM" doc Just r -> r) } \end{code} + +Note [Masking exceptions in forkM_maybe] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + +When using GHC-as-API it must be possible to interrupt snippets of code +executed using runStmt (#1381). Since commit 02c4ab04 this is almost possible +by throwing an asynchronous interrupt to the GHC thread. However, there is a +subtle problem: runStmt first typechecks the code before running it, and the +exception might interrupt the type checker rather than the code. Moreover, the +typechecker might be inside an unsafeInterleaveIO (through forkM_maybe), and +more importantly might be inside an exception handler inside that +unsafeInterleaveIO. If that is the case, the exception handler will rethrow the +asynchronous exception as a synchronous exception, and the exception will end +up as the value of the unsafeInterleaveIO thunk (see #8006 for a detailed +discussion). We don't currently know a general solution to this problem, but +we can use uninterruptibleMask_ to avoid the situation. diff --git a/compiler/utils/IOEnv.hs b/compiler/utils/IOEnv.hs index 04c11cf..6885bbd 100644 --- a/compiler/utils/IOEnv.hs +++ b/compiler/utils/IOEnv.hs @@ -22,7 +22,7 @@ module IOEnv ( -- Getting at the environment getEnv, setEnv, updEnv, - runIOEnv, unsafeInterleaveM, + runIOEnv, unsafeInterleaveM, uninterruptibleMaskM_, tryM, tryAllM, tryMostM, fixM, -- I/O operations @@ -149,6 +149,8 @@ tryMostM (IOEnv thing) = IOEnv (\ env -> tryMost (thing env)) unsafeInterleaveM :: IOEnv env a -> IOEnv env a unsafeInterleaveM (IOEnv m) = IOEnv (\ env -> unsafeInterleaveIO (m env)) +uninterruptibleMaskM_ :: IOEnv env a -> IOEnv env a +uninterruptibleMaskM_ (IOEnv m) = IOEnv (\ env -> uninterruptibleMask_ (m env)) ---------------------------------------------------------------------- -- Alternative/MonadPlus From git at git.haskell.org Tue Dec 3 18:10:34 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Dec 2013 18:10:34 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Do not forget about Divergence of thunks (a9cb62a) Message-ID: <20131203181034.56D942406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/a9cb62ae9730371bd22f193a655e6e6b131b0034/ghc >--------------------------------------------------------------- commit a9cb62ae9730371bd22f193a655e6e6b131b0034 Author: Joachim Breitner Date: Fri Nov 29 12:47:34 2013 +0000 Do not forget about Divergence of thunks >--------------------------------------------------------------- a9cb62ae9730371bd22f193a655e6e6b131b0034 compiler/basicTypes/Demand.lhs | 8 ++++++++ compiler/stranal/DmdAnal.lhs | 2 +- 2 files changed, 9 insertions(+), 1 deletion(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 7eda769..557a9bd 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -29,6 +29,7 @@ module Demand ( topRes, botRes, cprConRes, vanillaCprConRes, appIsBottom, isBottomingSig, pprIfaceStrictSig, returnsCPR, returnsCPR_maybe, + forgetCPR, StrictSig(..), mkStrictSig, topSig, botSig, cprProdSig, isTopSig, splitStrictSig, increaseStrictSigArity, sigMayConverge, @@ -809,6 +810,13 @@ cutCPRResult n (RetCon tag rs) = RetCon tag (map (cutDmdResult (n-1)) rs) divergeDmdResult :: DmdResult -> DmdResult divergeDmdResult r = r `lubDmdResult` botRes +-- Forget the CPR information, but remember if it converges or diverges +-- Used for non-strict thunks +forgetCPR :: DmdResult -> DmdResult +forgetCPR Diverges = Diverges +forgetCPR (Converges _) = Converges NoCPR +forgetCPR (Dunno _) = Dunno NoCPR + cprConRes :: ConTag -> [DmdType] -> CPRResult cprConRes tag arg_tys | opt_CprOff = NoCPR diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index 480f234..3bb197b 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -668,7 +668,7 @@ dmdAnalRhs top_lvl rec_flag env id rhs (lazy_fv, sig_fv) = splitFVs is_thunk rhs_fv1 -- Note [CPR for sum types] - rhs_res' | is_sum_type || (is_thunk && not_strict) = topRes + rhs_res' | is_sum_type || (is_thunk && not_strict) = forgetCPR rhs_res | otherwise = rhs_res -- See Note [CPR for thunks] From git at git.haskell.org Tue Dec 3 18:10:35 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Dec 2013 18:10:35 +0000 (UTC) Subject: [commit: testsuite] wip/nested-cpr: Test output update: Nested CPR signatures (0d96c4d) Message-ID: <20131203181035.3A3C82406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/testsuite On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/0d96c4d842e132884b174cdf686fe0eb3d33703f/testsuite >--------------------------------------------------------------- commit 0d96c4d842e132884b174cdf686fe0eb3d33703f Author: Joachim Breitner Date: Tue Dec 3 17:08:50 2013 +0000 Test output update: Nested CPR signatures >--------------------------------------------------------------- 0d96c4d842e132884b174cdf686fe0eb3d33703f tests/numeric/should_compile/T7116.stdout | 8 ++++---- tests/simplCore/should_compile/T3717.stderr | 2 +- tests/simplCore/should_compile/T4201.stdout | 2 +- tests/simplCore/should_compile/T4930.stderr | 2 +- tests/simplCore/should_compile/T7360.stderr | 8 ++++---- tests/simplCore/should_compile/spec-inline.stderr | 8 ++++---- 6 files changed, 15 insertions(+), 15 deletions(-) diff --git a/tests/numeric/should_compile/T7116.stdout b/tests/numeric/should_compile/T7116.stdout index 549ed48..79b4bf3 100644 --- a/tests/numeric/should_compile/T7116.stdout +++ b/tests/numeric/should_compile/T7116.stdout @@ -6,7 +6,7 @@ T7116.dl :: GHC.Types.Double -> GHC.Types.Double [GblId, Arity=1, Caf=NoCafRefs, - Str=DmdType m, + Str=DmdType tm1(d), Unf=Unf{Src=InlineStable, TopLvl=True, Arity=1, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(unsat_ok=True,boring_ok=False) @@ -24,7 +24,7 @@ T7116.dr :: GHC.Types.Double -> GHC.Types.Double [GblId, Arity=1, Caf=NoCafRefs, - Str=DmdType m, + Str=DmdType tm1(d), Unf=Unf{Src=InlineStable, TopLvl=True, Arity=1, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(unsat_ok=True,boring_ok=False) @@ -38,7 +38,7 @@ T7116.fl :: GHC.Types.Float -> GHC.Types.Float [GblId, Arity=1, Caf=NoCafRefs, - Str=DmdType m, + Str=DmdType tm1(d), Unf=Unf{Src=InlineStable, TopLvl=True, Arity=1, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(unsat_ok=True,boring_ok=False) @@ -56,7 +56,7 @@ T7116.fr :: GHC.Types.Float -> GHC.Types.Float [GblId, Arity=1, Caf=NoCafRefs, - Str=DmdType m, + Str=DmdType tm1(d), Unf=Unf{Src=InlineStable, TopLvl=True, Arity=1, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(unsat_ok=True,boring_ok=False) diff --git a/tests/simplCore/should_compile/T3717.stderr b/tests/simplCore/should_compile/T3717.stderr index 4522fb5..58f1349 100644 --- a/tests/simplCore/should_compile/T3717.stderr +++ b/tests/simplCore/should_compile/T3717.stderr @@ -17,7 +17,7 @@ T3717.foo [InlPrag=INLINE[0]] :: GHC.Types.Int -> GHC.Types.Int [GblId, Arity=1, Caf=NoCafRefs, - Str=DmdType m, + Str=DmdType dm1(d), Unf=Unf{Src=InlineStable, TopLvl=True, Arity=1, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(unsat_ok=True,boring_ok=False) diff --git a/tests/simplCore/should_compile/T4201.stdout b/tests/simplCore/should_compile/T4201.stdout index ed519ed..622276d 100644 --- a/tests/simplCore/should_compile/T4201.stdout +++ b/tests/simplCore/should_compile/T4201.stdout @@ -1,3 +1,3 @@ - {- Arity: 1, HasNoCafRefs, Strictness: m, + {- Arity: 1, HasNoCafRefs, Strictness: tm1(), Unfolding: InlineRule (0, True, True) Eta.bof `cast` (Sym (Eta.NTCo:Foo[0]) ->_R _R) -} diff --git a/tests/simplCore/should_compile/T4930.stderr b/tests/simplCore/should_compile/T4930.stderr index 9570b7b..e9f2965 100644 --- a/tests/simplCore/should_compile/T4930.stderr +++ b/tests/simplCore/should_compile/T4930.stderr @@ -13,7 +13,7 @@ T4930.foo1 = GHC.Err.error @ GHC.Types.Int lvl T4930.foo :: GHC.Types.Int -> GHC.Types.Int [GblId, Arity=1, - Str=DmdType m, + Str=DmdType dm1(d), Unf=Unf{Src=InlineStable, TopLvl=True, Arity=1, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(unsat_ok=True,boring_ok=False) diff --git a/tests/simplCore/should_compile/T7360.stderr b/tests/simplCore/should_compile/T7360.stderr index 9a5896a..10a267e 100644 --- a/tests/simplCore/should_compile/T7360.stderr +++ b/tests/simplCore/should_compile/T7360.stderr @@ -6,7 +6,7 @@ T7360.$WFoo3 [InlPrag=INLINE] :: GHC.Types.Int -> T7360.Foo [GblId[DataConWrapper], Arity=1, Caf=NoCafRefs, - Str=DmdType m3, + Str=DmdType tm3(d), Unf=Unf{Src=InlineStable, TopLvl=True, Arity=1, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(unsat_ok=False,boring_ok=False) @@ -21,7 +21,7 @@ T7360.$WFoo3 = } T7360.fun1 [InlPrag=NOINLINE] :: T7360.Foo -> () -[GblId, Arity=1, Caf=NoCafRefs, Str=DmdType ] +[GblId, Arity=1, Caf=NoCafRefs, Str=DmdType dm1()] T7360.fun1 = \ (x :: T7360.Foo) -> case x of _ [Occ=Dead] { __DEFAULT -> GHC.Tuple.() } @@ -37,7 +37,7 @@ T7360.fun4 = T7360.fun1 T7360.Foo1 T7360.fun3 :: GHC.Types.Int [GblId, Caf=NoCafRefs, - Str=DmdType m, + Str=DmdType tm1(d), Unf=Unf{Src=, TopLvl=True, Arity=0, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}] @@ -46,7 +46,7 @@ T7360.fun3 = GHC.Types.I# 0 T7360.fun2 :: forall a. [a] -> ((), GHC.Types.Int) [GblId, Arity=1, - Str=DmdType m, + Str=DmdType tm1(d,d), Unf=Unf{Src=InlineStable, TopLvl=True, Arity=1, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(unsat_ok=True,boring_ok=False) diff --git a/tests/simplCore/should_compile/spec-inline.stderr b/tests/simplCore/should_compile/spec-inline.stderr index 8690176..f931af3 100644 --- a/tests/simplCore/should_compile/spec-inline.stderr +++ b/tests/simplCore/should_compile/spec-inline.stderr @@ -98,7 +98,7 @@ Roman.foo_go [InlPrag=INLINE[0]] -> Data.Maybe.Maybe GHC.Types.Int -> GHC.Types.Int [GblId, Arity=2, - Str=DmdType m, + Str=DmdType dm1(d), Unf=Unf{Src=InlineStable, TopLvl=True, Arity=2, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(unsat_ok=True,boring_ok=False) @@ -113,7 +113,7 @@ Roman.foo_go = Roman.foo2 :: GHC.Types.Int [GblId, Caf=NoCafRefs, - Str=DmdType m, + Str=DmdType tm1(d), Unf=Unf{Src=, TopLvl=True, Arity=0, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}] @@ -122,7 +122,7 @@ Roman.foo2 = GHC.Types.I# 6 Roman.foo1 :: Data.Maybe.Maybe GHC.Types.Int [GblId, Caf=NoCafRefs, - Str=DmdType m2, + Str=DmdType t, Unf=Unf{Src=, TopLvl=True, Arity=0, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}] @@ -132,7 +132,7 @@ Roman.foo :: GHC.Types.Int -> GHC.Types.Int [GblId, Arity=1, Caf=NoCafRefs, - Str=DmdType m, + Str=DmdType dm1(d), Unf=Unf{Src=InlineStable, TopLvl=True, Arity=1, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(unsat_ok=True,boring_ok=False) From git at git.haskell.org Tue Dec 3 18:10:36 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Dec 2013 18:10:36 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: More tracing (e3c0015) Message-ID: <20131203181036.3DEFD2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/e3c00154b77fdbe28ef16a1f46fb587bf27588b1/ghc >--------------------------------------------------------------- commit e3c00154b77fdbe28ef16a1f46fb587bf27588b1 Author: Joachim Breitner Date: Thu Nov 28 18:49:04 2013 +0000 More tracing >--------------------------------------------------------------- e3c00154b77fdbe28ef16a1f46fb587bf27588b1 compiler/stranal/DmdAnal.lhs | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index 67e5663..953b616 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -115,7 +115,9 @@ dmdAnalStar :: AnalEnv dmdAnalStar env dmd e | (cd, defer_and_use) <- toCleanDmd dmd , (dmd_ty, e') <- dmdAnal env cd e - = (postProcessDmdTypeM defer_and_use dmd_ty, e') + = let dmd_ty' = postProcessDmdTypeM defer_and_use dmd_ty + in -- pprTrace "dmdAnalStar" (vcat [ppr e, ppr dmd, ppr defer_and_use, ppr dmd_ty, ppr dmd_ty']) + (dmd_ty', e') -- Main Demand Analsysis machinery dmdAnal :: AnalEnv @@ -639,7 +641,8 @@ dmdAnalRhs top_lvl rec_flag env id rhs = (fn_str, emptyDmdEnv, set_idStrictness env id fn_str, rhs) | otherwise - = (sig_ty, lazy_fv, id', mkLams bndrs' body') + = -- pprTrace "dmdAnalRhs" (vcat [ ppr id, ppr (idDemandInfo id), ppr rhs_dmd_ty, ppr sig_ty, ppr not_strict ]) + (sig_ty, lazy_fv, id', mkLams bndrs' body') where (bndrs, body) = collectBinders rhs env_body = foldl extendSigsWithLam env bndrs From git at git.haskell.org Tue Dec 3 18:10:38 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 3 Dec 2013 18:10:38 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Recover [CPR for sum types] (slightly differently) (317a8f5) Message-ID: <20131203181038.425BE2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/317a8f5982d4b7ebc943b901fd1e65759ed73e85/ghc >--------------------------------------------------------------- commit 317a8f5982d4b7ebc943b901fd1e65759ed73e85 Author: Joachim Breitner Date: Thu Nov 28 11:17:16 2013 +0000 Recover [CPR for sum types] (slightly differently) >--------------------------------------------------------------- 317a8f5982d4b7ebc943b901fd1e65759ed73e85 compiler/basicTypes/Demand.lhs | 16 +--------------- compiler/stranal/DmdAnal.lhs | 13 +++++++------ 2 files changed, 8 insertions(+), 21 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index b3fe942..7eda769 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -28,7 +28,7 @@ module Demand ( isBotRes, isTopRes, resTypeArgDmd, topRes, botRes, cprConRes, vanillaCprConRes, appIsBottom, isBottomingSig, pprIfaceStrictSig, - trimCPRInfo, returnsCPR, returnsCPR_maybe, + returnsCPR, returnsCPR_maybe, StrictSig(..), mkStrictSig, topSig, botSig, cprProdSig, isTopSig, splitStrictSig, increaseStrictSigArity, sigMayConverge, @@ -831,20 +831,6 @@ isBotRes :: DmdResult -> Bool isBotRes Diverges = True isBotRes _ = False --- TODO: This currently ignores trim_sums. Evaluate if still required, and fix --- Note [CPR for sum types] -trimCPRInfo :: Bool -> Bool -> DmdResult -> DmdResult -trimCPRInfo trim_all _trim_sums res - = trimR res - where - trimR (Converges c) = Converges (trimC c) - trimR (Dunno c) = Dunno (trimC c) - trimR Diverges = Diverges - - trimC (RetCon n rs) | trim_all = NoCPR - | otherwise = RetCon n (map trimR rs) - trimC NoCPR = NoCPR - returnsCPR :: DmdResult -> Bool returnsCPR dr = isJust (returnsCPR_maybe False dr) diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index 953b616..480f234 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -654,9 +654,10 @@ dmdAnalRhs top_lvl rec_flag env id rhs -- See Note [NOINLINE and strictness] -- See Note [Product demands for function body] - body_dmd = case deepSplitProductType_maybe (exprType body) of - Nothing -> cleanEvalDmd - Just (dc, _, _, _) -> cleanEvalProdDmd (dataConRepArity dc) + (is_sum_type, body_dmd) + = case deepSplitProductType_maybe (exprType body) of + Nothing -> (True, cleanEvalDmd) + Just (dc, _, _, _) -> (False, cleanEvalProdDmd (dataConRepArity dc)) -- See Note [Lazy and unleashable free variables] -- See Note [Aggregated demand for cardinality] @@ -666,9 +667,9 @@ dmdAnalRhs top_lvl rec_flag env id rhs (lazy_fv, sig_fv) = splitFVs is_thunk rhs_fv1 - rhs_res' = trimCPRInfo trim_all trim_sums rhs_res - trim_all = is_thunk && not_strict - trim_sums = not (isTopLevel top_lvl) -- See Note [CPR for sum types] + -- Note [CPR for sum types] + rhs_res' | is_sum_type || (is_thunk && not_strict) = topRes + | otherwise = rhs_res -- See Note [CPR for thunks] is_thunk = not (exprIsHNF rhs) From git at git.haskell.org Wed Dec 4 09:19:39 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 4 Dec 2013 09:19:39 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Add a flag -fnested-cpr-off to conveniently test the effect of nested CPR (90529b1) Message-ID: <20131204091939.3136F2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/90529b15c02ef03dcece13c267b76d470941b808/ghc >--------------------------------------------------------------- commit 90529b15c02ef03dcece13c267b76d470941b808 Author: Joachim Breitner Date: Wed Dec 4 09:14:26 2013 +0000 Add a flag -fnested-cpr-off to conveniently test the effect of nested CPR >--------------------------------------------------------------- 90529b15c02ef03dcece13c267b76d470941b808 compiler/basicTypes/Demand.lhs | 28 +++++++++++++++++++--------- compiler/main/StaticFlags.hs | 9 +++++++-- 2 files changed, 26 insertions(+), 11 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 557a9bd..e955195 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -791,20 +791,29 @@ botRes = Diverges maxCPRDepth :: Int maxCPRDepth = 3 +-- This is the depth we use with -fnested-cpr-off, in order +-- to get precisely the same behaviour as before introduction of nested cpr +-- -fnested-cpr-off can eventually be removed if nested cpr is deemd to be +-- a good thing always. +flatCPRDepth :: Int +flatCPRDepth = 1 + -- With nested CPR, DmdResult can be arbitrarily deep; consider e.g. the -- DmdResult of repeat -- -- So we need to forget information at a certain depth. We do that at all points -- where we are building RetCon constructors. -cutDmdResult :: Int -> DmdResult -> DmdResult -cutDmdResult 0 _ = topRes -cutDmdResult _ Diverges = Diverges -cutDmdResult n (Converges c) = Converges (cutCPRResult n c) -cutDmdResult n (Dunno c) = Dunno (cutCPRResult n c) - cutCPRResult :: Int -> CPRResult -> CPRResult -cutCPRResult _ NoCPR = NoCPR +cutCPRResult 0 _ = NoCPR +cutCPRResult _ NoCPR = NoCPR cutCPRResult n (RetCon tag rs) = RetCon tag (map (cutDmdResult (n-1)) rs) + where + cutDmdResult :: Int -> DmdResult -> DmdResult + cutDmdResult 0 _ = topRes + cutDmdResult _ Diverges = Diverges + cutDmdResult n (Converges c) = Converges (cutCPRResult n c) + cutDmdResult n (Dunno c) = Dunno (cutCPRResult n c) + -- Forget that something might converge for sure divergeDmdResult :: DmdResult -> DmdResult @@ -819,8 +828,9 @@ forgetCPR (Dunno _) = Dunno NoCPR cprConRes :: ConTag -> [DmdType] -> CPRResult cprConRes tag arg_tys - | opt_CprOff = NoCPR - | otherwise = cutCPRResult maxCPRDepth $ RetCon tag (map get_res arg_tys) + | opt_CprOff = NoCPR + | opt_NestedCprOff = cutCPRResult flatCPRDepth $ RetCon tag (map get_res arg_tys) + | otherwise = cutCPRResult maxCPRDepth $ RetCon tag (map get_res arg_tys) where get_res :: DmdType -> DmdResult get_res (DmdType _ [] r) = r -- Only for data-typed arguments! diff --git a/compiler/main/StaticFlags.hs b/compiler/main/StaticFlags.hs index 01dc3b7..feb7235 100644 --- a/compiler/main/StaticFlags.hs +++ b/compiler/main/StaticFlags.hs @@ -27,6 +27,7 @@ module StaticFlags ( -- optimisation opts opt_NoStateHack, opt_CprOff, + opt_NestedCprOff, opt_NoOptCoercion, -- For the parser @@ -140,7 +141,8 @@ flagsStaticNames :: [String] flagsStaticNames = [ "fno-state-hack", "fno-opt-coercion", - "fcpr-off" + "fcpr-off", + "fnested-cpr-off" ] -- We specifically need to discard static flags for clients of the @@ -195,10 +197,13 @@ opt_NoDebugOutput = lookUp (fsLit "-dno-debug-output") opt_NoStateHack :: Bool opt_NoStateHack = lookUp (fsLit "-fno-state-hack") --- Switch off CPR analysis in the new demand analyser +-- Switch off CPR analysis in the demand analyser opt_CprOff :: Bool opt_CprOff = lookUp (fsLit "-fcpr-off") +opt_NestedCprOff :: Bool +opt_NestedCprOff = lookUp (fsLit "-fnested-cpr-off") + opt_NoOptCoercion :: Bool opt_NoOptCoercion = lookUp (fsLit "-fno-opt-coercion") From git at git.haskell.org Wed Dec 4 09:19:41 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 4 Dec 2013 09:19:41 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Kill divergence information in deferType (f9a7404) Message-ID: <20131204091941.CD2652406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/f9a7404bce0a3a57015cf7402280bf525fcf5e5d/ghc >--------------------------------------------------------------- commit f9a7404bce0a3a57015cf7402280bf525fcf5e5d Author: Joachim Breitner Date: Wed Dec 4 09:16:55 2013 +0000 Kill divergence information in deferType >--------------------------------------------------------------- f9a7404bce0a3a57015cf7402280bf525fcf5e5d compiler/basicTypes/Demand.lhs | 8 ++++++-- 1 file changed, 6 insertions(+), 2 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index e955195..368468a 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -1209,15 +1209,19 @@ postProcessDmdType (True, One) ty = deferType ty postProcessDmdType (False, One) ty = ty deferType, useType, deferAndUse :: DmdType -> DmdType -deferType (DmdType fv ds _) = DmdType (deferEnv fv) (map deferDmd ds) topRes +deferType (DmdType fv ds res_ty) = DmdType (deferEnv fv) (map deferDmd ds) (deferRes res_ty) useType (DmdType fv ds res_ty) = DmdType (useEnv fv) (map useDmd ds) res_ty -deferAndUse (DmdType fv ds _) = DmdType (deferUseEnv fv) (map deferUseDmd ds) topRes +deferAndUse (DmdType fv ds res_ty) = DmdType (deferUseEnv fv) (map deferUseDmd ds) (deferRes res_ty) deferEnv, useEnv, deferUseEnv :: DmdEnv -> DmdEnv deferEnv fv = mapVarEnv deferDmd fv useEnv fv = mapVarEnv useDmd fv deferUseEnv fv = mapVarEnv deferUseDmd fv +deferRes :: DmdResult -> DmdResult +deferRes Diverges = topRes -- Kill outer divergence +deferRes r = r -- Preserve CPR info + deferDmd, useDmd, deferUseDmd :: JointDmd -> JointDmd deferDmd (JD {strd=_, absd=a}) = mkJointDmd Lazy a useDmd (JD {strd=d, absd=a}) = mkJointDmd d (markAsUsedDmd a) From johan.tibell at gmail.com Wed Dec 4 09:33:47 2013 From: johan.tibell at gmail.com (Johan Tibell) Date: Wed, 4 Dec 2013 10:33:47 +0100 Subject: [commit: ghc] wip/nested-cpr: Add a flag -fnested-cpr-off to conveniently test the effect of nested CPR (90529b1) In-Reply-To: <20131204091939.3136F2406B@ghc.haskell.org> References: <20131204091939.3136F2406B@ghc.haskell.org> Message-ID: Nitpick: don't we usually name these flags -fno-nested-cpr? On Wed, Dec 4, 2013 at 10:19 AM, wrote: > Repository : ssh://git at git.haskell.org/ghc > > On branch : wip/nested-cpr > Link : > http://ghc.haskell.org/trac/ghc/changeset/90529b15c02ef03dcece13c267b76d470941b808/ghc > > >--------------------------------------------------------------- > > commit 90529b15c02ef03dcece13c267b76d470941b808 > Author: Joachim Breitner > Date: Wed Dec 4 09:14:26 2013 +0000 > > Add a flag -fnested-cpr-off to conveniently test the effect of nested > CPR > > > >--------------------------------------------------------------- > > 90529b15c02ef03dcece13c267b76d470941b808 > compiler/basicTypes/Demand.lhs | 28 +++++++++++++++++++--------- > compiler/main/StaticFlags.hs | 9 +++++++-- > 2 files changed, 26 insertions(+), 11 deletions(-) > > diff --git a/compiler/basicTypes/Demand.lhs > b/compiler/basicTypes/Demand.lhs > index 557a9bd..e955195 100644 > --- a/compiler/basicTypes/Demand.lhs > +++ b/compiler/basicTypes/Demand.lhs > @@ -791,20 +791,29 @@ botRes = Diverges > maxCPRDepth :: Int > maxCPRDepth = 3 > > +-- This is the depth we use with -fnested-cpr-off, in order > +-- to get precisely the same behaviour as before introduction of nested > cpr > +-- -fnested-cpr-off can eventually be removed if nested cpr is deemd to be > +-- a good thing always. > +flatCPRDepth :: Int > +flatCPRDepth = 1 > + > -- With nested CPR, DmdResult can be arbitrarily deep; consider e.g. the > -- DmdResult of repeat > -- > -- So we need to forget information at a certain depth. We do that at all > points > -- where we are building RetCon constructors. > -cutDmdResult :: Int -> DmdResult -> DmdResult > -cutDmdResult 0 _ = topRes > -cutDmdResult _ Diverges = Diverges > -cutDmdResult n (Converges c) = Converges (cutCPRResult n c) > -cutDmdResult n (Dunno c) = Dunno (cutCPRResult n c) > - > cutCPRResult :: Int -> CPRResult -> CPRResult > -cutCPRResult _ NoCPR = NoCPR > +cutCPRResult 0 _ = NoCPR > +cutCPRResult _ NoCPR = NoCPR > cutCPRResult n (RetCon tag rs) = RetCon tag (map (cutDmdResult (n-1)) rs) > + where > + cutDmdResult :: Int -> DmdResult -> DmdResult > + cutDmdResult 0 _ = topRes > + cutDmdResult _ Diverges = Diverges > + cutDmdResult n (Converges c) = Converges (cutCPRResult n c) > + cutDmdResult n (Dunno c) = Dunno (cutCPRResult n c) > + > > -- Forget that something might converge for sure > divergeDmdResult :: DmdResult -> DmdResult > @@ -819,8 +828,9 @@ forgetCPR (Dunno _) = Dunno NoCPR > > cprConRes :: ConTag -> [DmdType] -> CPRResult > cprConRes tag arg_tys > - | opt_CprOff = NoCPR > - | otherwise = cutCPRResult maxCPRDepth $ RetCon tag (map get_res > arg_tys) > + | opt_CprOff = NoCPR > + | opt_NestedCprOff = cutCPRResult flatCPRDepth $ RetCon tag (map > get_res arg_tys) > + | otherwise = cutCPRResult maxCPRDepth $ RetCon tag (map > get_res arg_tys) > where > get_res :: DmdType -> DmdResult > get_res (DmdType _ [] r) = r -- Only for data-typed arguments! > diff --git a/compiler/main/StaticFlags.hs b/compiler/main/StaticFlags.hs > index 01dc3b7..feb7235 100644 > --- a/compiler/main/StaticFlags.hs > +++ b/compiler/main/StaticFlags.hs > @@ -27,6 +27,7 @@ module StaticFlags ( > -- optimisation opts > opt_NoStateHack, > opt_CprOff, > + opt_NestedCprOff, > opt_NoOptCoercion, > > -- For the parser > @@ -140,7 +141,8 @@ flagsStaticNames :: [String] > flagsStaticNames = [ > "fno-state-hack", > "fno-opt-coercion", > - "fcpr-off" > + "fcpr-off", > + "fnested-cpr-off" > ] > > -- We specifically need to discard static flags for clients of the > @@ -195,10 +197,13 @@ opt_NoDebugOutput = lookUp (fsLit > "-dno-debug-output") > opt_NoStateHack :: Bool > opt_NoStateHack = lookUp (fsLit "-fno-state-hack") > > --- Switch off CPR analysis in the new demand analyser > +-- Switch off CPR analysis in the demand analyser > opt_CprOff :: Bool > opt_CprOff = lookUp (fsLit "-fcpr-off") > > +opt_NestedCprOff :: Bool > +opt_NestedCprOff = lookUp (fsLit "-fnested-cpr-off") > + > opt_NoOptCoercion :: Bool > opt_NoOptCoercion = lookUp (fsLit "-fno-opt-coercion") > > > _______________________________________________ > ghc-commits mailing list > ghc-commits at haskell.org > http://www.haskell.org/mailman/listinfo/ghc-commits > -------------- next part -------------- An HTML attachment was scrubbed... URL: From git at git.haskell.org Wed Dec 4 09:58:51 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 4 Dec 2013 09:58:51 +0000 (UTC) Subject: [commit: testsuite] master: Update output: More elaborate GND error messages (20d7273) Message-ID: <20131204095851.68FBB2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/testsuite On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/20d7273788c9d0bc0aa002830f0c0717560a9ce4/testsuite >--------------------------------------------------------------- commit 20d7273788c9d0bc0aa002830f0c0717560a9ce4 Author: Joachim Breitner Date: Wed Dec 4 09:02:50 2013 +0000 Update output: More elaborate GND error messages >--------------------------------------------------------------- 20d7273788c9d0bc0aa002830f0c0717560a9ce4 tests/deriving/should_fail/T1496.stderr | 4 +++- tests/deriving/should_fail/T7148.stderr | 8 ++++++-- tests/deriving/should_fail/T7148a.stderr | 4 +++- tests/gadt/CasePrune.stderr | 3 ++- tests/roles/should_fail/Roles10.stderr | 3 ++- 5 files changed, 16 insertions(+), 6 deletions(-) diff --git a/tests/deriving/should_fail/T1496.stderr b/tests/deriving/should_fail/T1496.stderr index 59f70ca..a18d392 100644 --- a/tests/deriving/should_fail/T1496.stderr +++ b/tests/deriving/should_fail/T1496.stderr @@ -2,7 +2,9 @@ T1496.hs:10:32: Could not coerce from ?c Int? to ?c Moo? because ?c Int? and ?c Moo? are different types. - arising from the 'deriving' clause of a data type declaration + arising from the coercion of the method ?isInt? from type + ?forall (c :: * -> *). c Int -> c Int? to type + ?forall (c :: * -> *). c Int -> c Moo? Possible fix: use a standalone 'deriving instance' declaration, so you can specify the instance context yourself diff --git a/tests/deriving/should_fail/T7148.stderr b/tests/deriving/should_fail/T7148.stderr index ab87a27..21e350c 100644 --- a/tests/deriving/should_fail/T7148.stderr +++ b/tests/deriving/should_fail/T7148.stderr @@ -3,7 +3,9 @@ T7148.hs:27:40: Could not coerce from ?SameType b1 b? to ?SameType b1 (Tagged a b)? because the second type argument of ?SameType? has role Nominal, but the arguments ?b? and ?Tagged a b? differ - arising from the 'deriving' clause of a data type declaration + arising from the coercion of the method ?iso2? from type + ?forall b. SameType b () -> SameType b b? to type + ?forall b. SameType b () -> SameType b (Tagged a b)? Possible fix: use a standalone 'deriving instance' declaration, so you can specify the instance context yourself @@ -13,7 +15,9 @@ T7148.hs:27:40: Could not coerce from ?SameType b b1? to ?SameType (Tagged a b) b1? because the first type argument of ?SameType? has role Nominal, but the arguments ?b? and ?Tagged a b? differ - arising from the 'deriving' clause of a data type declaration + arising from the coercion of the method ?iso1? from type + ?forall b. SameType () b -> SameType b b? to type + ?forall b. SameType () b -> SameType (Tagged a b) b? Possible fix: use a standalone 'deriving instance' declaration, so you can specify the instance context yourself diff --git a/tests/deriving/should_fail/T7148a.stderr b/tests/deriving/should_fail/T7148a.stderr index 484d5aa..1984eb9 100644 --- a/tests/deriving/should_fail/T7148a.stderr +++ b/tests/deriving/should_fail/T7148a.stderr @@ -2,7 +2,9 @@ T7148a.hs:19:50: Could not coerce from ?Result a b? to ?b? because ?Result a b? and ?b? are different types. - arising from the 'deriving' clause of a data type declaration + arising from the coercion of the method ?coerce? from type + ?forall b. Proxy b -> a -> Result a b? to type + ?forall b. Proxy b -> IS_NO_LONGER a -> Result (IS_NO_LONGER a) b? Possible fix: use a standalone 'deriving instance' declaration, so you can specify the instance context yourself diff --git a/tests/gadt/CasePrune.stderr b/tests/gadt/CasePrune.stderr index 7263461..64b7157 100644 --- a/tests/gadt/CasePrune.stderr +++ b/tests/gadt/CasePrune.stderr @@ -3,7 +3,8 @@ CasePrune.hs:14:31: Could not coerce from ?T Int? to ?T A? because the first type argument of ?T? has role Nominal, but the arguments ?Int? and ?A? differ - arising from the 'deriving' clause of a data type declaration + arising from the coercion of the method ?ic? from type ?T Int? + to type ?T A? Possible fix: use a standalone 'deriving instance' declaration, so you can specify the instance context yourself diff --git a/tests/roles/should_fail/Roles10.stderr b/tests/roles/should_fail/Roles10.stderr index 230f2c9..1c63658 100644 --- a/tests/roles/should_fail/Roles10.stderr +++ b/tests/roles/should_fail/Roles10.stderr @@ -2,7 +2,8 @@ Roles10.hs:16:12: Could not coerce from ?Bool? to ?Char? because ?Bool? and ?Char? are different types. - arising from the 'deriving' clause of a data type declaration + arising from the coercion of the method ?meth? from type + ?Int -> F Int? to type ?Age -> F Age? Possible fix: use a standalone 'deriving instance' declaration, so you can specify the instance context yourself From git at git.haskell.org Wed Dec 4 09:59:01 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 4 Dec 2013 09:59:01 +0000 (UTC) Subject: [commit: ghc] master: More detailed error message when GND fails (95ba5d8) Message-ID: <20131204095902.E69332406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/95ba5d81efcf817768d65552843c7f6c4d63e340/ghc >--------------------------------------------------------------- commit 95ba5d81efcf817768d65552843c7f6c4d63e340 Author: Joachim Breitner Date: Wed Dec 4 08:42:13 2013 +0000 More detailed error message when GND fails we now print the precise class method, with types, where the coercion failed. >--------------------------------------------------------------- 95ba5d81efcf817768d65552843c7f6c4d63e340 compiler/typecheck/TcDeriv.lhs | 6 +++--- compiler/typecheck/TcErrors.lhs | 1 + compiler/typecheck/TcGenDeriv.lhs | 16 ++++++---------- compiler/typecheck/TcRnTypes.lhs | 9 ++++++++- 4 files changed, 18 insertions(+), 14 deletions(-) diff --git a/compiler/typecheck/TcDeriv.lhs b/compiler/typecheck/TcDeriv.lhs index 49111a9..bc40d80 100644 --- a/compiler/typecheck/TcDeriv.lhs +++ b/compiler/typecheck/TcDeriv.lhs @@ -1560,9 +1560,9 @@ mkNewTypeEqn dflags tvs -- newtype type; precisely the constraints required for the -- calls to coercible that we are going to generate. coercible_constraints = - mkThetaOrigin DerivOrigin $ - map (\(Pair t1 t2) -> mkCoerciblePred t1 t2) $ - mkCoerceClassMethEqn cls (varSetElemsKvsFirst dfun_tvs) inst_tys rep_inst_ty + [ let (Pair t1 t2) = mkCoerceClassMethEqn cls (varSetElemsKvsFirst dfun_tvs) inst_tys rep_inst_ty meth + in mkPredOrigin (DerivOriginCoerce meth t1 t2) (mkCoerciblePred t1 t2) + | meth <- classMethods cls ] -- If there are no tyvars, there's no need -- to abstract over the dictionaries we need diff --git a/compiler/typecheck/TcErrors.lhs b/compiler/typecheck/TcErrors.lhs index e0be85f..a28a9f5 100644 --- a/compiler/typecheck/TcErrors.lhs +++ b/compiler/typecheck/TcErrors.lhs @@ -1051,6 +1051,7 @@ mk_dict_err ctxt (ct, (matches, unifiers, safe_haskell)) drv_fixes = case orig of DerivOrigin -> [drv_fix] DerivOriginDC {} -> [drv_fix] + DerivOriginCoerce {} -> [drv_fix] _ -> [] drv_fix = hang (ptext (sLit "use a standalone 'deriving instance' declaration,")) diff --git a/compiler/typecheck/TcGenDeriv.lhs b/compiler/typecheck/TcGenDeriv.lhs index f2e5413..0040be2 100644 --- a/compiler/typecheck/TcGenDeriv.lhs +++ b/compiler/typecheck/TcGenDeriv.lhs @@ -1913,20 +1913,16 @@ mkCoerceClassMethEqn :: Class -- the class being derived -> [TyVar] -- the tvs in the instance head -> [Type] -- instance head parameters (incl. newtype) -> Type -- the representation type (already eta-reduced) - -> [Pair Type] -mkCoerceClassMethEqn cls inst_tvs cls_tys rhs_ty - = map mk_tys $ classMethods cls + -> Id -- the method to look at + -> Pair Type +mkCoerceClassMethEqn cls inst_tvs cls_tys rhs_ty id + = Pair (substTy rhs_subst user_meth_ty) (substTy lhs_subst user_meth_ty) where cls_tvs = classTyVars cls in_scope = mkInScopeSet $ mkVarSet inst_tvs lhs_subst = mkTvSubst in_scope (zipTyEnv cls_tvs cls_tys) rhs_subst = mkTvSubst in_scope (zipTyEnv cls_tvs (changeLast cls_tys rhs_ty)) - - mk_tys :: Id -> Pair Type - mk_tys id = Pair (substTy rhs_subst user_meth_ty) - (substTy lhs_subst user_meth_ty) - where - (_class_tvs, _class_constraint, user_meth_ty) = tcSplitSigmaTy (varType id) + (_class_tvs, _class_constraint, user_meth_ty) = tcSplitSigmaTy (varType id) changeLast :: [a] -> a -> [a] changeLast [] _ = panic "changeLast" @@ -1943,7 +1939,7 @@ gen_Newtype_binds :: SrcSpan gen_Newtype_binds loc cls inst_tvs cls_tys rhs_ty = listToBag $ zipWith mk_bind (classMethods cls) - (mkCoerceClassMethEqn cls inst_tvs cls_tys rhs_ty) + (map (mkCoerceClassMethEqn cls inst_tvs cls_tys rhs_ty) (classMethods cls)) where coerce_RDR = getRdrName coerceId mk_bind :: Id -> Pair Type -> LHsBind RdrName diff --git a/compiler/typecheck/TcRnTypes.lhs b/compiler/typecheck/TcRnTypes.lhs index 1b38378..2ad9b95 100644 --- a/compiler/typecheck/TcRnTypes.lhs +++ b/compiler/typecheck/TcRnTypes.lhs @@ -1780,7 +1780,10 @@ data CtOrigin | ScOrigin -- Typechecking superclasses of an instance declaration | DerivOrigin -- Typechecking deriving | DerivOriginDC DataCon Int - -- Checking constraings arising from this data an and field index + -- Checking constraints arising from this data con and field index + | DerivOriginCoerce Id Type Type + -- DerivOriginCoerce id ty1 ty2: Trying to coerce class method `id` from + -- `ty1` to `ty2`. | StandAloneDerivOrigin -- Typechecking stand-alone deriving | DefaultOrigin -- Typechecking a default decl | DoOrigin -- Arising from a do expression @@ -1822,6 +1825,10 @@ pprO (DerivOriginDC dc n) = hsep [ ptext (sLit "the"), speakNth n, ptext (sLit "field of"), quotes (ppr dc), parens (ptext (sLit "type") <+> quotes (ppr ty)) ] where ty = dataConOrigArgTys dc !! (n-1) +pprO (DerivOriginCoerce meth ty1 ty2) + = fsep [ ptext (sLit "the coercion"), ptext (sLit "of the method") + , quotes (ppr meth), ptext (sLit "from type"), quotes (ppr ty1) + , ptext (sLit "to type"), quotes (ppr ty2) ] pprO StandAloneDerivOrigin = ptext (sLit "a 'deriving' declaration") pprO DefaultOrigin = ptext (sLit "a 'default' declaration") pprO DoOrigin = ptext (sLit "a do statement") From git at git.haskell.org Wed Dec 4 10:06:44 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 4 Dec 2013 10:06:44 +0000 (UTC) Subject: [commit: ghc] master: Fix note reference [WildCard binders] (356bc56) Message-ID: <20131204100644.121152406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/356bc56cc03f94a773cfcc04e02c5fbe8caac75f/ghc >--------------------------------------------------------------- commit 356bc56cc03f94a773cfcc04e02c5fbe8caac75f Author: Joachim Breitner Date: Wed Dec 4 10:07:09 2013 +0000 Fix note reference [WildCard binders] >--------------------------------------------------------------- 356bc56cc03f94a773cfcc04e02c5fbe8caac75f compiler/prelude/PrelNames.lhs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/prelude/PrelNames.lhs b/compiler/prelude/PrelNames.lhs index 85da3ac..53cf251 100644 --- a/compiler/prelude/PrelNames.lhs +++ b/compiler/prelude/PrelNames.lhs @@ -1581,7 +1581,7 @@ wildCardKey, absentErrorIdKey, augmentIdKey, appendIdKey, realWorldPrimIdKey, recConErrorIdKey, unpackCStringUtf8IdKey, unpackCStringAppendIdKey, unpackCStringFoldrIdKey, unpackCStringIdKey :: Unique -wildCardKey = mkPreludeMiscIdUnique 0 -- See Note [WildCard] +wildCardKey = mkPreludeMiscIdUnique 0 -- See Note [WildCard binders] absentErrorIdKey = mkPreludeMiscIdUnique 1 augmentIdKey = mkPreludeMiscIdUnique 2 appendIdKey = mkPreludeMiscIdUnique 3 From git at git.haskell.org Wed Dec 4 11:46:24 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 4 Dec 2013 11:46:24 +0000 (UTC) Subject: [commit: packages/base] master: Avoid unsafeCoerce# in TopHandler (c68f564) Message-ID: <20131204114624.BCFCD2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/base On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c68f56488be342ef34a6808f32232a4dd4bd713b/base >--------------------------------------------------------------- commit c68f56488be342ef34a6808f32232a4dd4bd713b Author: Joachim Breitner Date: Wed Dec 4 10:30:45 2013 +0000 Avoid unsafeCoerce# in TopHandler instead use `... >> fail "..."` to turn IO () into IO a. >--------------------------------------------------------------- c68f56488be342ef34a6808f32232a4dd4bd713b GHC/TopHandler.lhs | 13 +++++++------ 1 file changed, 7 insertions(+), 6 deletions(-) diff --git a/GHC/TopHandler.lhs b/GHC/TopHandler.lhs index 8e50333..ee8e792 100644 --- a/GHC/TopHandler.lhs +++ b/GHC/TopHandler.lhs @@ -181,12 +181,13 @@ safeExit, fastExit :: Int -> IO a safeExit = exitHelper useSafeExit fastExit = exitHelper useFastExit +unreachable :: IO a +unreachable = fail "If you can read this, shutdownHaskellAndExit did not exit." + exitHelper :: CInt -> Int -> IO a --- we have to use unsafeCoerce# to get the 'IO a' result type, since the --- compiler doesn't let us declare that as the result type of a foreign export. #ifdef mingw32_HOST_OS exitHelper exitKind r = - unsafeCoerce# (shutdownHaskellAndExit (fromIntegral r) exitKind) + shutdownHaskellAndExit (fromIntegral r) exitKind >> unreachable #else -- On Unix we use an encoding for the ExitCode: -- 0 -- 255 normal exit code @@ -194,11 +195,11 @@ exitHelper exitKind r = -- For any invalid encoding we just use a replacement (0xff). exitHelper exitKind r | r >= 0 && r <= 255 - = unsafeCoerce# (shutdownHaskellAndExit (fromIntegral r) exitKind) + = shutdownHaskellAndExit (fromIntegral r) exitKind >> unreachable | r >= -127 && r <= -1 - = unsafeCoerce# (shutdownHaskellAndSignal (fromIntegral (-r)) exitKind) + = shutdownHaskellAndSignal (fromIntegral (-r)) exitKind >> unreachable | otherwise - = unsafeCoerce# (shutdownHaskellAndExit 0xff exitKind) + = shutdownHaskellAndExit 0xff exitKind >> unreachable foreign import ccall "shutdownHaskellAndSignal" shutdownHaskellAndSignal :: CInt -> CInt -> IO () From git at git.haskell.org Wed Dec 4 13:04:04 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 4 Dec 2013 13:04:04 +0000 (UTC) Subject: [commit: packages/base] master: Add fusion RULES for mapMaybe (de86df4) Message-ID: <20131204130404.6E8432406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/base On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/de86df4da85f704a433c546e77f0d33ad6b9ad0d/base >--------------------------------------------------------------- commit de86df4da85f704a433c546e77f0d33ad6b9ad0d Author: Takano Akio Date: Wed Nov 20 16:30:31 2013 +0900 Add fusion RULES for mapMaybe >--------------------------------------------------------------- de86df4da85f704a433c546e77f0d33ad6b9ad0d Data/Maybe.hs | 14 +++++++++++++- 1 file changed, 13 insertions(+), 1 deletion(-) diff --git a/Data/Maybe.hs b/Data/Maybe.hs index 245e307..fe2a0ab 100644 --- a/Data/Maybe.hs +++ b/Data/Maybe.hs @@ -126,4 +126,16 @@ mapMaybe f (x:xs) = case f x of Nothing -> rs Just r -> r:rs - +{-# NOINLINE [1] mapMaybe #-} + +{-# RULES +"mapMaybe" [~1] forall f xs. mapMaybe f xs + = build (\c n -> foldr (mapMaybeFB c f) n xs) +"mapMaybeList" [1] forall f. foldr (mapMaybeFB (:) f) [] = mapMaybe f + #-} + +{-# NOINLINE [0] mapMaybeFB #-} +mapMaybeFB :: (b -> r -> r) -> (a -> Maybe b) -> a -> r -> r +mapMaybeFB cons f x next = case f x of + Nothing -> next + Just r -> cons r next From git at git.haskell.org Wed Dec 4 13:17:44 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 4 Dec 2013 13:17:44 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Elaborate "non-algebraic or open body type" message (92da8cd) Message-ID: <20131204131744.5128F2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/92da8cd29e6872d1fb7228cf1f548808d0320940/ghc >--------------------------------------------------------------- commit 92da8cd29e6872d1fb7228cf1f548808d0320940 Author: Joachim Breitner Date: Wed Dec 4 09:36:04 2013 +0000 Elaborate "non-algebraic or open body type" message >--------------------------------------------------------------- 92da8cd29e6872d1fb7228cf1f548808d0320940 compiler/stranal/WwLib.lhs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/compiler/stranal/WwLib.lhs b/compiler/stranal/WwLib.lhs index 861a03b..4f2e68b 100644 --- a/compiler/stranal/WwLib.lhs +++ b/compiler/stranal/WwLib.lhs @@ -584,7 +584,8 @@ mkWWcpr_help inner ty res , \e body -> mkUnpackCase e co work_uniq data_con arg_vars (nested_decon body) ) | otherwise - -> pprPanic "mkWWcpr: non-algebraic or open body type" (ppr ty) + -> pprPanic "mkWWcpr:" $ ptext (sLit "non-algebraic or open body type") <+> + (ppr ty) <+> ptext (sLit "but CPR type") <+> ppr (res) Nothing -> do uniq <- getUniqueM let var = mk_ww_local uniq ty From git at git.haskell.org Wed Dec 4 13:17:46 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 4 Dec 2013 13:17:46 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Turn "non-algebraic or open body type" back into a warning (73d9daa) Message-ID: <20131204131746.6376D2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/73d9daa4f0d30ac9d950a58f850711a7fe5b5abd/ghc >--------------------------------------------------------------- commit 73d9daa4f0d30ac9d950a58f850711a7fe5b5abd Author: Joachim Breitner Date: Wed Dec 4 09:55:04 2013 +0000 Turn "non-algebraic or open body type" back into a warning >--------------------------------------------------------------- 73d9daa4f0d30ac9d950a58f850711a7fe5b5abd compiler/stranal/WwLib.lhs | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/compiler/stranal/WwLib.lhs b/compiler/stranal/WwLib.lhs index 4f2e68b..ffc7d4c 100644 --- a/compiler/stranal/WwLib.lhs +++ b/compiler/stranal/WwLib.lhs @@ -584,8 +584,10 @@ mkWWcpr_help inner ty res , \e body -> mkUnpackCase e co work_uniq data_con arg_vars (nested_decon body) ) | otherwise - -> pprPanic "mkWWcpr:" $ ptext (sLit "non-algebraic or open body type") <+> - (ppr ty) <+> ptext (sLit "but CPR type") <+> ppr (res) + -> -- I would be happier if this were a error, but there are nasty corner cases. + WARN ( True, ptext (sLit "mkWwcpr: non-algebraic or open body type") <+> + (ppr ty) <+> ptext (sLit "but CPR type") <+> ppr (res) ) + mkWWcpr_help inner ty topRes Nothing -> do uniq <- getUniqueM let var = mk_ww_local uniq ty From git at git.haskell.org Wed Dec 4 13:17:48 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 4 Dec 2013 13:17:48 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Use mkWildCase in mkUnpackCase in WwLib (2643b5e) Message-ID: <20131204131749.BD0C42406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/2643b5e4d356ff28f617ac7d7985dbc3c1cf5ca0/ghc >--------------------------------------------------------------- commit 2643b5e4d356ff28f617ac7d7985dbc3c1cf5ca0 Author: Joachim Breitner Date: Wed Dec 4 10:11:30 2013 +0000 Use mkWildCase in mkUnpackCase in WwLib >--------------------------------------------------------------- 2643b5e4d356ff28f617ac7d7985dbc3c1cf5ca0 compiler/stranal/WwLib.lhs | 26 +++++++++++--------------- 1 file changed, 11 insertions(+), 15 deletions(-) diff --git a/compiler/stranal/WwLib.lhs b/compiler/stranal/WwLib.lhs index ffc7d4c..d7c0fd2 100644 --- a/compiler/stranal/WwLib.lhs +++ b/compiler/stranal/WwLib.lhs @@ -17,7 +17,7 @@ import Id ( Id, idType, mkSysLocal, idDemandInfo, setIdDemandInfo, import IdInfo ( vanillaIdInfo ) import DataCon import Demand -import MkCore ( mkRuntimeErrorApp, aBSENT_ERROR_ID, mkCoreLet ) +import MkCore ( mkRuntimeErrorApp, aBSENT_ERROR_ID, mkCoreLet, mkWildCase ) import MkId ( voidArgId, voidPrimId ) import TysPrim ( voidPrimTy ) import TysWiredIn ( tupleCon ) @@ -448,11 +448,10 @@ mkWWstr_one dflags arg <- deepSplitProductType_maybe (idType arg) , cs `equalLength` inst_con_arg_tys -- See Note [mkWWstr and unsafeCore] - = do { (uniq1:uniqs) <- getUniquesM + = do { uniqs <- getUniquesM ; let unpk_args = zipWith mk_ww_local uniqs inst_con_arg_tys unpk_args_w_ds = zipWithEqual "mkWWstr" set_worker_arg_info unpk_args cs - unbox_fn = mkUnpackCase (Var arg) co uniq1 - data_con unpk_args + unbox_fn = mkUnpackCase (Var arg) co data_con unpk_args rebox_fn = Let (NonRec arg con_app) con_app = mkConApp2 data_con inst_tys unpk_args `mkCast` mkSymCo co ; (worker_args, wrap_fn, work_fn) <- mkWWstr dflags unpk_args_w_ds @@ -576,12 +575,10 @@ mkWWcpr_help inner ty res nested_arg_vars = concat nested_arg_varss nested_decon = foldr (.) id $ zipWith id arg_decons (map Var arg_vars) - work_uniq <- getUniqueM - return ( nested_arg_vars , mkConApp data_con (map Type inst_tys ++ arg_cons) `mkCast` mkSymCo co - , \e body -> mkUnpackCase e co work_uniq data_con arg_vars (nested_decon body) + , \e body -> mkUnpackCase e co data_con arg_vars (nested_decon body) ) | otherwise -> -- I would be happier if this were a error, but there are nasty corner cases. @@ -602,19 +599,18 @@ mkRename :: CoreExpr -> Var -> CoreExpr -> CoreExpr mkRename e v body = ASSERT( idType v `eqType` exprType e) mkCoreLet (NonRec v e) body -mkUnpackCase :: CoreExpr -> Coercion -> Unique -> DataCon -> [Id] -> CoreExpr -> CoreExpr --- (mkUnpackCase e co uniq Con args body) +mkUnpackCase :: CoreExpr -> Coercion -> DataCon -> [Id] -> CoreExpr -> CoreExpr +-- (mkUnpackCase e co Con args body) -- returns --- case e |> co of bndr { Con args -> body } +-- case e |> co of _ { Con args -> body } -mkUnpackCase (Tick tickish e) co uniq con args body -- See Note [Profiling and unpacking] - = Tick tickish (mkUnpackCase e co uniq con args body) -mkUnpackCase scrut co uniq boxing_con unpk_args body - = Case casted_scrut bndr (exprType body) +mkUnpackCase (Tick tickish e) co con args body -- See Note [Profiling and unpacking] + = Tick tickish (mkUnpackCase e co con args body) +mkUnpackCase scrut co boxing_con unpk_args body + = mkWildCase casted_scrut (exprType casted_scrut) (exprType body) [(DataAlt boxing_con, unpk_args, body)] where casted_scrut = scrut `mkCast` co - bndr = mk_ww_local uniq (exprType casted_scrut) \end{code} Note [Profiling and unpacking] From git at git.haskell.org Wed Dec 4 13:17:50 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 4 Dec 2013 13:17:50 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: More precisely recover [CPR for sum types] behaviour (6449837) Message-ID: <20131204131750.C4A0D2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/64498375b347186c0c146805b71305d75791e2be/ghc >--------------------------------------------------------------- commit 64498375b347186c0c146805b71305d75791e2be Author: Joachim Breitner Date: Wed Dec 4 12:11:09 2013 +0000 More precisely recover [CPR for sum types] behaviour >--------------------------------------------------------------- 64498375b347186c0c146805b71305d75791e2be compiler/stranal/DmdAnal.lhs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index 3bb197b..686c4de 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -668,7 +668,8 @@ dmdAnalRhs top_lvl rec_flag env id rhs (lazy_fv, sig_fv) = splitFVs is_thunk rhs_fv1 -- Note [CPR for sum types] - rhs_res' | is_sum_type || (is_thunk && not_strict) = forgetCPR rhs_res + rhs_res' | (is_sum_type && not (isTopLevel top_lvl)) || + (is_thunk && not_strict) = forgetCPR rhs_res | otherwise = rhs_res -- See Note [CPR for thunks] From git at git.haskell.org Wed Dec 4 13:41:16 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 4 Dec 2013 13:41:16 +0000 (UTC) Subject: [commit: ghc] master: Comments only (cd03893) Message-ID: <20131204134116.C430D2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/cd038938ba0c98f81a3ac2e047f8a4f46f4982bd/ghc >--------------------------------------------------------------- commit cd038938ba0c98f81a3ac2e047f8a4f46f4982bd Author: Simon Peyton Jones Date: Wed Dec 4 13:40:43 2013 +0000 Comments only >--------------------------------------------------------------- cd038938ba0c98f81a3ac2e047f8a4f46f4982bd compiler/typecheck/TcInteract.lhs | 5 ++++- compiler/typecheck/TcRnTypes.lhs | 19 ++++++++++++------- 2 files changed, 16 insertions(+), 8 deletions(-) diff --git a/compiler/typecheck/TcInteract.lhs b/compiler/typecheck/TcInteract.lhs index f2289b1..b6a62af 100644 --- a/compiler/typecheck/TcInteract.lhs +++ b/compiler/typecheck/TcInteract.lhs @@ -517,7 +517,10 @@ interactFunEq inerts workItem@(CFunEqCan { cc_ev = ev, cc_fun = tc ; return (Just (inerts { inert_funeqs = replaceFunEqs funeqs tc args workItem }), True) } | (CFunEqCan { cc_rhs = rhs_i } : _) <- matching_inerts - = do { mb <- newDerived loc (mkTcEqPred rhs_i rhs) + = -- We have F ty ~ r1, F ty ~ r2, but neither can rewrite the other; + -- for example, they might both be Derived, or both Wanted + -- So we generate a new derived equality r1~r2 + do { mb <- newDerived loc (mkTcEqPred rhs_i rhs) ; case mb of Just x -> updWorkListTcS (extendWorkListEq (mkNonCanonical x)) Nothing -> return () diff --git a/compiler/typecheck/TcRnTypes.lhs b/compiler/typecheck/TcRnTypes.lhs index 2ad9b95..e71d73a 100644 --- a/compiler/typecheck/TcRnTypes.lhs +++ b/compiler/typecheck/TcRnTypes.lhs @@ -1057,7 +1057,7 @@ ctPred :: Ct -> PredType ctPred ct = ctEvPred (cc_ev ct) dropDerivedWC :: WantedConstraints -> WantedConstraints --- See Note [Insoluble derived constraints] +-- See Note [Dropping derived constraints] dropDerivedWC wc@(WC { wc_flat = flats, wc_insol = insols }) = wc { wc_flat = filterBag isWantedCt flats , wc_insol = filterBag (not . isDerivedCt) insols } @@ -1065,10 +1065,14 @@ dropDerivedWC wc@(WC { wc_flat = flats, wc_insol = insols }) -- The implications are (recursively) already filtered \end{code} -Note [Insoluble derived constraints] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Note [Dropping derived constraints] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ In general we discard derived constraints at the end of constraint solving; -see dropDerivedWC. For example, +see dropDerivedWC. A consequence is that + we never report an error for a derived constraint, + and hence we do not need to take much care with their CtLoc + +For example, * If we have an unsolved (Ord a), we don't want to complain about an unsolved (Eq a) as well. @@ -1080,9 +1084,10 @@ Notably, functional dependencies. If we have class C a b | a -> b and we have [W] C a b, [W] C a c -where a,b,c are all signature variables. Then we could reasonably -report an error unifying (b ~ c). But it's probably not worth it; -after all, we also get an error because we can't discharge the constraint. +where a,b,c are all signature variables. Then we could imagine +reporting an error unifying (b ~ c). But it's better to report that we can't +solve (C a b) and (C a c) since those arose directly from something the +programmer wrote. %************************************************************************ From git at git.haskell.org Wed Dec 4 13:41:18 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 4 Dec 2013 13:41:18 +0000 (UTC) Subject: [commit: ghc] master: Comments only (e122154) Message-ID: <20131204134118.E9BD62406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e1221541ec1587c8bb6a637afd09490566dbdd0e/ghc >--------------------------------------------------------------- commit e1221541ec1587c8bb6a637afd09490566dbdd0e Author: Simon Peyton Jones Date: Mon Dec 2 16:49:22 2013 +0000 Comments only >--------------------------------------------------------------- e1221541ec1587c8bb6a637afd09490566dbdd0e compiler/typecheck/TcSMonad.lhs | 19 +++++++++---------- 1 file changed, 9 insertions(+), 10 deletions(-) diff --git a/compiler/typecheck/TcSMonad.lhs b/compiler/typecheck/TcSMonad.lhs index ba46248..78ecea1 100644 --- a/compiler/typecheck/TcSMonad.lhs +++ b/compiler/typecheck/TcSMonad.lhs @@ -1651,22 +1651,21 @@ xCtFlavor (CtDerived { ctev_loc = loc }) ptys _xev ; return (catMaybes ders) } ----------------------------- -rewriteCtFlavor :: CtEvidence +rewriteCtFlavor :: CtEvidence -- old evidence -> TcPredType -- new predicate - -> TcCoercion -- new ~ old + -> TcCoercion -- Of type :: new predicate ~ -> TcS (Maybe CtEvidence) --- Returns Just new_fl iff either (i) 'co' is reflexivity +-- Returns Just new_ev iff either (i) 'co' is reflexivity -- or (ii) 'co' is not reflexivity, and 'new_pred' not cached --- In either case, there is nothing new to do with new_fl +-- In either case, there is nothing new to do with new_ev {- - rewriteCtFlavor old_fl new_pred co + rewriteCtFlavor old_ev new_pred co Main purpose: create new evidence for new_pred; unless new_pred is cached already -* Returns a new_fl : new_pred, with same wanted/given/derived flag as old_fl -* If old_fl was wanted, create a binding for old_fl, in terms of new_fl -* If old_fl was given, AND not cached, create a binding for new_fl, in terms of old_fl -* Returns Nothing if new_fl is already cached - +* Returns a new_ev : new_pred, with same wanted/given/derived flag as old_ev +* If old_ev was wanted, create a binding for old_ev, in terms of new_ev +* If old_ev was given, AND not cached, create a binding for new_ev, in terms of old_ev +* Returns Nothing if new_ev is already cached Old evidence New predicate is Return new evidence flavour of same flavor From git at git.haskell.org Wed Dec 4 13:41:20 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 4 Dec 2013 13:41:20 +0000 (UTC) Subject: [commit: ghc] master: Improve ASSERT (b67f503) Message-ID: <20131204134120.ECDB72406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b67f50350e6d15049ba2110b31dd63f20db27746/ghc >--------------------------------------------------------------- commit b67f50350e6d15049ba2110b31dd63f20db27746 Author: Simon Peyton Jones Date: Mon Dec 2 16:49:57 2013 +0000 Improve ASSERT >--------------------------------------------------------------- b67f50350e6d15049ba2110b31dd63f20db27746 compiler/basicTypes/Demand.lhs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 42590c9..cd844a1 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -437,7 +437,7 @@ seqMaybeUsed _ = () splitUseProdDmd :: Int -> UseDmd -> [MaybeUsed] splitUseProdDmd n Used = replicate n useTop splitUseProdDmd n UHead = replicate n Abs -splitUseProdDmd n (UProd ds) = ASSERT( ds `lengthIs` n ) ds +splitUseProdDmd n (UProd ds) = ASSERT2( ds `lengthIs` n, ppr n $$ ppr ds ) ds splitUseProdDmd _ d@(UCall _ _) = pprPanic "attempt to prod-split usage call demand" (ppr d) \end{code} From git at git.haskell.org Wed Dec 4 15:47:21 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 4 Dec 2013 15:47:21 +0000 (UTC) Subject: [commit: ghc] master: Untab ClosureTypes.h and ClosureFlags.c (4f603db) Message-ID: <20131204154721.B66B32406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4f603db253434ba0758142c42109d02c95a0ceda/ghc >--------------------------------------------------------------- commit 4f603db253434ba0758142c42109d02c95a0ceda Author: Patrick Palka Date: Tue Dec 3 10:27:14 2013 -0500 Untab ClosureTypes.h and ClosureFlags.c >--------------------------------------------------------------- 4f603db253434ba0758142c42109d02c95a0ceda includes/rts/storage/ClosureTypes.h | 76 ++++++++++++++++---------------- rts/ClosureFlags.c | 82 +++++++++++++++++------------------ 2 files changed, 79 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 4f603db253434ba0758142c42109d02c95a0ceda From git at git.haskell.org Wed Dec 4 16:00:45 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 4 Dec 2013 16:00:45 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Comments and small refactor (052d78b) Message-ID: <20131204160045.465462406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/052d78b0851b46eec7eb9c4d075af443b5def704/ghc >--------------------------------------------------------------- commit 052d78b0851b46eec7eb9c4d075af443b5def704 Author: Simon Peyton Jones Date: Wed Dec 4 16:00:24 2013 +0000 Comments and small refactor >--------------------------------------------------------------- 052d78b0851b46eec7eb9c4d075af443b5def704 compiler/basicTypes/Demand.lhs | 8 ++++---- compiler/stranal/DmdAnal.lhs | 41 +++++++++++++++++++++------------------- 2 files changed, 26 insertions(+), 23 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 368468a..1af645f 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -723,16 +723,16 @@ We have lubs, but not glbs; but that is ok. -- Constructed Product Result ------------------------------------------------------------------------ -data CPRResult = NoCPR -- Top of the lattice - | RetCon ConTag [DmdResult] -- Returns a constructor from a data type - deriving( Eq, Show ) - data DmdResult = Diverges -- Definitely diverges | Converges CPRResult -- Definitely converges | Dunno CPRResult -- Might diverge or converge, but in the latter case the -- result shape is described by CPRResult deriving( Eq, Show ) +data CPRResult = NoCPR -- Top of the lattice + | RetCon ConTag [DmdResult] -- Returns a constructor from a data type + deriving( Eq, Show ) + lubCPR :: CPRResult -> CPRResult -> CPRResult lubCPR (RetCon ct1 ds1) (RetCon ct2 ds2) | ct1 == ct2 diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index 686c4de..a029fff 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -523,34 +523,37 @@ dmdAnalVarApp env dmd fun args -- , ppr arg_tys, ppr cpr_info, ppr res_ty]) $ ( res_ty , foldl App (Var fun) args') - - | otherwise - = --pprTrace "dmdAnalVarApp" (vcat [ ppr fun, ppr args, ppr n_val_args - -- , ppr dmd - -- , ppr (mkCallDmdN n_val_args dmd) - -- , ppr $ dmdTransform env fun (mkCallDmdN n_val_args dmd) - -- , ppr $ completeApp env (dmdTransform env fun (mkCallDmdN n_val_args dmd), Var fun) args - -- ]) - completeApp env (dmdTransform env fun (mkCallDmdN n_val_args dmd), Var fun) args where n_val_args = valArgCount args - cxt_ds = splitProdCleanDmd n_val_args dmd - (arg_tys, args') = anal_args cxt_ds args - -- The constructor itself is lazy + cxt_ds = splitProdCleanDmd n_val_args dmd + (arg_tys, args') = anal_con_args cxt_ds args + -- The constructor itself is lazy, so we don't need to look at the + -- strictness signature on the data constructor. Instead just + -- propagate demand from the context into the constructor arguments -- See Note [Data-con worker strictness] in MkId - anal_args :: [Demand] -> [CoreExpr] -> ([DmdType], [CoreExpr]) - anal_args _ [] = ([],[]) - anal_args ds (arg : args) + anal_con_args :: [Demand] -> [CoreExpr] -> ([DmdType], [CoreExpr]) + anal_con_args _ [] = ([],[]) + anal_con_args ds (arg : args) | isTypeArg arg - , (arg_tys, args') <- anal_args ds args + , (arg_tys, args') <- anal_con_args ds args = (arg_tys, arg:args') - anal_args (d:ds) (arg : args) + anal_con_args (d:ds) (arg : args) | (arg_ty, arg') <- dmdAnalArg env d arg - , (arg_tys, args') <- anal_args ds args + , (arg_tys, args') <- anal_con_args ds args = --pprTrace "dmdAnalVarApp arg" (vcat [ ppr d, ppr arg, ppr arg_ty, ppr arg' ]) (arg_ty:arg_tys, arg':args') - anal_args ds args = pprPanic "anal_args" (ppr args $$ ppr ds) + anal_con_args ds args = pprPanic "anal_con_args" (ppr args $$ ppr ds) + + +dmdAnalVarApp env dmd fun args + | otherwise -- Not a saturated constructor + = --pprTrace "dmdAnalVarApp" (vcat [ ppr fun, ppr args, ppr n_val_args + -- , ppr dmd + -- , ppr $ dmdTransform env fun (mkCallDmdN n_val_args dmd) + -- , ppr $ completeApp env (dmdTransform env fun (mkCallDmdN n_val_args dmd), Var fun) args + -- ]) + completeApp env (dmdTransform env fun (mkCallDmdN (valArgCount args) dmd), Var fun) args \end{code} %************************************************************************ From git at git.haskell.org Wed Dec 4 16:56:25 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 4 Dec 2013 16:56:25 +0000 (UTC) Subject: [commit: ghc] master: Remove code that generates FunDep error message context (9d7cbbc) Message-ID: <20131204165625.D4EEC2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9d7cbbcf625bc103d9fd086e9fcf99cb5c4b56ea/ghc >--------------------------------------------------------------- commit 9d7cbbcf625bc103d9fd086e9fcf99cb5c4b56ea Author: Joachim Breitner Date: Wed Dec 4 15:47:49 2013 +0000 Remove code that generates FunDep error message context as it seems that this code is now dead (due to [Dropping derived constraints]) (See #8592) >--------------------------------------------------------------- 9d7cbbcf625bc103d9fd086e9fcf99cb5c4b56ea compiler/typecheck/FunDeps.lhs | 27 +++++++++++---------------- compiler/typecheck/TcInteract.lhs | 35 ++++++----------------------------- 2 files changed, 17 insertions(+), 45 deletions(-) diff --git a/compiler/typecheck/FunDeps.lhs b/compiler/typecheck/FunDeps.lhs index 202ef1a..1dc96aa 100644 --- a/compiler/typecheck/FunDeps.lhs +++ b/compiler/typecheck/FunDeps.lhs @@ -133,12 +133,10 @@ unification variables when producing the FD constraints. Finally, the position parameters will help us rewrite the wanted constraint ``on the spot'' \begin{code} -type Pred_Loc = (PredType, SDoc) -- SDoc says where the Pred comes from - data Equation = FDEqn { fd_qtvs :: [TyVar] -- Instantiate these type and kind vars to fresh unification vars , fd_eqs :: [FDEq] -- and then make these equal - , fd_pred1, fd_pred2 :: Pred_Loc } -- The Equation arose from + , fd_pred1, fd_pred2 :: PredType } -- The Equation arose from -- combining these two constraints data FDEq = FDEq { fd_pos :: Int -- We use '0' for the first position @@ -213,14 +211,14 @@ zipAndComputeFDEqs _ _ _ = [] -- Improve a class constraint from another class constraint -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -improveFromAnother :: Pred_Loc -- Template item (usually given, or inert) - -> Pred_Loc -- Workitem [that can be improved] +improveFromAnother :: PredType -- Template item (usually given, or inert) + -> PredType -- Workitem [that can be improved] -> [Equation] -- Post: FDEqs always oriented from the other to the workitem -- Equations have empty quantified variables -improveFromAnother pred1@(ty1, _) pred2@(ty2, _) - | Just (cls1, tys1) <- getClassPredTys_maybe ty1 - , Just (cls2, tys2) <- getClassPredTys_maybe ty2 +improveFromAnother pred1 pred2 + | Just (cls1, tys1) <- getClassPredTys_maybe pred1 + , Just (cls2, tys2) <- getClassPredTys_maybe pred2 , tys1 `lengthAtLeast` 2 && cls1 == cls2 = [ FDEqn { fd_qtvs = [], fd_eqs = eqs, fd_pred1 = pred1, fd_pred2 = pred2 } | let (cls_tvs, cls_fds) = classTvsFds cls1 @@ -243,15 +241,15 @@ pprEquation (FDEqn { fd_qtvs = qtvs, fd_eqs = pairs }) nest 2 (vcat [ ppr t1 <+> ptext (sLit "~") <+> ppr t2 | (FDEq _ t1 t2) <- pairs])] improveFromInstEnv :: (InstEnv,InstEnv) - -> Pred_Loc + -> PredType -> [Equation] -- Needs to be an Equation because -- of quantified variables -- Post: Equations oriented from the template (matching instance) to the workitem! -improveFromInstEnv _inst_env (pred,_loc) +improveFromInstEnv _inst_env pred | not (isClassPred pred) = panic "improveFromInstEnv: not a class predicate" -improveFromInstEnv inst_env pred@(ty, _) - | Just (cls, tys) <- getClassPredTys_maybe ty +improveFromInstEnv inst_env pred + | Just (cls, tys) <- getClassPredTys_maybe pred , tys `lengthAtLeast` 2 , let (cls_tvs, cls_fds) = classTvsFds cls instances = classInstances inst_env cls @@ -267,10 +265,7 @@ improveFromInstEnv inst_env pred@(ty, _) , ispec <- instances , (meta_tvs, eqs) <- checkClsFD fd cls_tvs ispec emptyVarSet tys trimmed_tcs -- NB: orientation - , let p_inst = (mkClassPred cls (is_tys ispec), - sep [ ptext (sLit "arising from the dependency") <+> quotes (pprFunDep fd) - , ptext (sLit "in the instance declaration") - <+> pprNameDefnLoc (getName ispec)]) + , let p_inst = mkClassPred cls (is_tys ispec) ] improveFromInstEnv _ _ = [] diff --git a/compiler/typecheck/TcInteract.lhs b/compiler/typecheck/TcInteract.lhs index b6a62af..4323888 100644 --- a/compiler/typecheck/TcInteract.lhs +++ b/compiler/typecheck/TcInteract.lhs @@ -31,8 +31,6 @@ import FamInstEnv ( FamInstEnvs, instNewTyConTF_maybe ) import TcEvidence import Outputable -import TcMType ( zonkTcPredType ) - import TcRnTypes import TcErrors import TcSMonad @@ -411,13 +409,8 @@ interactGivenIP _ wi = pprPanic "interactGivenIP" (ppr wi) addFunDepWork :: Ct -> Ct -> TcS () addFunDepWork work_ct inert_ct - = do { let work_loc = ctLoc work_ct - inert_loc = ctLoc inert_ct - inert_pred_loc = (ctPred inert_ct, pprArisingAt inert_loc) - work_item_pred_loc = (ctPred work_ct, pprArisingAt work_loc) - - ; let fd_eqns = improveFromAnother inert_pred_loc work_item_pred_loc - ; fd_work <- rewriteWithFunDeps fd_eqns work_loc + = do { let fd_eqns = improveFromAnother (ctPred inert_ct) (ctPred work_ct) + ; fd_work <- rewriteWithFunDeps fd_eqns (ctLoc work_ct) -- We don't really rewrite tys2, see below _rewritten_tys2, so that's ok -- NB: We do create FDs for given to report insoluble equations that arise -- from pairs of Givens, and also because of floating when we approximate @@ -1355,20 +1348,17 @@ rewriteWithFunDeps eqn_pred_locs loc instFunDepEqn :: CtLoc -> Equation -> TcS [Ct] -- Post: Returns the position index as well as the corresponding FunDep equality -instFunDepEqn loc (FDEqn { fd_qtvs = tvs, fd_eqs = eqs - , fd_pred1 = d1, fd_pred2 = d2 }) +instFunDepEqn loc (FDEqn { fd_qtvs = tvs, fd_eqs = eqs }) = do { (subst, _) <- instFlexiTcS tvs -- Takes account of kind substitution ; foldM (do_one subst) [] eqs } where - der_loc = pushErrCtxt FunDepOrigin (False, mkEqnMsg d1 d2) loc - do_one subst ievs (FDEq { fd_ty_left = ty1, fd_ty_right = ty2 }) | tcEqType sty1 sty2 = return ievs -- Return no trivial equalities | otherwise - = do { mb_eqv <- newDerived der_loc (mkTcEqPred sty1 sty2) + = do { mb_eqv <- newDerived loc (mkTcEqPred sty1 sty2) ; case mb_eqv of - Just ev -> return (mkNonCanonical (ev {ctev_loc = der_loc}) : ievs) + Just ev -> return (mkNonCanonical (ev {ctev_loc = loc}) : ievs) Nothing -> return ievs } -- We are eventually going to emit FD work back in the work list so -- it is important that we only return the /freshly created/ and not @@ -1376,18 +1366,6 @@ instFunDepEqn loc (FDEqn { fd_qtvs = tvs, fd_eqs = eqs where sty1 = Type.substTy subst ty1 sty2 = Type.substTy subst ty2 - -mkEqnMsg :: (TcPredType, SDoc) - -> (TcPredType, SDoc) -> TidyEnv -> TcM (TidyEnv, SDoc) -mkEqnMsg (pred1,from1) (pred2,from2) tidy_env - = do { zpred1 <- zonkTcPredType pred1 - ; zpred2 <- zonkTcPredType pred2 - ; let { tpred1 = tidyType tidy_env zpred1 - ; tpred2 = tidyType tidy_env zpred2 } - ; let msg = vcat [ptext (sLit "When using functional dependencies to combine"), - nest 2 (sep [ppr tpred1 <> comma, nest 2 from1]), - nest 2 (sep [ppr tpred2 <> comma, nest 2 from2])] - ; return (tidy_env, msg) } \end{code} @@ -1459,7 +1437,6 @@ doTopReactDict inerts fl cls xis ; solve_from_instance wtvs ev_term } NoInstance -> try_fundeps_and_return } where - arising_sdoc = pprArisingAt loc dict_id = ctEvId fl pred = mkClassPred cls xis loc = ctev_loc fl @@ -1492,7 +1469,7 @@ doTopReactDict inerts fl cls xis -- so we make sure we get on and solve it first. See Note [Weird fundeps] try_fundeps_and_return = do { instEnvs <- getInstEnvs - ; let fd_eqns = improveFromInstEnv instEnvs (pred, arising_sdoc) + ; let fd_eqns = improveFromInstEnv instEnvs pred ; fd_work <- rewriteWithFunDeps fd_eqns loc ; unless (null fd_work) (updWorkListTcS (extendWorkListEqs fd_work)) ; return NoTopInt } From git at git.haskell.org Wed Dec 4 18:05:56 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 4 Dec 2013 18:05:56 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Move peelFV from DmdAnal to Demand (0dca497) Message-ID: <20131204180556.2F1412406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/0dca497357f158f735aacf7287baa1db003bee51/ghc >--------------------------------------------------------------- commit 0dca497357f158f735aacf7287baa1db003bee51 Author: Joachim Breitner Date: Wed Dec 4 16:09:34 2013 +0000 Move peelFV from DmdAnal to Demand >--------------------------------------------------------------- 0dca497357f158f735aacf7287baa1db003bee51 compiler/basicTypes/Demand.lhs | 20 ++++++++++++++++++-- compiler/stranal/DmdAnal.lhs | 31 ++++++++++--------------------- 2 files changed, 28 insertions(+), 23 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 368468a..dbae6bd 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -20,9 +20,10 @@ module Demand ( DmdType(..), dmdTypeDepth, lubDmdType, bothDmdEnv, bothDmdType, bothDmdTypeCase, topDmdType, botDmdType, mkDmdType, mkTopDmdType, - dmdTypeArgTop, + dmdTypeArgTop, addDemand, DmdEnv, emptyDmdEnv, + peelFV, DmdResult(..), CPRResult(..), isBotRes, isTopRes, resTypeArgDmd, @@ -57,12 +58,13 @@ module Demand ( import StaticFlags import DynFlags import Outputable +import Var ( Var ) import VarEnv import UniqFM import Util import BasicTypes import Binary -import Maybes ( isJust, expectJust ) +import Maybes ( isJust, expectJust, orElse ) import Type ( Type ) import TyCon ( isNewTyCon, isClassTyCon ) @@ -1257,6 +1259,20 @@ peelManyCalls arg_ds (CD { sd = str, ud = abs }) go_abs [] _ = One -- one UCall Many in the demand go_abs (_:as) (UCall One d') = go_abs as d' go_abs _ _ = Many + + +peelFV :: DmdType -> Var -> (DmdType, Demand) +peelFV (DmdType fv ds res) id = -- pprTrace "rfv" (ppr id <+> ppr dmd $$ ppr fv) + (DmdType fv' ds res, dmd) + where + fv' = fv `delVarEnv` id + dmd = lookupVarEnv fv id `orElse` deflt + -- See note [Default demand for variables] + deflt | isBotRes res = botDmd + | otherwise = absDmd + +addDemand :: Demand -> DmdType -> DmdType +addDemand dmd (DmdType fv ds res) = DmdType fv (dmd:ds) res \end{code} Note [Always analyse in virgin pass] diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index 686c4de..2e33ca8 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -32,7 +32,7 @@ import Type ( eqType ) -- import Pair -- import Coercion ( coercionKind ) import Util -import Maybes ( isJust, orElse ) +import Maybes ( isJust ) import TysWiredIn ( unboxedPairDataCon ) import TysPrim ( realWorldStatePrimTy ) \end{code} @@ -766,16 +766,6 @@ addLazyFVs dmd_ty lazy_fvs -- which floats out of the defn for h. Without the modifyEnv, that -- L demand doesn't get both'd with the Bot coming up from the inner -- call to f. So we just get an L demand for x for g. - -peelFV :: DmdEnv -> Var -> DmdResult -> (DmdEnv, Demand) -peelFV fv id res = -- pprTrace "rfv" (ppr id <+> ppr dmd $$ ppr fv) - (fv', dmd) - where - fv' = fv `delVarEnv` id - dmd = lookupVarEnv fv id `orElse` deflt - -- See note [Default demand for variables] - deflt | isBotRes res = botDmd - | otherwise = absDmd \end{code} Note [Default demand for variables] @@ -801,11 +791,11 @@ annotateBndr :: AnalEnv -> DmdType -> Var -> (DmdType, Var) -- The returned var is annotated with demand info -- according to the result demand of the provided demand type -- No effect on the argument demands -annotateBndr env dmd_ty@(DmdType fv ds res) var +annotateBndr env dmd_ty var | isTyVar var = (dmd_ty, var) - | otherwise = (DmdType fv' ds res, set_idDemandInfo env var dmd') + | otherwise = (dmd_ty', set_idDemandInfo env var dmd') where - (fv', dmd) = peelFV fv var res + (dmd_ty', dmd) = peelFV dmd_ty var dmd' | gopt Opt_DictsStrict (ae_dflags env) -- We never want to strictify a recursive let. At the moment @@ -826,13 +816,13 @@ annotateLamBndrs env args_of_dfun ty bndrs = mapAccumR annotate ty bndrs annotateLamIdBndr :: AnalEnv -> DFunFlag -- is this lambda at the top of the RHS of a dfun? - -> DmdType -- Demand type of body + -> DmdType -- Demand type of body -> Count -- One-shot-ness of the lambda - -> Id -- Lambda binder - -> (DmdType, -- Demand type of lambda + -> Id -- Lambda binder + -> (DmdType, -- Demand type of lambda Id) -- and binder annotated with demand -annotateLamIdBndr env arg_of_dfun _dmd_ty@(DmdType fv ds res) one_shot id +annotateLamIdBndr env arg_of_dfun dmd_ty one_shot id -- For lambdas we add the demand to the argument demands -- Only called for Ids = ASSERT( isId id ) @@ -846,9 +836,8 @@ annotateLamIdBndr env arg_of_dfun _dmd_ty@(DmdType fv ds res) one_shot id where (unf_ty, _) = dmdAnalStar env dmd unf - main_ty = DmdType fv' (dmd:ds) res - - (fv', dmd) = peelFV fv id res + main_ty = addDemand dmd dmd_ty' + (dmd_ty', dmd) = peelFV dmd_ty id dmd' | gopt Opt_DictsStrict (ae_dflags env), -- see Note [do not strictify the argument dictionaries of a dfun] From git at git.haskell.org Wed Dec 4 18:05:58 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 4 Dec 2013 18:05:58 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Put bothDmdResult back into bothDmdType (7a9b9be) Message-ID: <20131204180558.5DDEA2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/7a9b9be12d3606128e47026e1aa1b7bce3b9d085/ghc >--------------------------------------------------------------- commit 7a9b9be12d3606128e47026e1aa1b7bce3b9d085 Author: Joachim Breitner Date: Wed Dec 4 16:11:28 2013 +0000 Put bothDmdResult back into bothDmdType >--------------------------------------------------------------- 7a9b9be12d3606128e47026e1aa1b7bce3b9d085 compiler/basicTypes/Demand.lhs | 10 +++------- compiler/stranal/DmdAnal.lhs | 4 ++-- 2 files changed, 5 insertions(+), 9 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index dbae6bd..b4597b2 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -18,7 +18,7 @@ module Demand ( isTopDmd, isBotDmd, isAbsDmd, isSeqDmd, peelUseCall, cleanUseDmd_maybe, strictenDmd, bothCleanDmd, - DmdType(..), dmdTypeDepth, lubDmdType, bothDmdEnv, bothDmdType, bothDmdTypeCase, + DmdType(..), dmdTypeDepth, lubDmdType, bothDmdEnv, bothDmdType, topDmdType, botDmdType, mkDmdType, mkTopDmdType, dmdTypeArgTop, addDemand, @@ -1087,17 +1087,13 @@ bothDmdType (DmdType fv1 ds1 r1) (DmdType fv2 _ r2) -- using its second arg just for its free-var info. -- NB: Don't forget about r2! It might be BotRes, which is -- a bottom demand on all the in-scope variables. - = DmdType both_fv2 ds1 r1 + = DmdType both_fv2 ds1 (r1 `bothDmdResult` r2) + where both_fv = plusVarEnv_C bothDmd fv1 fv2 both_fv1 = modifyEnv (isBotRes r1) (`bothDmd` botDmd) fv2 fv1 both_fv both_fv2 = modifyEnv (isBotRes r2) (`bothDmd` botDmd) fv1 fv2 both_fv1 -bothDmdTypeCase :: DmdType -> DmdType -> DmdType -bothDmdTypeCase d1@(DmdType _ _ r1) d2@(DmdType _ _ r2) - = DmdType fv' ds' (r1 `bothDmdResult` r2) - where (DmdType fv' ds' _) = bothDmdType d1 d2 - bothDmdEnv :: DmdEnv -> DmdEnv -> DmdEnv bothDmdEnv = plusVarEnv_C bothDmd diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index 2e33ca8..edb8fba 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -224,7 +224,7 @@ dmdAnal env dmd (Case scrut case_bndr ty [alt@(DataAlt dc, _, _)]) scrut_dmd = scrut_dmd1 `bothCleanDmd` scrut_dmd2 (scrut_ty, scrut') = dmdAnal env scrut_dmd scrut - res_ty = alt_ty1 `bothDmdTypeCase` scrut_ty + res_ty = alt_ty1 `bothDmdType` scrut_ty in -- pprTrace "dmdAnal:Case1" (vcat [ text "scrut" <+> ppr scrut -- , text "dmd" <+> ppr dmd @@ -240,7 +240,7 @@ dmdAnal env dmd (Case scrut case_bndr ty alts) (alt_tys, alts') = mapAndUnzip (dmdAnalAlt env dmd) alts (scrut_ty, scrut') = dmdAnal env cleanEvalDmd scrut (alt_ty, case_bndr') = annotateBndr env (foldr lubDmdType botDmdType alt_tys) case_bndr - res_ty = alt_ty `bothDmdTypeCase` scrut_ty + res_ty = alt_ty `bothDmdType` scrut_ty in -- pprTrace "dmdAnal:Case2" (vcat [ text "scrut" <+> ppr scrut -- , text "scrut_ty" <+> ppr scrut_ty From git at git.haskell.org Wed Dec 4 18:06:00 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 4 Dec 2013 18:06:00 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Use the un-postprocessed DmdResult to build nested CPR (ecfab42) Message-ID: <20131204180600.5CEC72406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/ecfab42ee7563ad0cdade10a470b31cc678056f3/ghc >--------------------------------------------------------------- commit ecfab42ee7563ad0cdade10a470b31cc678056f3 Author: Joachim Breitner Date: Wed Dec 4 16:29:35 2013 +0000 Use the un-postprocessed DmdResult to build nested CPR >--------------------------------------------------------------- ecfab42ee7563ad0cdade10a470b31cc678056f3 compiler/basicTypes/Demand.lhs | 18 +++++++++--------- compiler/stranal/DmdAnal.lhs | 32 ++++++++++++++++++-------------- 2 files changed, 27 insertions(+), 23 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index b4597b2..27ed312 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -26,7 +26,7 @@ module Demand ( peelFV, DmdResult(..), CPRResult(..), - isBotRes, isTopRes, resTypeArgDmd, + isBotRes, isTopRes, getDmdResult, resTypeArgDmd, topRes, botRes, cprConRes, vanillaCprConRes, appIsBottom, isBottomingSig, pprIfaceStrictSig, returnsCPR, returnsCPR_maybe, @@ -828,15 +828,15 @@ forgetCPR Diverges = Diverges forgetCPR (Converges _) = Converges NoCPR forgetCPR (Dunno _) = Dunno NoCPR -cprConRes :: ConTag -> [DmdType] -> CPRResult -cprConRes tag arg_tys +cprConRes :: ConTag -> [DmdResult] -> CPRResult +cprConRes tag arg_ress | opt_CprOff = NoCPR - | opt_NestedCprOff = cutCPRResult flatCPRDepth $ RetCon tag (map get_res arg_tys) - | otherwise = cutCPRResult maxCPRDepth $ RetCon tag (map get_res arg_tys) - where - get_res :: DmdType -> DmdResult - get_res (DmdType _ [] r) = r -- Only for data-typed arguments! - get_res _ = topRes + | opt_NestedCprOff = cutCPRResult flatCPRDepth $ RetCon tag arg_ress + | otherwise = cutCPRResult maxCPRDepth $ RetCon tag arg_ress + +getDmdResult :: DmdType -> DmdResult +getDmdResult (DmdType _ [] r) = r -- Only for data-typed arguments! +getDmdResult _ = topRes vanillaCprConRes :: ConTag -> Arity -> CPRResult vanillaCprConRes tag arity diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index edb8fba..fb45b46 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -100,24 +100,28 @@ c) The application rule wouldn't be right either \begin{code} dmdAnalArg :: AnalEnv -> Demand -- This one takes a *Demand* - -> CoreExpr -> (DmdType, CoreExpr) + -> CoreExpr + -> (DmdType, DmdResult, CoreExpr) -- Used for function arguments dmdAnalArg env dmd e | exprIsTrivial e = dmdAnalStar env dmd e | otherwise = dmdAnalStar env (oneifyDmd dmd) e + -- oneifyDmd: This is a thunk, so its content will be evaluated at most once -- Do not process absent demands -- Otherwise act like in a normal demand analysis -- See |-* relation in the companion paper dmdAnalStar :: AnalEnv -> Demand -- This one takes a *Demand* - -> CoreExpr -> (DmdType, CoreExpr) + -> CoreExpr + -> (DmdType, DmdResult, CoreExpr) dmdAnalStar env dmd e | (cd, defer_and_use) <- toCleanDmd dmd , (dmd_ty, e') <- dmdAnal env cd e = let dmd_ty' = postProcessDmdTypeM defer_and_use dmd_ty in -- pprTrace "dmdAnalStar" (vcat [ppr e, ppr dmd, ppr defer_and_use, ppr dmd_ty, ppr dmd_ty']) - (dmd_ty', e') + -- We also return the unmodified DmdResult, to store it in nested CPR information + (dmd_ty', getDmdResult dmd_ty, e') -- Main Demand Analsysis machinery dmdAnal :: AnalEnv @@ -508,7 +512,7 @@ completeApp env (fun_ty, fun') (arg:args) | otherwise = completeApp env (res_ty `bothDmdType` arg_ty, App fun' arg') args where (arg_dmd, res_ty) = splitDmdTy fun_ty - (arg_ty, arg') = dmdAnalArg env arg_dmd arg + (arg_ty, _, arg') = dmdAnalArg env arg_dmd arg ---------------- dmdAnalVarApp :: AnalEnv -> CleanDemand -> Id @@ -517,7 +521,7 @@ dmdAnalVarApp env dmd fun args | Just con <- isDataConWorkId_maybe fun -- Data constructor , isVanillaDataCon con , n_val_args == dataConRepArity con -- Saturated - , let cpr_info = Converges (cprConRes (dataConTag con) arg_tys) + , let cpr_info = Converges (cprConRes (dataConTag con) arg_rets) res_ty = foldl bothDmdType (DmdType emptyDmdEnv [] cpr_info) arg_tys = -- pprTrace "dmdAnalVarApp" (vcat [ ppr con, ppr args, ppr n_val_args, ppr cxt_ds -- , ppr arg_tys, ppr cpr_info, ppr res_ty]) $ @@ -535,21 +539,21 @@ dmdAnalVarApp env dmd fun args where n_val_args = valArgCount args cxt_ds = splitProdCleanDmd n_val_args dmd - (arg_tys, args') = anal_args cxt_ds args + (arg_tys, arg_rets, args') = anal_args cxt_ds args -- The constructor itself is lazy -- See Note [Data-con worker strictness] in MkId - anal_args :: [Demand] -> [CoreExpr] -> ([DmdType], [CoreExpr]) - anal_args _ [] = ([],[]) + anal_args :: [Demand] -> [CoreExpr] -> ([DmdType], [DmdResult], [CoreExpr]) + anal_args _ [] = ([],[],[]) anal_args ds (arg : args) | isTypeArg arg - , (arg_tys, args') <- anal_args ds args - = (arg_tys, arg:args') + , (arg_tys, arg_rets, args') <- anal_args ds args + = (arg_tys, arg_rets, arg:args') anal_args (d:ds) (arg : args) - | (arg_ty, arg') <- dmdAnalArg env d arg - , (arg_tys, args') <- anal_args ds args + | (arg_ty, arg_ret, arg') <- dmdAnalArg env d arg + , (arg_tys, arg_rets, args') <- anal_args ds args = --pprTrace "dmdAnalVarApp arg" (vcat [ ppr d, ppr arg, ppr arg_ty, ppr arg' ]) - (arg_ty:arg_tys, arg':args') + (arg_ty:arg_tys, arg_ret:arg_rets, arg':args') anal_args ds args = pprPanic "anal_args" (ppr args $$ ppr ds) \end{code} @@ -834,7 +838,7 @@ annotateLamIdBndr env arg_of_dfun dmd_ty one_shot id Nothing -> main_ty Just unf -> main_ty `bothDmdType` unf_ty where - (unf_ty, _) = dmdAnalStar env dmd unf + (unf_ty, _, _) = dmdAnalStar env dmd unf main_ty = addDemand dmd dmd_ty' (dmd_ty', dmd) = peelFV dmd_ty id From git at git.haskell.org Wed Dec 4 18:06:02 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 4 Dec 2013 18:06:02 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Only use bothDmdEnv, not bothDmdType, in dmdAnalVarApp for constructors (2b1ebab) Message-ID: <20131204180602.838BE2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/2b1ebabdfbc07d0bdba60e04bbd6cdcf210f7953/ghc >--------------------------------------------------------------- commit 2b1ebabdfbc07d0bdba60e04bbd6cdcf210f7953 Author: Joachim Breitner Date: Wed Dec 4 16:43:47 2013 +0000 Only use bothDmdEnv, not bothDmdType, in dmdAnalVarApp for constructors >--------------------------------------------------------------- 2b1ebabdfbc07d0bdba60e04bbd6cdcf210f7953 compiler/basicTypes/Demand.lhs | 5 ++++- compiler/stranal/DmdAnal.lhs | 17 +++++++++-------- 2 files changed, 13 insertions(+), 9 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 27ed312..95f6a8b 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -22,7 +22,7 @@ module Demand ( topDmdType, botDmdType, mkDmdType, mkTopDmdType, dmdTypeArgTop, addDemand, - DmdEnv, emptyDmdEnv, + DmdEnv, emptyDmdEnv, getDmdEnv, peelFV, DmdResult(..), CPRResult(..), @@ -1111,6 +1111,9 @@ instance Outputable DmdType where emptyDmdEnv :: VarEnv Demand emptyDmdEnv = emptyVarEnv +getDmdEnv :: DmdType -> DmdEnv +getDmdEnv (DmdType e _ _) = e -- Only for data-typed arguments! + topDmdType, botDmdType :: DmdType topDmdType = DmdType emptyDmdEnv [] topRes botDmdType = DmdType emptyDmdEnv [] botRes diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index fb45b46..b7ce27c 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -522,7 +522,8 @@ dmdAnalVarApp env dmd fun args , isVanillaDataCon con , n_val_args == dataConRepArity con -- Saturated , let cpr_info = Converges (cprConRes (dataConTag con) arg_rets) - res_ty = foldl bothDmdType (DmdType emptyDmdEnv [] cpr_info) arg_tys + fv_env = foldl bothDmdEnv emptyDmdEnv arg_envs + res_ty = DmdType fv_env [] cpr_info = -- pprTrace "dmdAnalVarApp" (vcat [ ppr con, ppr args, ppr n_val_args, ppr cxt_ds -- , ppr arg_tys, ppr cpr_info, ppr res_ty]) $ ( res_ty @@ -539,21 +540,21 @@ dmdAnalVarApp env dmd fun args where n_val_args = valArgCount args cxt_ds = splitProdCleanDmd n_val_args dmd - (arg_tys, arg_rets, args') = anal_args cxt_ds args + (arg_envs, arg_rets, args') = anal_args cxt_ds args -- The constructor itself is lazy -- See Note [Data-con worker strictness] in MkId - anal_args :: [Demand] -> [CoreExpr] -> ([DmdType], [DmdResult], [CoreExpr]) + anal_args :: [Demand] -> [CoreExpr] -> ([DmdEnv], [DmdResult], [CoreExpr]) anal_args _ [] = ([],[],[]) anal_args ds (arg : args) | isTypeArg arg - , (arg_tys, arg_rets, args') <- anal_args ds args - = (arg_tys, arg_rets, arg:args') + , (arg_envs, arg_rets, args') <- anal_args ds args + = (arg_envs, arg_rets, arg:args') anal_args (d:ds) (arg : args) | (arg_ty, arg_ret, arg') <- dmdAnalArg env d arg - , (arg_tys, arg_rets, args') <- anal_args ds args - = --pprTrace "dmdAnalVarApp arg" (vcat [ ppr d, ppr arg, ppr arg_ty, ppr arg' ]) - (arg_ty:arg_tys, arg_ret:arg_rets, arg':args') + , (arg_envs, arg_rets, args') <- anal_args ds args + = --pprTrace "dmdAnalVarApp arg" (vcat [ ppr d, ppr arg, ppr arg_env, ppr arg' ]) + (getDmdEnv arg_ty:arg_envs, arg_ret:arg_rets, arg':args') anal_args ds args = pprPanic "anal_args" (ppr args $$ ppr ds) \end{code} From git at git.haskell.org Wed Dec 4 18:06:04 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 4 Dec 2013 18:06:04 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Revert "Only use bothDmdEnv, not bothDmdType, in dmdAnalVarApp for constructors" (d037873) Message-ID: <20131204180604.98B1A2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/d0378738c069261d8bffdc48a6ad7ef25386b671/ghc >--------------------------------------------------------------- commit d0378738c069261d8bffdc48a6ad7ef25386b671 Author: Joachim Breitner Date: Wed Dec 4 16:47:47 2013 +0000 Revert "Only use bothDmdEnv, not bothDmdType, in dmdAnalVarApp for constructors" This reverts commit 2b1ebabdfbc07d0bdba60e04bbd6cdcf210f7953. >--------------------------------------------------------------- d0378738c069261d8bffdc48a6ad7ef25386b671 compiler/basicTypes/Demand.lhs | 5 +---- compiler/stranal/DmdAnal.lhs | 17 ++++++++--------- 2 files changed, 9 insertions(+), 13 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 95f6a8b..27ed312 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -22,7 +22,7 @@ module Demand ( topDmdType, botDmdType, mkDmdType, mkTopDmdType, dmdTypeArgTop, addDemand, - DmdEnv, emptyDmdEnv, getDmdEnv, + DmdEnv, emptyDmdEnv, peelFV, DmdResult(..), CPRResult(..), @@ -1111,9 +1111,6 @@ instance Outputable DmdType where emptyDmdEnv :: VarEnv Demand emptyDmdEnv = emptyVarEnv -getDmdEnv :: DmdType -> DmdEnv -getDmdEnv (DmdType e _ _) = e -- Only for data-typed arguments! - topDmdType, botDmdType :: DmdType topDmdType = DmdType emptyDmdEnv [] topRes botDmdType = DmdType emptyDmdEnv [] botRes diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index b7ce27c..fb45b46 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -522,8 +522,7 @@ dmdAnalVarApp env dmd fun args , isVanillaDataCon con , n_val_args == dataConRepArity con -- Saturated , let cpr_info = Converges (cprConRes (dataConTag con) arg_rets) - fv_env = foldl bothDmdEnv emptyDmdEnv arg_envs - res_ty = DmdType fv_env [] cpr_info + res_ty = foldl bothDmdType (DmdType emptyDmdEnv [] cpr_info) arg_tys = -- pprTrace "dmdAnalVarApp" (vcat [ ppr con, ppr args, ppr n_val_args, ppr cxt_ds -- , ppr arg_tys, ppr cpr_info, ppr res_ty]) $ ( res_ty @@ -540,21 +539,21 @@ dmdAnalVarApp env dmd fun args where n_val_args = valArgCount args cxt_ds = splitProdCleanDmd n_val_args dmd - (arg_envs, arg_rets, args') = anal_args cxt_ds args + (arg_tys, arg_rets, args') = anal_args cxt_ds args -- The constructor itself is lazy -- See Note [Data-con worker strictness] in MkId - anal_args :: [Demand] -> [CoreExpr] -> ([DmdEnv], [DmdResult], [CoreExpr]) + anal_args :: [Demand] -> [CoreExpr] -> ([DmdType], [DmdResult], [CoreExpr]) anal_args _ [] = ([],[],[]) anal_args ds (arg : args) | isTypeArg arg - , (arg_envs, arg_rets, args') <- anal_args ds args - = (arg_envs, arg_rets, arg:args') + , (arg_tys, arg_rets, args') <- anal_args ds args + = (arg_tys, arg_rets, arg:args') anal_args (d:ds) (arg : args) | (arg_ty, arg_ret, arg') <- dmdAnalArg env d arg - , (arg_envs, arg_rets, args') <- anal_args ds args - = --pprTrace "dmdAnalVarApp arg" (vcat [ ppr d, ppr arg, ppr arg_env, ppr arg' ]) - (getDmdEnv arg_ty:arg_envs, arg_ret:arg_rets, arg':args') + , (arg_tys, arg_rets, args') <- anal_args ds args + = --pprTrace "dmdAnalVarApp arg" (vcat [ ppr d, ppr arg, ppr arg_ty, ppr arg' ]) + (arg_ty:arg_tys, arg_ret:arg_rets, arg':args') anal_args ds args = pprPanic "anal_args" (ppr args $$ ppr ds) \end{code} From git at git.haskell.org Wed Dec 4 18:06:06 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 4 Dec 2013 18:06:06 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: In deferType, return convRes = Converges NoCPR (6bd9939) Message-ID: <20131204180606.B665C2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/6bd9939ba8e7d0efe0aba410e97496afd89d58dc/ghc >--------------------------------------------------------------- commit 6bd9939ba8e7d0efe0aba410e97496afd89d58dc Author: Joachim Breitner Date: Wed Dec 4 16:55:18 2013 +0000 In deferType, return convRes = Converges NoCPR because this is the right-identity to `bothDmdResult`, and this is the right thing to do in a lazy context. >--------------------------------------------------------------- 6bd9939ba8e7d0efe0aba410e97496afd89d58dc compiler/basicTypes/Demand.lhs | 12 +++++------- 1 file changed, 5 insertions(+), 7 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 27ed312..bb2e215 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -786,8 +786,9 @@ seqCPRResult (RetCon n rs) = n `seq` seqListWith seqDmdResult rs -- [cprRes] lets us switch off CPR analysis -- by making sure that everything uses TopRes -topRes, botRes :: DmdResult +topRes, convRes, botRes :: DmdResult topRes = Dunno NoCPR +convRes = Converges NoCPR botRes = Diverges maxCPRDepth :: Int @@ -1206,20 +1207,17 @@ postProcessDmdType (False, Many) ty = useType ty postProcessDmdType (True, One) ty = deferType ty postProcessDmdType (False, One) ty = ty +-- If we use something lazily, we want to ignore any possible divergence deferType, useType, deferAndUse :: DmdType -> DmdType -deferType (DmdType fv ds res_ty) = DmdType (deferEnv fv) (map deferDmd ds) (deferRes res_ty) +deferType (DmdType fv ds _) = DmdType (deferEnv fv) (map deferDmd ds) convRes useType (DmdType fv ds res_ty) = DmdType (useEnv fv) (map useDmd ds) res_ty -deferAndUse (DmdType fv ds res_ty) = DmdType (deferUseEnv fv) (map deferUseDmd ds) (deferRes res_ty) +deferAndUse (DmdType fv ds _) = DmdType (deferUseEnv fv) (map deferUseDmd ds) convRes deferEnv, useEnv, deferUseEnv :: DmdEnv -> DmdEnv deferEnv fv = mapVarEnv deferDmd fv useEnv fv = mapVarEnv useDmd fv deferUseEnv fv = mapVarEnv deferUseDmd fv -deferRes :: DmdResult -> DmdResult -deferRes Diverges = topRes -- Kill outer divergence -deferRes r = r -- Preserve CPR info - deferDmd, useDmd, deferUseDmd :: JointDmd -> JointDmd deferDmd (JD {strd=_, absd=a}) = mkJointDmd Lazy a useDmd (JD {strd=d, absd=a}) = mkJointDmd d (markAsUsedDmd a) From git at git.haskell.org Wed Dec 4 18:06:08 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 4 Dec 2013 18:06:08 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Add Note [non-algebraic or open body type warning] (b8faa4e) Message-ID: <20131204180608.D9B122406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/b8faa4ee51232e395e210e16a9c07b360247301a/ghc >--------------------------------------------------------------- commit b8faa4ee51232e395e210e16a9c07b360247301a Author: Joachim Breitner Date: Wed Dec 4 17:12:07 2013 +0000 Add Note [non-algebraic or open body type warning] >--------------------------------------------------------------- b8faa4ee51232e395e210e16a9c07b360247301a compiler/stranal/WwLib.lhs | 21 ++++++++++++++++++++- 1 file changed, 20 insertions(+), 1 deletion(-) diff --git a/compiler/stranal/WwLib.lhs b/compiler/stranal/WwLib.lhs index d7c0fd2..4ab2609 100644 --- a/compiler/stranal/WwLib.lhs +++ b/compiler/stranal/WwLib.lhs @@ -581,7 +581,7 @@ mkWWcpr_help inner ty res , \e body -> mkUnpackCase e co data_con arg_vars (nested_decon body) ) | otherwise - -> -- I would be happier if this were a error, but there are nasty corner cases. + -> -- See Note [non-algebraic or open body type warning] WARN ( True, ptext (sLit "mkWwcpr: non-algebraic or open body type") <+> (ppr ty) <+> ptext (sLit "but CPR type") <+> ppr (res) ) mkWWcpr_help inner ty topRes @@ -613,6 +613,25 @@ mkUnpackCase scrut co boxing_con unpk_args body casted_scrut = scrut `mkCast` co \end{code} +Note [non-algebraic or open body type warning] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + +There are a few cases where the W/W transformation is told that something +returns a constructor, but the type at hand doesn't really match this. One +real-world example involves unsafeCoerce: + foo = IO a + foo = unsafeCoere c_exit + foreign import ccall "c_exit" c_exit :: IO () +Here CPR will tell you that `foo` returns a () constructor for sure, but trying +to create a worker/wrapper for type `a` obviously fails. +(This was a real example until ee8e792 in libraries/base.) + +It does not seem feasilbe to avoid all such cases already in the analyser (and +after all, the analysis is not really wrong), so we simply do nothing here in +mkWWcpr. But we still want to emit warning with -DDEBUG, to hopefully catch +other cases where something went avoidably wrong. + + Note [Profiling and unpacking] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ If the original function looked like From git at git.haskell.org Wed Dec 4 18:06:10 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 4 Dec 2013 18:06:10 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Remove dmdAnalArg and replace by easier to understand code (09c78a1) Message-ID: <20131204180610.E9F3E2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/09c78a1746dc59be3939a7c738c09afbd2a6797e/ghc >--------------------------------------------------------------- commit 09c78a1746dc59be3939a7c738c09afbd2a6797e Author: Joachim Breitner Date: Wed Dec 4 17:38:25 2013 +0000 Remove dmdAnalArg and replace by easier to understand code >--------------------------------------------------------------- 09c78a1746dc59be3939a7c738c09afbd2a6797e compiler/stranal/DmdAnal.lhs | 19 ++++++++----------- 1 file changed, 8 insertions(+), 11 deletions(-) diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index fb45b46..dc346b3 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -98,15 +98,12 @@ c) The application rule wouldn't be right either evaluation of f in a C(L) demand! \begin{code} -dmdAnalArg :: AnalEnv - -> Demand -- This one takes a *Demand* - -> CoreExpr - -> (DmdType, DmdResult, CoreExpr) --- Used for function arguments -dmdAnalArg env dmd e - | exprIsTrivial e = dmdAnalStar env dmd e - | otherwise = dmdAnalStar env (oneifyDmd dmd) e - -- oneifyDmd: This is a thunk, so its content will be evaluated at most once +-- If e is complicated enough to become a thunk, its contents will be evaluated +-- at most once, so oneify it. +dmdTransformThunkDmd :: CoreExpr -> Demand -> Demand +dmdTransformThunkDmd e + | exprIsTrivial e = id + | otherwise = oneifyDmd -- Do not process absent demands -- Otherwise act like in a normal demand analysis @@ -512,7 +509,7 @@ completeApp env (fun_ty, fun') (arg:args) | otherwise = completeApp env (res_ty `bothDmdType` arg_ty, App fun' arg') args where (arg_dmd, res_ty) = splitDmdTy fun_ty - (arg_ty, _, arg') = dmdAnalArg env arg_dmd arg + (arg_ty, _, arg') = dmdAnalStar env (dmdTransformThunkDmd arg arg_dmd) arg ---------------- dmdAnalVarApp :: AnalEnv -> CleanDemand -> Id @@ -550,7 +547,7 @@ dmdAnalVarApp env dmd fun args , (arg_tys, arg_rets, args') <- anal_args ds args = (arg_tys, arg_rets, arg:args') anal_args (d:ds) (arg : args) - | (arg_ty, arg_ret, arg') <- dmdAnalArg env d arg + | (arg_ty, arg_ret, arg') <- dmdAnalStar env (dmdTransformThunkDmd arg d) arg , (arg_tys, arg_rets, args') <- anal_args ds args = --pprTrace "dmdAnalVarApp arg" (vcat [ ppr d, ppr arg, ppr arg_ty, ppr arg' ]) (arg_ty:arg_tys, arg_ret:arg_rets, arg':args') From git at git.haskell.org Wed Dec 4 18:06:13 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 4 Dec 2013 18:06:13 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Change the handling of Bottom demands on free variables (e765e10) Message-ID: <20131204180613.36ECA2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/e765e106c613a7fd9c0fd7ed569b9744c536c6d4/ghc >--------------------------------------------------------------- commit e765e106c613a7fd9c0fd7ed569b9744c536c6d4 Author: Joachim Breitner Date: Wed Dec 4 17:59:09 2013 +0000 Change the handling of Bottom demands on free variables and add a few Notes to explain it. >--------------------------------------------------------------- e765e106c613a7fd9c0fd7ed569b9744c536c6d4 compiler/basicTypes/Demand.lhs | 52 +++++++++++++++++++++++----------------- compiler/stranal/DmdAnal.lhs | 10 -------- 2 files changed, 30 insertions(+), 32 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index bb2e215..34adac2 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -998,8 +998,7 @@ in GHC itself where the tuple was DynFlags \begin{code} type Demand = JointDmd -type DmdEnv = VarEnv Demand -- If a variable v is not in the domain of the - -- DmdEnv, it implicitly maps to +type DmdEnv = VarEnv Demand -- See Note [Default demand on free variables] data DmdType = DmdType DmdEnv -- Demand on explicitly-mentioned @@ -1045,8 +1044,14 @@ Similarly with we get dt_scrut from the scrutinee and dt_rhs from the RHS, and then compute (dt_rhs `bothType` dt_scrut). -We take the CPR info from FIRST argument, but combine both to get -termination info. +We + 1. combine the information on the free variables, + 2. take the demand on arguments from the first argument + 3. combine the termination results, but + 4 take CPR info from the first argument. + +3 and 4 are implementd in bothDmdResult. + \begin{code} @@ -1076,24 +1081,15 @@ lubDmdType (DmdType fv1 ds1 r1) (DmdType fv2 ds2 r2) lub_ds ds1 [] = map (`lubDmd` resTypeArgDmd r2) ds1 lub_ds [] ds2 = map (resTypeArgDmd r1 `lubDmd`) ds2 --- TODO: This is used for both --- * f `bothDmdType` e (in which case divergence of e does not prevent CPR of f e), and --- * e `bothDmdType` scrut (in which case divergence of scurt prevence convergence of case scrut of _ -> e) --- HACK for now: Use bothDmdTypeCase for case --- Need to take strict demand into account? bothDmdType :: DmdType -> DmdType -> DmdType bothDmdType (DmdType fv1 ds1 r1) (DmdType fv2 _ r2) -- See Note [Asymmetry of 'both' for DmdType and DmdResult] -- 'both' takes the argument/result info from its *first* arg, -- using its second arg just for its free-var info. - -- NB: Don't forget about r2! It might be BotRes, which is - -- a bottom demand on all the in-scope variables. - = DmdType both_fv2 ds1 (r1 `bothDmdResult` r2) - - where - both_fv = plusVarEnv_C bothDmd fv1 fv2 - both_fv1 = modifyEnv (isBotRes r1) (`bothDmd` botDmd) fv2 fv1 both_fv - both_fv2 = modifyEnv (isBotRes r2) (`bothDmd` botDmd) fv1 fv2 both_fv1 + -- Also See Note [Default demand on free variables] + = DmdType (fv1 `bothDmdEnv` fv2) + ds1 + (r1 `bothDmdResult` r2) bothDmdEnv :: DmdEnv -> DmdEnv -> DmdEnv bothDmdEnv = plusVarEnv_C bothDmd @@ -1257,18 +1253,30 @@ peelManyCalls arg_ds (CD { sd = str, ud = abs }) peelFV :: DmdType -> Var -> (DmdType, Demand) peelFV (DmdType fv ds res) id = -- pprTrace "rfv" (ppr id <+> ppr dmd $$ ppr fv) - (DmdType fv' ds res, dmd) + (DmdType fv' ds res, dmd') where fv' = fv `delVarEnv` id - dmd = lookupVarEnv fv id `orElse` deflt - -- See note [Default demand for variables] - deflt | isBotRes res = botDmd - | otherwise = absDmd + -- See note [Default demand on free variables] + dmd = lookupVarEnv fv id `orElse` absDmd + dmd' | isBotRes res = dmd `bothDmd` botDmd + | otherwise = dmd addDemand :: Demand -> DmdType -> DmdType addDemand dmd (DmdType fv ds res) = DmdType fv (dmd:ds) res \end{code} +Note [Default demand on free variables] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +If the variable is not mentioned in the environment of a demand type, +its demand is taken to be a result demand of the type: either L or the +bottom. Both are safe from the semantical pont of view, however, for +the safe result we also have absent demand set to Abs, which makes it +possible to safely ignore non-mentioned variables (their joint demand +is ). absDmd is the identity of bothDmd. + +If the result is bottom, we we still have to `bothDmd` the `botDmd` to the +value in the environment; as we do _not_ do that in bothDmdType. + Note [Always analyse in virgin pass] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Tricky point: make sure that we analyse in the 'virgin' pass. Consider diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index dc346b3..a43e963 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -769,16 +769,6 @@ addLazyFVs dmd_ty lazy_fvs -- call to f. So we just get an L demand for x for g. \end{code} -Note [Default demand for variables] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ - -If the variable is not mentioned in the environment of a demand type, -its demand is taken to be a result demand of the type: either L or the -bottom. Both are safe from the semantical pont of view, however, for -the safe result we also have absent demand set to Abs, which makes it -possible to safely ignore non-mentioned variables (their joint demand -is ). - Note [do not strictify the argument dictionaries of a dfun] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ From git at git.haskell.org Wed Dec 4 18:06:15 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 4 Dec 2013 18:06:15 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Merge branch 'wip/nested-cpr' of git://git.haskell.org/ghc into wip/nested-cpr (e71635f) Message-ID: <20131204180615.5761C2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/e71635f0a533ecffb48dfd36a771dede678a55aa/ghc >--------------------------------------------------------------- commit e71635f0a533ecffb48dfd36a771dede678a55aa Merge: e765e10 052d78b Author: Joachim Breitner Date: Wed Dec 4 18:03:47 2013 +0000 Merge branch 'wip/nested-cpr' of git://git.haskell.org/ghc into wip/nested-cpr Conflicts: compiler/stranal/DmdAnal.lhs >--------------------------------------------------------------- e71635f0a533ecffb48dfd36a771dede678a55aa compiler/basicTypes/Demand.lhs | 8 ++++---- compiler/stranal/DmdAnal.lhs | 33 +++++++++++++++------------------ 2 files changed, 19 insertions(+), 22 deletions(-) diff --cc compiler/stranal/DmdAnal.lhs index a43e963,a029fff..342a760 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@@ -522,36 -521,39 +522,33 @@@ dmdAnalVarApp env dmd fun arg res_ty = foldl bothDmdType (DmdType emptyDmdEnv [] cpr_info) arg_tys = -- pprTrace "dmdAnalVarApp" (vcat [ ppr con, ppr args, ppr n_val_args, ppr cxt_ds -- , ppr arg_tys, ppr cpr_info, ppr res_ty]) $ - ( res_ty + ( res_ty , foldl App (Var fun) args') - - | otherwise - = --pprTrace "dmdAnalVarApp" (vcat [ ppr fun, ppr args, ppr n_val_args - -- , ppr dmd - -- , ppr (mkCallDmdN n_val_args dmd) - -- , ppr $ dmdTransform env fun (mkCallDmdN n_val_args dmd) - -- , ppr $ completeApp env (dmdTransform env fun (mkCallDmdN n_val_args dmd), Var fun) args - -- ]) - completeApp env (dmdTransform env fun (mkCallDmdN n_val_args dmd), Var fun) args where n_val_args = valArgCount args - cxt_ds = splitProdCleanDmd n_val_args dmd - (arg_tys, args') = anal_con_args cxt_ds args + cxt_ds = splitProdCleanDmd n_val_args dmd - (arg_tys, arg_rets, args') = anal_args cxt_ds args - -- The constructor itself is lazy ++ (arg_tys, arg_rets, args') = anal_con_args cxt_ds args + -- The constructor itself is lazy, so we don't need to look at the + -- strictness signature on the data constructor. Instead just + -- propagate demand from the context into the constructor arguments -- See Note [Data-con worker strictness] in MkId - - anal_con_args :: [Demand] -> [CoreExpr] -> ([DmdType], [CoreExpr]) - anal_con_args _ [] = ([],[]) + - anal_args :: [Demand] -> [CoreExpr] -> ([DmdType], [DmdResult], [CoreExpr]) - anal_args _ [] = ([],[],[]) - anal_args ds (arg : args) ++ anal_con_args :: [Demand] -> [CoreExpr] -> ([DmdType], [DmdResult], [CoreExpr]) ++ anal_con_args _ [] = ([],[],[]) + anal_con_args ds (arg : args) - | isTypeArg arg - , (arg_tys, args') <- anal_con_args ds args - = (arg_tys, arg:args') + | isTypeArg arg - , (arg_tys, arg_rets, args') <- anal_args ds args ++ , (arg_tys, arg_rets, args') <- anal_con_args ds args + = (arg_tys, arg_rets, arg:args') - anal_args (d:ds) (arg : args) + anal_con_args (d:ds) (arg : args) - | (arg_ty, arg') <- dmdAnalArg env d arg - , (arg_tys, args') <- anal_con_args ds args + | (arg_ty, arg_ret, arg') <- dmdAnalStar env (dmdTransformThunkDmd arg d) arg - , (arg_tys, arg_rets, args') <- anal_args ds args ++ , (arg_tys, arg_rets, args') <- anal_con_args ds args = --pprTrace "dmdAnalVarApp arg" (vcat [ ppr d, ppr arg, ppr arg_ty, ppr arg' ]) - (arg_ty:arg_tys, arg':args') + (arg_ty:arg_tys, arg_ret:arg_rets, arg':args') - anal_args ds args = pprPanic "anal_args" (ppr args $$ ppr ds) + anal_con_args ds args = pprPanic "anal_con_args" (ppr args $$ ppr ds) + - -dmdAnalVarApp env dmd fun args - | otherwise -- Not a saturated constructor - = --pprTrace "dmdAnalVarApp" (vcat [ ppr fun, ppr args, ppr n_val_args - -- , ppr dmd - -- , ppr $ dmdTransform env fun (mkCallDmdN n_val_args dmd) - -- , ppr $ completeApp env (dmdTransform env fun (mkCallDmdN n_val_args dmd), Var fun) args - -- ]) ++dmdAnalVarApp env dmd fun args -- Not a saturated constructor ++ = --pprTrace "dmdAnalVarApp" (vcat [ ppr fun, ppr args, ppr dmd ]) + completeApp env (dmdTransform env fun (mkCallDmdN (valArgCount args) dmd), Var fun) args \end{code} %************************************************************************ From git at git.haskell.org Wed Dec 4 18:39:19 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 4 Dec 2013 18:39:19 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Avoid CPR w/w for something that already returns an unboxed tuple (0be8638) Message-ID: <20131204183919.27BD72406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/0be8638df719f4a6a7a3c2dd99601d65f9503438/ghc >--------------------------------------------------------------- commit 0be8638df719f4a6a7a3c2dd99601d65f9503438 Author: Joachim Breitner Date: Wed Dec 4 18:39:16 2013 +0000 Avoid CPR w/w for something that already returns an unboxed tuple >--------------------------------------------------------------- 0be8638df719f4a6a7a3c2dd99601d65f9503438 compiler/basicTypes/Demand.lhs | 1 - compiler/stranal/WwLib.lhs | 14 ++++++++++++++ 2 files changed, 14 insertions(+), 1 deletion(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 0a7138c..82a7109 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -779,7 +779,6 @@ seqCPRResult :: CPRResult -> () seqCPRResult NoCPR = () seqCPRResult (RetCon n rs) = n `seq` seqListWith seqDmdResult rs - ------------------------------------------------------------------------ -- Combined demand result -- ------------------------------------------------------------------------ diff --git a/compiler/stranal/WwLib.lhs b/compiler/stranal/WwLib.lhs index 4ab2609..e20472f 100644 --- a/compiler/stranal/WwLib.lhs +++ b/compiler/stranal/WwLib.lhs @@ -542,6 +542,7 @@ mkWWcpr body_ty res , \ body -> decon body (Var arg_var) , idType arg_var ) + _ | isWWUseless body_ty res -> return (id, id, body_ty) _ -> do wrap_wild_uniq <- getUniqueM @@ -593,6 +594,19 @@ mkWWcpr_help inner ty res , \e body -> mkRename e var body ) +-- If something is known to return (# t1, t2 #), this is a CPR property. But it would +-- be useless to then add a wrapper that unwraps that unboxed tuple and recreates it. +-- So try to detect that situation here. +isWWUseless :: Type -> DmdResult -> Bool +isWWUseless ty res + | Just (con_tag, rs) <- returnsCPR_maybe False res + , all isTopRes rs + , Just (data_con, _, _, _) <- deepSplitCprType_maybe con_tag ty + , isUnboxedTupleCon data_con + = True + | otherwise + = False + -- mkRename e v body -- binds v to e in body. This will later be removed by the simplifiers mkRename :: CoreExpr -> Var -> CoreExpr -> CoreExpr From git at git.haskell.org Wed Dec 4 18:49:30 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 4 Dec 2013 18:49:30 +0000 (UTC) Subject: [commit: ghc] master: Move the allocation of CAF blackholes into 'newCAF' (#8590) (55c703b) Message-ID: <20131204184931.276472406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/55c703b8fdb040c51bf8784beb3dc02332db417a/ghc >--------------------------------------------------------------- commit 55c703b8fdb040c51bf8784beb3dc02332db417a Author: Patrick Palka Date: Sun Dec 1 21:17:43 2013 -0500 Move the allocation of CAF blackholes into 'newCAF' (#8590) We now do the allocation of the blackhole indirection closure inside the RTS procedure 'newCAF' instead of generating the allocation code inline in the closure body of each CAF. This slightly decreases code size in modules with a lot of CAFs. As a result of this change, for example, the size of DynFlags.o drops by ~60KB and HsExpr.o by ~100KB. >--------------------------------------------------------------- 55c703b8fdb040c51bf8784beb3dc02332db417a compiler/codeGen/StgCmmBind.hs | 40 ++++++++++------------------------------ includes/rts/storage/GC.h | 4 ++-- rts/sm/Storage.c | 40 +++++++++++++++++++++++++++------------- 3 files changed, 39 insertions(+), 45 deletions(-) diff --git a/compiler/codeGen/StgCmmBind.hs b/compiler/codeGen/StgCmmBind.hs index 64772c6..05aae0a 100644 --- a/compiler/codeGen/StgCmmBind.hs +++ b/compiler/codeGen/StgCmmBind.hs @@ -21,7 +21,7 @@ import StgCmmEnv import StgCmmCon import StgCmmHeap import StgCmmProf (curCCS, ldvEnterClosure, enterCostCentreFun, enterCostCentreThunk, - initUpdFrameProf, costCentreFrom) + initUpdFrameProf) import StgCmmTicky import StgCmmLayout import StgCmmUtils @@ -718,13 +718,6 @@ emitUpdateFrame dflags frame lbl updatee = do -- (which Hugs needs to do in order that combined mode works right.) -- --- ToDo [Feb 04] This entire link_caf nonsense could all be moved --- into the "newCAF" RTS procedure, which we call anyway, including --- the allocation of the black-hole indirection closure. --- That way, code size would fall, the CAF-handling code would --- be closer together, and the compiler wouldn't need to know --- about off_indirectee etc. - link_caf :: LocalReg -- pointer to the closure -> Bool -- True <=> updatable, False <=> single-entry -> FCode CmmExpr -- Returns amode for closure to be updated @@ -736,40 +729,27 @@ link_caf :: LocalReg -- pointer to the closure -- so that generational GC is easier. link_caf node _is_upd = do { dflags <- getDynFlags - -- Alloc black hole specifying CC_HDR(Node) as the cost centre - ; let use_cc = costCentreFrom dflags (CmmReg nodeReg) - blame_cc = use_cc - tso = CmmReg (CmmGlobal CurrentTSO) - - ; hp_rel <- allocDynClosureCmm Nothing cafBlackHoleInfoTable mkLFBlackHole - use_cc blame_cc [(tso,fixedHdrSize dflags)] - -- small optimisation: we duplicate the hp_rel expression in - -- both the newCAF call and the value returned below. - -- If we instead used allocDynClosureReg which assigns it to a reg, - -- then the reg is live across the newCAF call and gets spilled, - -- which is stupid. Really we should have an optimisation pass to - -- fix this, but we don't yet. --SDM - -- Call the RTS function newCAF to add the CAF to the CafList -- so that the garbage collector can find them -- This must be done *before* the info table pointer is overwritten, -- because the old info table ptr is needed for reversion - ; ret <- newTemp (bWord dflags) - ; emitRtsCallGen [(ret,NoHint)] (mkForeignLabel (fsLit "newCAF") Nothing ForeignLabelInExternalPackage IsFunction) + ; let newCAF_lbl = mkForeignLabel (fsLit "newCAF") Nothing + ForeignLabelInExternalPackage IsFunction + ; bh <- newTemp (bWord dflags) + ; emitRtsCallGen [(bh,AddrHint)] newCAF_lbl [ (CmmReg (CmmGlobal BaseReg), AddrHint), - (CmmReg (CmmLocal node), AddrHint), - (hp_rel, AddrHint) ] + (CmmReg (CmmLocal node), AddrHint) ] False -- see Note [atomic CAF entry] in rts/sm/Storage.c ; updfr <- getUpdFrameOff + ; let target = entryCode dflags (closureInfoPtr dflags (CmmReg (CmmLocal node))) ; emit =<< mkCmmIfThen - (CmmMachOp (mo_wordEq dflags) [ CmmReg (CmmLocal ret), CmmLit (zeroCLit dflags)]) + (cmmEqWord dflags (CmmReg (CmmLocal bh)) (zeroExpr dflags)) -- re-enter the CAF - (let target = entryCode dflags (closureInfoPtr dflags (CmmReg (CmmLocal node))) in - mkJump dflags NativeNodeCall target [] updfr) + (mkJump dflags NativeNodeCall target [] updfr) - ; return hp_rel } + ; return (CmmReg (CmmLocal bh)) } ------------------------------------------------------------------------ -- Profiling diff --git a/includes/rts/storage/GC.h b/includes/rts/storage/GC.h index f8b8afe..63a9594 100644 --- a/includes/rts/storage/GC.h +++ b/includes/rts/storage/GC.h @@ -181,8 +181,8 @@ void performMajorGC(void); The CAF table - used to let us revert CAFs in GHCi -------------------------------------------------------------------------- */ -StgWord newCAF (StgRegTable *reg, StgIndStatic *caf, StgClosure *bh); -StgWord newDynCAF (StgRegTable *reg, StgIndStatic *caf, StgClosure *bh); +StgInd *newCAF (StgRegTable *reg, StgIndStatic *caf); +StgInd *newDynCAF (StgRegTable *reg, StgIndStatic *caf); void revertCAFs (void); // Request that all CAFs are retained indefinitely. diff --git a/rts/sm/Storage.c b/rts/sm/Storage.c index b5f3202..755b3d9 100644 --- a/rts/sm/Storage.c +++ b/rts/sm/Storage.c @@ -333,9 +333,12 @@ freeStorage (rtsBool free_heap) -------------------------------------------------------------------------- */ -STATIC_INLINE StgWord lockCAF (StgIndStatic *caf, StgClosure *bh) +STATIC_INLINE StgInd * +lockCAF (StgRegTable *reg, StgIndStatic *caf) { const StgInfoTable *orig_info; + Capability *cap = regTableToCapability(reg); + StgInd *bh; orig_info = caf->header.info; @@ -345,7 +348,7 @@ STATIC_INLINE StgWord lockCAF (StgIndStatic *caf, StgClosure *bh) if (orig_info == &stg_IND_STATIC_info || orig_info == &stg_WHITEHOLE_info) { // already claimed by another thread; re-enter the CAF - return 0; + return NULL; } cur_info = (const StgInfoTable *) @@ -355,7 +358,7 @@ STATIC_INLINE StgWord lockCAF (StgIndStatic *caf, StgClosure *bh) if (cur_info != orig_info) { // already claimed by another thread; re-enter the CAF - return 0; + return NULL; } // successfully claimed by us; overwrite with IND_STATIC @@ -364,17 +367,25 @@ STATIC_INLINE StgWord lockCAF (StgIndStatic *caf, StgClosure *bh) // For the benefit of revertCAFs(), save the original info pointer caf->saved_info = orig_info; - caf->indirectee = bh; + // Allocate the blackhole indirection closure + bh = (StgInd *)allocate(cap, sizeofW(*bh)); + SET_HDR(bh, &stg_CAF_BLACKHOLE_info, caf->header.prof.ccs); + bh->indirectee = (StgClosure *)cap->r.rCurrentTSO; + + caf->indirectee = (StgClosure *)bh; write_barrier(); SET_INFO((StgClosure*)caf,&stg_IND_STATIC_info); - return 1; + return bh; } -StgWord -newCAF(StgRegTable *reg, StgIndStatic *caf, StgClosure *bh) +StgInd * +newCAF(StgRegTable *reg, StgIndStatic *caf) { - if (lockCAF(caf,bh) == 0) return 0; + StgInd *bh; + + bh = lockCAF(reg, caf); + if (!bh) return NULL; if(keepCAFs) { @@ -418,7 +429,7 @@ newCAF(StgRegTable *reg, StgIndStatic *caf, StgClosure *bh) #endif } - return 1; + return bh; } // External API for setting the keepCAFs flag. see #3900. @@ -437,10 +448,13 @@ setKeepCAFs (void) // // The linker hackily arranges that references to newCaf from dynamic // code end up pointing to newDynCAF. -StgWord -newDynCAF (StgRegTable *reg STG_UNUSED, StgIndStatic *caf, StgClosure *bh) +StgInd * +newDynCAF (StgRegTable *reg, StgIndStatic *caf) { - if (lockCAF(caf,bh) == 0) return 0; + StgInd *bh; + + bh = lockCAF(reg, caf); + if (!bh) return NULL; ACQUIRE_SM_LOCK; @@ -449,7 +463,7 @@ newDynCAF (StgRegTable *reg STG_UNUSED, StgIndStatic *caf, StgClosure *bh) RELEASE_SM_LOCK; - return 1; + return bh; } /* ----------------------------------------------------------------------------- From git at git.haskell.org Wed Dec 4 18:49:32 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 4 Dec 2013 18:49:32 +0000 (UTC) Subject: [commit: ghc] master: Update and deduplicate the comments on CAF management (#8590) (fe68ad5) Message-ID: <20131204184932.9144C2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/fe68ad50f3fa7d73df691f9fd9decd17a72b8b46/ghc >--------------------------------------------------------------- commit fe68ad50f3fa7d73df691f9fd9decd17a72b8b46 Author: Patrick Palka Date: Wed Dec 4 10:38:47 2013 -0500 Update and deduplicate the comments on CAF management (#8590) >--------------------------------------------------------------- fe68ad50f3fa7d73df691f9fd9decd17a72b8b46 compiler/codeGen/StgCmmBind.hs | 35 ++++------------------------------- rts/sm/Storage.c | 14 +++++++++----- 2 files changed, 13 insertions(+), 36 deletions(-) diff --git a/compiler/codeGen/StgCmmBind.hs b/compiler/codeGen/StgCmmBind.hs index 05aae0a..2336792 100644 --- a/compiler/codeGen/StgCmmBind.hs +++ b/compiler/codeGen/StgCmmBind.hs @@ -695,44 +695,17 @@ emitUpdateFrame dflags frame lbl updatee = do ----------------------------------------------------------------------------- -- Entering a CAF -- --- When a CAF is first entered, it creates a black hole in the heap, --- and updates itself with an indirection to this new black hole. --- --- We update the CAF with an indirection to a newly-allocated black --- hole in the heap. We also set the blocking queue on the newly --- allocated black hole to be empty. --- --- Why do we make a black hole in the heap when we enter a CAF? --- --- - for a generational garbage collector, which needs a fast --- test for whether an updatee is in an old generation or not --- --- - for the parallel system, which can implement updates more --- easily if the updatee is always in the heap. (allegedly). --- --- When debugging, we maintain a separate CAF list so we can tell when --- a CAF has been garbage collected. - --- newCAF must be called before the itbl ptr is overwritten, since --- newCAF records the old itbl ptr in order to do CAF reverting --- (which Hugs needs to do in order that combined mode works right.) --- +-- See Note [CAF management] in rts/sm/Storage.c link_caf :: LocalReg -- pointer to the closure -> Bool -- True <=> updatable, False <=> single-entry -> FCode CmmExpr -- Returns amode for closure to be updated --- To update a CAF we must allocate a black hole, link the CAF onto the --- CAF list, then update the CAF to point to the fresh black hole. -- This function returns the address of the black hole, so it can be --- updated with the new value when available. The reason for all of this --- is that we only want to update dynamic heap objects, not static ones, --- so that generational GC is easier. +-- updated with the new value when available. link_caf node _is_upd = do { dflags <- getDynFlags - -- Call the RTS function newCAF to add the CAF to the CafList - -- so that the garbage collector can find them - -- This must be done *before* the info table pointer is overwritten, - -- because the old info table ptr is needed for reversion + -- Call the RTS function newCAF, returning the newly-allocated + -- blackhole indirection closure ; let newCAF_lbl = mkForeignLabel (fsLit "newCAF") Nothing ForeignLabelInExternalPackage IsFunction ; bh <- newTemp (bWord dflags) diff --git a/rts/sm/Storage.c b/rts/sm/Storage.c index 755b3d9..0f28820 100644 --- a/rts/sm/Storage.c +++ b/rts/sm/Storage.c @@ -268,14 +268,12 @@ freeStorage (rtsBool free_heap) } /* ----------------------------------------------------------------------------- - CAF management. + Note [CAF management]. The entry code for every CAF does the following: - - builds a CAF_BLACKHOLE in the heap - - - calls newCaf, which atomically updates the CAF with - IND_STATIC pointing to the CAF_BLACKHOLE + - calls newCaf, which builds a CAF_BLACKHOLE on the heap and atomically + updates the CAF with IND_STATIC pointing to the CAF_BLACKHOLE - if newCaf returns zero, it re-enters the CAF (see Note [atomic CAF entry]) @@ -290,6 +288,10 @@ freeStorage (rtsBool free_heap) newCaf() does the following: + - atomically locks the CAF (see [atomic CAF entry]) + + - it builds a CAF_BLACKHOLE on the heap + - it updates the CAF with an IND_STATIC pointing to the CAF_BLACKHOLE, atomically. @@ -297,6 +299,8 @@ freeStorage (rtsBool free_heap) This is so that we treat the CAF as a root when collecting younger generations. + - links the CAF onto the CAF list (see below) + ------------------ Note [atomic CAF entry] From git at git.haskell.org Thu Dec 5 00:16:59 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 5 Dec 2013 00:16:59 +0000 (UTC) Subject: [commit: ghc] master: Use new flushExec implementation on all operating systems (#8562) (95854ca) Message-ID: <20131205001659.818862406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/95854ca5276e3f4063ade7fe3a934bed46648270/ghc >--------------------------------------------------------------- commit 95854ca5276e3f4063ade7fe3a934bed46648270 Author: Christopher Rodrigues Date: Fri Nov 29 23:05:50 2013 -0600 Use new flushExec implementation on all operating systems (#8562) An earlier patch fixes a bug in flushExec on linux only. This patch uses the fixed code on all operating systems. Signed-off-by: Austin Seipp >--------------------------------------------------------------- 95854ca5276e3f4063ade7fe3a934bed46648270 rts/sm/Storage.c | 56 ++++++++++++++++++------------------------------------ 1 file changed, 19 insertions(+), 37 deletions(-) diff --git a/rts/sm/Storage.c b/rts/sm/Storage.c index 0f28820..c7126fe 100644 --- a/rts/sm/Storage.c +++ b/rts/sm/Storage.c @@ -1152,24 +1152,6 @@ calcNeeded (rtsBool force_major, memcount *blocks_needed) should be modified to use allocateExec instead of VirtualAlloc. ------------------------------------------------------------------------- */ -#if defined(linux_HOST_OS) - -// On Linux we need to use libffi for allocating executable memory, -// because it knows how to work around the restrictions put in place -// by SELinux. - -AdjustorWritable allocateExec (W_ bytes, AdjustorExecutable *exec_ret) -{ - void **ret, **exec; - ACQUIRE_SM_LOCK; - ret = ffi_closure_alloc (sizeof(void *) + (size_t)bytes, (void**)&exec); - RELEASE_SM_LOCK; - if (ret == NULL) return ret; - *ret = ret; // save the address of the writable mapping, for freeExec(). - *exec_ret = exec + 1; - return (ret + 1); -} - #if defined(arm_HOST_ARCH) && defined(ios_HOST_OS) void sys_icache_invalidate(void *start, size_t len); #endif @@ -1195,6 +1177,24 @@ void flushExec (W_ len, AdjustorExecutable exec_addr) #endif } +#if defined(linux_HOST_OS) + +// On Linux we need to use libffi for allocating executable memory, +// because it knows how to work around the restrictions put in place +// by SELinux. + +AdjustorWritable allocateExec (W_ bytes, AdjustorExecutable *exec_ret) +{ + void **ret, **exec; + ACQUIRE_SM_LOCK; + ret = ffi_closure_alloc (sizeof(void *) + (size_t)bytes, (void**)&exec); + RELEASE_SM_LOCK; + if (ret == NULL) return ret; + *ret = ret; // save the address of the writable mapping, for freeExec(). + *exec_ret = exec + 1; + return (ret + 1); +} + // freeExec gets passed the executable address, not the writable address. void freeExec (AdjustorExecutable addr) { @@ -1241,15 +1241,6 @@ AdjustorWritable execToWritable(AdjustorExecutable exec) return writ; } -void flushExec (W_ len, AdjustorExecutable exec_addr) -{ - /* On ARM and other platforms, we need to flush the cache after - writing code into memory, so the processor reliably sees it. */ - unsigned char* begin = (unsigned char*)exec_addr; - unsigned char* end = begin + len; - __builtin___clear_cache(begin, end); -} - void freeExec(AdjustorExecutable exec) { AdjustorWritable writ; @@ -1303,15 +1294,6 @@ AdjustorWritable allocateExec (W_ bytes, AdjustorExecutable *exec_ret) return ret; } -void flushExec (W_ len, AdjustorExecutable exec_addr) -{ - /* On ARM and other platforms, we need to flush the cache after - writing code into memory, so the processor reliably sees it. */ - unsigned char* begin = (unsigned char*)exec_addr; - unsigned char* end = begin + len; - __builtin___clear_cache(begin, end); -} - void freeExec (void *addr) { StgPtr p = (StgPtr)addr - 1; @@ -1346,7 +1328,7 @@ void freeExec (void *addr) RELEASE_SM_LOCK } -#endif /* mingw32_HOST_OS */ +#endif /* switch(HOST_OS) */ #ifdef DEBUG From git at git.haskell.org Thu Dec 5 04:00:11 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 5 Dec 2013 04:00:11 +0000 (UTC) Subject: [commit: ghc] master: Made ghc -e have a nonzero exit code upon failure (Trac #7962 ) (47024b6) Message-ID: <20131205040011.E77732406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/47024b63835e2bc238f88e3e1a5b5927a850e74c/ghc >--------------------------------------------------------------- commit 47024b63835e2bc238f88e3e1a5b5927a850e74c Author: khyperia Date: Wed Nov 27 23:30:59 2013 -0500 Made ghc -e have a nonzero exit code upon failure (Trac #7962 ) Signed-off-by: Austin Seipp >--------------------------------------------------------------- 47024b63835e2bc238f88e3e1a5b5927a850e74c ghc/InteractiveUI.hs | 14 ++++++++++---- 1 file changed, 10 insertions(+), 4 deletions(-) diff --git a/ghc/InteractiveUI.hs b/ghc/InteractiveUI.hs index 5413a1a..024aa2d 100644 --- a/ghc/InteractiveUI.hs +++ b/ghc/InteractiveUI.hs @@ -524,7 +524,8 @@ runGHCi paths maybe_exprs = do $ topHandler e -- this used to be topHandlerFastExit, see #2228 runInputTWithPrefs defaultPrefs defaultSettings $ do - runCommands' hdle (return Nothing) + -- make `ghc -e` exit nonzero on invalid input, see Trac #7962 + runCommands' hdle (Just $ hdle (toException $ ExitFailure 1) >> return ()) (return Nothing) -- and finally, exit liftIO $ when (verbosity dflags > 0) $ putStrLn "Leaving GHCi." @@ -675,11 +676,12 @@ installInteractivePrint (Just ipFun) exprmode = do -- | The main read-eval-print loop runCommands :: InputT GHCi (Maybe String) -> InputT GHCi () -runCommands = runCommands' handler +runCommands = runCommands' handler Nothing runCommands' :: (SomeException -> GHCi Bool) -- ^ Exception handler + -> Maybe (GHCi ()) -- ^ Source error handler -> InputT GHCi (Maybe String) -> InputT GHCi () -runCommands' eh gCmd = do +runCommands' eh sourceErrorHandler gCmd = do b <- ghandle (\e -> case fromException e of Just UserInterrupt -> return $ Just False _ -> case fromException e of @@ -691,7 +693,11 @@ runCommands' eh gCmd = do (runOneCommand eh gCmd) case b of Nothing -> return () - Just _ -> runCommands' eh gCmd + Just success -> do + let nextCommand = runCommands' eh sourceErrorHandler gCmd + case sourceErrorHandler of + Just handler | success == False -> lift handler >> nextCommand + _ -> nextCommand -- | Evaluate a single line of user input (either : or Haskell code) runOneCommand :: (SomeException -> GHCi Bool) -> InputT GHCi (Maybe String) From git at git.haskell.org Thu Dec 5 04:00:13 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 5 Dec 2013 04:00:13 +0000 (UTC) Subject: [commit: ghc] master: Refactored by Simon Marlow's suggestion (415f0d6) Message-ID: <20131205040013.EA5572406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/415f0d6cb716b68318dad1af4e9ab6ec13844136/ghc >--------------------------------------------------------------- commit 415f0d6cb716b68318dad1af4e9ab6ec13844136 Author: Evan Hauck Date: Thu Nov 28 11:58:50 2013 -0500 Refactored by Simon Marlow's suggestion Signed-off-by: Austin Seipp >--------------------------------------------------------------- 415f0d6cb716b68318dad1af4e9ab6ec13844136 ghc/InteractiveUI.hs | 6 ++---- 1 file changed, 2 insertions(+), 4 deletions(-) diff --git a/ghc/InteractiveUI.hs b/ghc/InteractiveUI.hs index 024aa2d..be97bc0 100644 --- a/ghc/InteractiveUI.hs +++ b/ghc/InteractiveUI.hs @@ -694,10 +694,8 @@ runCommands' eh sourceErrorHandler gCmd = do case b of Nothing -> return () Just success -> do - let nextCommand = runCommands' eh sourceErrorHandler gCmd - case sourceErrorHandler of - Just handler | success == False -> lift handler >> nextCommand - _ -> nextCommand + when (not success) $ maybe (return ()) lift sourceErrorHandler + runCommands' eh sourceErrorHandler gCmd -- | Evaluate a single line of user input (either : or Haskell code) runOneCommand :: (SomeException -> GHCi Bool) -> InputT GHCi (Maybe String) From git at git.haskell.org Thu Dec 5 04:00:16 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 5 Dec 2013 04:00:16 +0000 (UTC) Subject: [commit: ghc] master: Fix compiler warnings due to integer size mismatch (d9ad369) Message-ID: <20131205040016.14AAC2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d9ad369d89be9b0c541eb9a311caf89392c64379/ghc >--------------------------------------------------------------- commit d9ad369d89be9b0c541eb9a311caf89392c64379 Author: Christopher Rodrigues Date: Sat Nov 30 13:06:43 2013 -0600 Fix compiler warnings due to integer size mismatch Signed-off-by: Austin Seipp >--------------------------------------------------------------- d9ad369d89be9b0c541eb9a311caf89392c64379 rts/Stats.c | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/rts/Stats.c b/rts/Stats.c index 7db4563..48c320c 100644 --- a/rts/Stats.c +++ b/rts/Stats.c @@ -691,8 +691,8 @@ stat_exit (void) statsPrintf("%16s bytes maximum slop\n", temp); statsPrintf("%16" FMT_SizeT " MB total memory in use (%" FMT_SizeT " MB lost due to fragmentation)\n\n", - (W_)(peak_mblocks_allocated * MBLOCK_SIZE_W / (1024 * 1024 / sizeof(W_))), - (W_)(peak_mblocks_allocated * BLOCKS_PER_MBLOCK * BLOCK_SIZE_W - hw_alloc_blocks * BLOCK_SIZE_W) / (1024 * 1024 / sizeof(W_))); + (size_t)(peak_mblocks_allocated * MBLOCK_SIZE_W) / (1024 * 1024 / sizeof(W_)), + (size_t)(peak_mblocks_allocated * BLOCKS_PER_MBLOCK * BLOCK_SIZE_W - hw_alloc_blocks * BLOCK_SIZE_W) / (1024 * 1024 / sizeof(W_))); /* Print garbage collections in each gen */ statsPrintf(" Tot time (elapsed) Avg pause Max pause\n"); From git at git.haskell.org Thu Dec 5 04:34:56 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 5 Dec 2013 04:34:56 +0000 (UTC) Subject: [commit: testsuite] master: Add new ghc-e/should_fail test suite (69f6072) Message-ID: <20131205043456.ACED92406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/testsuite On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/69f60722eabcce8283a4270b8d3aff712c8d462a/testsuite >--------------------------------------------------------------- commit 69f60722eabcce8283a4270b8d3aff712c8d462a Author: Austin Seipp Date: Wed Dec 4 22:33:19 2013 -0600 Add new ghc-e/should_fail test suite Also add a basic test for #7962. Signed-off-by: Austin Seipp >--------------------------------------------------------------- 69f60722eabcce8283a4270b8d3aff712c8d462a tests/{cabal/pkg02 => ghc-e/should_fail}/Makefile | 2 ++ tests/ghc-e/should_fail/all.T | 3 +++ 2 files changed, 5 insertions(+) diff --git a/tests/cabal/pkg02/Makefile b/tests/ghc-e/should_fail/Makefile similarity index 51% copy from tests/cabal/pkg02/Makefile copy to tests/ghc-e/should_fail/Makefile index 4a26853..5b0d753 100644 --- a/tests/cabal/pkg02/Makefile +++ b/tests/ghc-e/should_fail/Makefile @@ -2,3 +2,5 @@ TOP=../../.. include $(TOP)/mk/boilerplate.mk include $(TOP)/mk/test.mk +T7962: + '$(TEST_HC)' $(TEST_HC_OPTS) -ignore-dot-ghci -e "return (" diff --git a/tests/ghc-e/should_fail/all.T b/tests/ghc-e/should_fail/all.T new file mode 100644 index 0000000..4c5ac5c --- /dev/null +++ b/tests/ghc-e/should_fail/all.T @@ -0,0 +1,3 @@ +setTestOpts(when(compiler_profiled(), skip)) + +test('T7962', [exit_code(2), req_interp, ignore_output], run_command, ['$MAKE --no-print-directory -s T7962']) From git at git.haskell.org Thu Dec 5 08:31:06 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 5 Dec 2013 08:31:06 +0000 (UTC) Subject: [commit: testsuite] master: Different quotes in error messages following lexer clean-up (0d939eb) Message-ID: <20131205083107.015792406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/testsuite On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0d939eb56d8ea05899270537469e6cf00dffd82c/testsuite >--------------------------------------------------------------- commit 0d939eb56d8ea05899270537469e6cf00dffd82c Author: Simon Peyton Jones Date: Thu Dec 5 08:30:53 2013 +0000 Different quotes in error messages following lexer clean-up >--------------------------------------------------------------- 0d939eb56d8ea05899270537469e6cf00dffd82c tests/annotations/should_fail/annfail13.stderr | 2 +- tests/ghci/prog009/ghci.prog009.stderr | 4 ++-- tests/ghci/scripts/T1914.stderr | 4 +++- tests/ghci/scripts/T6106.stderr | 4 +++- tests/haddock/should_fail_flag_haddock/haddockE004.stderr | 2 +- tests/layout/layout001.stdout | 2 +- tests/layout/layout003.stdout | 2 +- tests/layout/layout004.stdout | 4 ++-- tests/layout/layout006.stdout | 2 +- tests/mdo/should_fail/mdofail005.stderr | 2 +- tests/module/mod76.stderr | 2 +- tests/parser/should_fail/ExportCommaComma.stderr | 2 +- tests/parser/should_fail/ParserNoLambdaCase.stderr | 2 +- tests/parser/should_fail/position001.stderr | 2 +- tests/parser/should_fail/position002.stderr | 2 +- tests/parser/should_fail/readFail006.stderr | 2 +- tests/parser/should_fail/readFail011.stderr | 2 +- tests/parser/should_fail/readFail013.stderr | 2 +- tests/parser/should_fail/readFail014.stderr | 2 +- tests/parser/should_fail/readFail019.stderr | 2 +- tests/parser/should_fail/readFail020.stderr | 2 +- tests/parser/should_fail/readFail024.stderr | 2 +- tests/parser/should_fail/readFail026.stderr | 2 +- tests/parser/should_fail/readFail034.stderr | 2 +- tests/parser/should_fail/readFail040.stderr | 2 +- tests/rename/should_fail/T4042.stderr | 4 +++- tests/safeHaskell/ghci/p14.stderr | 2 +- 27 files changed, 35 insertions(+), 29 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 0d939eb56d8ea05899270537469e6cf00dffd82c From git at git.haskell.org Thu Dec 5 08:31:24 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 5 Dec 2013 08:31:24 +0000 (UTC) Subject: [commit: ghc] master: Suggest TemplateHaskell after encountering a naked top-level expression (0f2a20b) Message-ID: <20131205083124.9646D2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0f2a20bc882a918d39219b045a8db1ac7d9354fc/ghc >--------------------------------------------------------------- commit 0f2a20bc882a918d39219b045a8db1ac7d9354fc Author: Patrick Palka Date: Fri Nov 15 13:57:26 2013 -0500 Suggest TemplateHaskell after encountering a naked top-level expression Helps fix #7396 >--------------------------------------------------------------- 0f2a20bc882a918d39219b045a8db1ac7d9354fc compiler/rename/RnSource.lhs | 1 + 1 file changed, 1 insertion(+) diff --git a/compiler/rename/RnSource.lhs b/compiler/rename/RnSource.lhs index 90175c0..624c3b6 100644 --- a/compiler/rename/RnSource.lhs +++ b/compiler/rename/RnSource.lhs @@ -1475,6 +1475,7 @@ add gp loc (SpliceD splice@(SpliceDecl _ flag)) ds ; return (gp, Just (splice, ds)) } where badImplicitSplice = ptext (sLit "Parse error: naked expression at top level") + $$ ptext (sLit "Perhaps you intended to use TemplateHaskell") add gp _ (QuasiQuoteD qq) ds -- Expand quasiquotes = do { ds' <- runQuasiQuoteDecl qq From git at git.haskell.org Thu Dec 5 08:31:26 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 5 Dec 2013 08:31:26 +0000 (UTC) Subject: [commit: ghc] master: Typecheck typed TH splices properly (fix Trac #8577) (8b642de) Message-ID: <20131205083126.AEA912406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8b642debfabe00377f47d461d31d70636bf0fce3/ghc >--------------------------------------------------------------- commit 8b642debfabe00377f47d461d31d70636bf0fce3 Author: Simon Peyton Jones Date: Wed Dec 4 18:04:08 2013 +0000 Typecheck typed TH splices properly (fix Trac #8577) This was an egregious error. If e :: T (Q ty1) then when we have the splice $e :: ty2 we must ensure that ty1~ty2 before we even think about running the splice! I took the opportunity to remove the dead-code tcSpliceDecls altogether. >--------------------------------------------------------------- 8b642debfabe00377f47d461d31d70636bf0fce3 compiler/hsSyn/HsExpr.lhs | 3 +++ compiler/typecheck/TcExpr.lhs | 5 ++++- compiler/typecheck/TcSplice.lhs | 41 ++++++++++++---------------------- compiler/typecheck/TcSplice.lhs-boot | 4 +--- 4 files changed, 22 insertions(+), 31 deletions(-) diff --git a/compiler/hsSyn/HsExpr.lhs b/compiler/hsSyn/HsExpr.lhs index 61c41da..bb91790 100644 --- a/compiler/hsSyn/HsExpr.lhs +++ b/compiler/hsSyn/HsExpr.lhs @@ -1382,6 +1382,9 @@ instance OutputableBndr id => Outputable (HsSplice id) where pprUntypedSplice :: OutputableBndr id => HsSplice id -> SDoc pprUntypedSplice = pprSplice False +pprTypedSplice :: OutputableBndr id => HsSplice id -> SDoc +pprTypedSplice = pprSplice True + pprSplice :: OutputableBndr id => Bool -> HsSplice id -> SDoc pprSplice is_typed (HsSplice n e) = (if is_typed then ptext (sLit "$$") else char '$') diff --git a/compiler/typecheck/TcExpr.lhs b/compiler/typecheck/TcExpr.lhs index ccd1196..a26c269 100644 --- a/compiler/typecheck/TcExpr.lhs +++ b/compiler/typecheck/TcExpr.lhs @@ -797,7 +797,10 @@ tcExpr (PArrSeq _ _) _ %************************************************************************ \begin{code} -tcExpr (HsSpliceE is_ty splice) res_ty = tcSpliceExpr is_ty splice res_ty +tcExpr (HsSpliceE is_ty splice) res_ty + = ASSERT( is_ty ) -- Untyped splices are expanced by the renamer + tcSpliceExpr splice res_ty + tcExpr (HsBracket brack) res_ty = tcTypedBracket brack res_ty tcExpr (HsRnBracketOut brack ps) res_ty = tcUntypedBracket brack ps res_ty \end{code} diff --git a/compiler/typecheck/TcSplice.lhs b/compiler/typecheck/TcSplice.lhs index 2277871..100ed34 100644 --- a/compiler/typecheck/TcSplice.lhs +++ b/compiler/typecheck/TcSplice.lhs @@ -12,7 +12,7 @@ TcSplice: Template Haskell splices module TcSplice( -- These functions are defined in stage1 and stage2 -- The raise civilised errors in stage1 - tcSpliceExpr, tcSpliceDecls, tcTypedBracket, tcUntypedBracket, + tcSpliceExpr, tcTypedBracket, tcUntypedBracket, runQuasiQuoteExpr, runQuasiQuotePat, runQuasiQuoteDecl, runQuasiQuoteType, runAnnotation, @@ -116,8 +116,7 @@ import GHC.Exts ( unsafeCoerce# ) \begin{code} tcTypedBracket :: HsBracket Name -> TcRhoType -> TcM (HsExpr TcId) tcUntypedBracket :: HsBracket Name -> [PendingRnSplice] -> TcRhoType -> TcM (HsExpr TcId) -tcSpliceDecls :: HsSplice Name -> TcM [LHsDecl RdrName] -tcSpliceExpr :: Bool -> HsSplice Name -> TcRhoType -> TcM (HsExpr TcId) +tcSpliceExpr :: HsSplice Name -> TcRhoType -> TcM (HsExpr TcId) -- None of these functions add constraints to the LIE runQuasiQuoteExpr :: HsQuasiQuote RdrName -> RnM (LHsExpr RdrName) @@ -130,8 +129,7 @@ runAnnotation :: CoreAnnTarget -> LHsExpr Name -> TcM Annotation #ifndef GHCI tcTypedBracket x _ = failTH x "Template Haskell bracket" tcUntypedBracket x _ _ = failTH x "Template Haskell bracket" -tcSpliceExpr _ e _ = failTH e "Template Haskell splice" -tcSpliceDecls x = failTH x "Template Haskell declaration splice" +tcSpliceExpr e _ = failTH e "Template Haskell splice" runQuasiQuoteExpr q = failTH q "quasiquote" runQuasiQuotePat q = failTH q "pattern quasiquote" @@ -417,9 +415,8 @@ tcTExpTy tau = do %************************************************************************ \begin{code} -tcSpliceExpr is_typed splice@(HsSplice name expr) res_ty - = ASSERT2( is_typed, ppr splice ) - addErrCtxt (spliceCtxtDoc splice) $ +tcSpliceExpr splice@(HsSplice name expr) res_ty + = addErrCtxt (spliceCtxtDoc splice) $ setSrcSpan (getLoc expr) $ do { stage <- getStage ; case stage of @@ -449,20 +446,21 @@ tcNestedSplice _ _ splice_name _ _ tcTopSplice :: LHsExpr Name -> TcRhoType -> TcM (HsExpr Id) tcTopSplice expr res_ty - = do { any_ty <- newFlexiTyVarTy openTypeKind - ; meta_exp_ty <- tcTExpTy any_ty - - -- Typecheck the expression + = do { -- Typecheck the expression, + -- making sure it has type Q (T res_ty) + meta_exp_ty <- tcTExpTy res_ty ; zonked_q_expr <- tcTopSpliceExpr True $ tcMonoExpr expr meta_exp_ty - -- Run the expression + -- Run the expression ; expr2 <- runMetaE zonked_q_expr ; showSplice "expression" expr (ppr expr2) + -- Rename and typecheck the spliced-in expression, + -- making sure it has type res_ty + -- These steps should never fail; this is a *typed* splice ; addErrCtxt (spliceResultDoc expr) $ do - { (exp3, _fvs) <- checkNoErrs $ rnLExpr expr2 - -- checkNoErrs: see Note [Renamer errors] + { (exp3, _fvs) <- rnLExpr expr2 ; exp4 <- tcMonoExpr exp3 res_ty ; return (unLoc exp4) } } \end{code} @@ -470,17 +468,6 @@ tcTopSplice expr res_ty %************************************************************************ %* * -\subsection{Splicing a pattern} -%* * -%************************************************************************ - -\begin{code} -tcSpliceDecls splice - = pprPanic "tcSpliceDecls: encountered a typed type splice" (ppr splice) -\end{code} - -%************************************************************************ -%* * \subsection{Error messages} %* * %************************************************************************ @@ -494,7 +481,7 @@ quotationCtxtDoc br_body spliceCtxtDoc :: HsSplice Name -> SDoc spliceCtxtDoc splice = hang (ptext (sLit "In the Template Haskell splice")) - 2 (ppr splice) + 2 (pprTypedSplice splice) spliceResultDoc :: LHsExpr Name -> SDoc spliceResultDoc expr diff --git a/compiler/typecheck/TcSplice.lhs-boot b/compiler/typecheck/TcSplice.lhs-boot index b96cf18..c496aed 100644 --- a/compiler/typecheck/TcSplice.lhs-boot +++ b/compiler/typecheck/TcSplice.lhs-boot @@ -14,12 +14,10 @@ import Annotations ( Annotation, CoreAnnTarget ) import qualified Language.Haskell.TH as TH #endif -tcSpliceExpr :: Bool -> HsSplice Name +tcSpliceExpr :: HsSplice Name -> TcRhoType -> TcM (HsExpr TcId) -tcSpliceDecls :: HsSplice Name -> TcM [LHsDecl RdrName] - tcUntypedBracket :: HsBracket Name -> [PendingRnSplice] -> TcRhoType From git at git.haskell.org Thu Dec 5 08:31:28 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 5 Dec 2013 08:31:28 +0000 (UTC) Subject: [commit: ghc] master: Comments, and rename a variable (9d6f111) Message-ID: <20131205083128.D29E52406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9d6f11157404656fba9fc59d168b0eee1448a6f5/ghc >--------------------------------------------------------------- commit 9d6f11157404656fba9fc59d168b0eee1448a6f5 Author: Simon Peyton Jones Date: Wed Dec 4 17:57:59 2013 +0000 Comments, and rename a variable >--------------------------------------------------------------- 9d6f11157404656fba9fc59d168b0eee1448a6f5 compiler/typecheck/TcTyClsDecls.lhs | 38 ++++++++++++++++++++++++++--------- 1 file changed, 28 insertions(+), 10 deletions(-) diff --git a/compiler/typecheck/TcTyClsDecls.lhs b/compiler/typecheck/TcTyClsDecls.lhs index 62dd8ed..47d970d 100644 --- a/compiler/typecheck/TcTyClsDecls.lhs +++ b/compiler/typecheck/TcTyClsDecls.lhs @@ -1482,26 +1482,44 @@ checkValidDataCon dflags existential_ok tc con = setSrcSpan (srcLocSpan (getSrcLoc con)) $ addErrCtxt (dataConCtxt con) $ do { traceTc "checkValidDataCon" (ppr con $$ ppr tc) + + -- Check that the return type of the data constructor + -- matches the type constructor; eg reject this: + -- data T a where { MkT :: Bogus a } + -- c.f. Note [Check role annotations in a second pass] + -- and Note [Checking GADT return types] ; let tc_tvs = tyConTyVars tc res_ty_tmpl = mkFamilyTyConApp tc (mkTyVarTys tc_tvs) - actual_res_ty = dataConOrigResTy con + orig_res_ty = dataConOrigResTy con ; checkTc (isJust (tcMatchTy (mkVarSet tc_tvs) - res_ty_tmpl - actual_res_ty)) - (badDataConTyCon con res_ty_tmpl actual_res_ty) - -- IA0_TODO: we should also check that kind variables - -- are only instantiated with kind variables - ; checkValidMonoType (dataConOrigResTy con) - -- Disallow MkT :: T (forall a. a->a) - -- Reason: it's really the argument of an equality constraint + res_ty_tmpl + orig_res_ty)) + (badDataConTyCon con res_ty_tmpl orig_res_ty) + + -- Check that the result type is a *monotype* + -- e.g. reject this: MkT :: T (forall a. a->a) + -- Reason: it's really the argument of an equality constraint + ; checkValidMonoType orig_res_ty + + -- Check all argument types for validity ; checkValidType ctxt (dataConUserType con) + + -- Extra checks for newtype data constructors ; when (isNewTyCon tc) (checkNewDataCon con) + -- Check that UNPACK pragmas and bangs work out + -- E.g. reject data T = MkT {-# UNPACK #-} Int -- No "!" + -- data T = MkT {-# UNPACK #-} !a -- Can't unpack ; mapM_ check_bang (zip3 (dataConStrictMarks con) (dataConRepBangs con) [1..]) + -- Check that existentials are allowed if they are used ; checkTc (existential_ok || isVanillaDataCon con) (badExistential con) + -- Check that we aren't doing GADT type refinement on kind variables + -- e.g reject data T (a::k) where + -- T1 :: T Int + -- T2 :: T Maybe ; checkTc (not (any (isKindVar . fst) (dataConEqSpec con))) (badGadtKindCon con) @@ -1527,7 +1545,7 @@ checkValidDataCon dflags existential_ok tc con <+> ptext (sLit "argument of") <+> quotes (ppr con)) ------------------------------- checkNewDataCon :: DataCon -> TcM () --- Checks for the data constructor of a newtype +-- Further checks for the data constructor of a newtype checkNewDataCon con = do { checkTc (isSingleton arg_tys) (newtypeFieldErr con (length arg_tys)) -- One argument From git at git.haskell.org Thu Dec 5 08:31:30 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 5 Dec 2013 08:31:30 +0000 (UTC) Subject: [commit: ghc] master: Suggest TemplateHaskell after encountering a parse error on '$' (#7396) (1860dae) Message-ID: <20131205083130.EACF32406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1860dae3a7e377f085f3a4134f532a7f577fccbe/ghc >--------------------------------------------------------------- commit 1860dae3a7e377f085f3a4134f532a7f577fccbe Author: Patrick Palka Date: Fri Nov 29 19:12:33 2013 -0500 Suggest TemplateHaskell after encountering a parse error on '$' (#7396) >--------------------------------------------------------------- 1860dae3a7e377f085f3a4134f532a7f577fccbe compiler/parser/Lexer.x | 16 ++++++++++------ 1 file changed, 10 insertions(+), 6 deletions(-) diff --git a/compiler/parser/Lexer.x b/compiler/parser/Lexer.x index 490ca5f..8eeab6b 100644 --- a/compiler/parser/Lexer.x +++ b/compiler/parser/Lexer.x @@ -2058,11 +2058,11 @@ setContext :: [LayoutContext] -> P () setContext ctx = P $ \s -> POk s{context=ctx} () popContext :: P () -popContext = P $ \ s@(PState{ buffer = buf, context = ctx, +popContext = P $ \ s@(PState{ buffer = buf, dflags = flags, context = ctx, last_len = len, last_loc = last_loc }) -> case ctx of (_:tl) -> POk s{ context = tl } () - [] -> PFailed (RealSrcSpan last_loc) (srcParseErr buf len) + [] -> PFailed (RealSrcSpan last_loc) (srcParseErr flags buf len) -- Push a new layout context at the indentation of the last token read. -- This is only used at the outer level of a module when the 'module' @@ -2084,22 +2084,26 @@ getOffside = P $ \s at PState{last_loc=loc, context=stk} -> -- Construct a parse error srcParseErr - :: StringBuffer -- current buffer (placed just after the last token) + :: DynFlags + -> StringBuffer -- current buffer (placed just after the last token) -> Int -- length of the previous token -> MsgDoc -srcParseErr buf len +srcParseErr dflags buf len = if null token then ptext (sLit "parse error (possibly incorrect indentation or mismatched brackets)") else ptext (sLit "parse error on input") <+> quotes (text token) + $$ ppWhen (not th_enabled && token == "$") -- #7396 + (text "Perhaps you intended to use TemplateHaskell") where token = lexemeToString (offsetBytes (-len) buf) len + th_enabled = xopt Opt_TemplateHaskell dflags -- Report a parse failure, giving the span of the previous token as -- the location of the error. This is the entry point for errors -- detected during parsing. srcParseFail :: P a -srcParseFail = P $ \PState{ buffer = buf, last_len = len, +srcParseFail = P $ \PState{ buffer = buf, dflags = flags, last_len = len, last_loc = last_loc } -> - PFailed (RealSrcSpan last_loc) (srcParseErr buf len) + PFailed (RealSrcSpan last_loc) (srcParseErr flags buf len) -- A lexical error is reported at a particular position in the source file, -- not over a token range. From git at git.haskell.org Thu Dec 5 08:31:32 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 5 Dec 2013 08:31:32 +0000 (UTC) Subject: [commit: ghc] master: Clean up Lexer.srcParseErr (1c69305) Message-ID: <20131205083133.2773E2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1c69305e47bd01d9be42716a3d308681bfb1b0b4/ghc >--------------------------------------------------------------- commit 1c69305e47bd01d9be42716a3d308681bfb1b0b4 Author: Patrick Palka Date: Fri Nov 29 19:06:29 2013 -0500 Clean up Lexer.srcParseErr The lexer now uses unicode single quotation marks in its error messages if possible. This is due to the use of the 'quotes' combinator. >--------------------------------------------------------------- 1c69305e47bd01d9be42716a3d308681bfb1b0b4 compiler/parser/Lexer.x | 8 +++----- 1 file changed, 3 insertions(+), 5 deletions(-) diff --git a/compiler/parser/Lexer.x b/compiler/parser/Lexer.x index 49f6dcd..490ca5f 100644 --- a/compiler/parser/Lexer.x +++ b/compiler/parser/Lexer.x @@ -2088,11 +2088,9 @@ srcParseErr -> Int -- length of the previous token -> MsgDoc srcParseErr buf len - = hcat [ if null token - then ptext (sLit "parse error (possibly incorrect indentation or mismatched brackets)") - else hcat [ptext (sLit "parse error on input "), - char '`', text token, char '\''] - ] + = if null token + then ptext (sLit "parse error (possibly incorrect indentation or mismatched brackets)") + else ptext (sLit "parse error on input") <+> quotes (text token) where token = lexemeToString (offsetBytes (-len) buf) len -- Report a parse failure, giving the span of the previous token as From git at git.haskell.org Thu Dec 5 08:34:33 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 5 Dec 2013 08:34:33 +0000 (UTC) Subject: [commit: testsuite] master: Test Trac #8577 (3e66489) Message-ID: <20131205083433.8A9CD2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/testsuite On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3e66489ebcef0f4cd86968c6781a1d4ad1981f94/testsuite >--------------------------------------------------------------- commit 3e66489ebcef0f4cd86968c6781a1d4ad1981f94 Author: Simon Peyton Jones Date: Thu Dec 5 08:34:22 2013 +0000 Test Trac #8577 >--------------------------------------------------------------- 3e66489ebcef0f4cd86968c6781a1d4ad1981f94 tests/th/T8577.hs | 10 ++++++++++ tests/th/T8577.stderr | 7 +++++++ tests/th/T8577a.hs | 11 +++++++++++ tests/th/all.T | 4 ++++ 4 files changed, 32 insertions(+) diff --git a/tests/th/T8577.hs b/tests/th/T8577.hs new file mode 100644 index 0000000..8a467e4 --- /dev/null +++ b/tests/th/T8577.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE TemplateHaskell #-} +module T8577 where + +import Language.Haskell.TH + +import T8577a + +foo2 :: A Bool +foo2 = $$(y) + diff --git a/tests/th/T8577.stderr b/tests/th/T8577.stderr new file mode 100644 index 0000000..6e35e4a --- /dev/null +++ b/tests/th/T8577.stderr @@ -0,0 +1,7 @@ + +T8577.hs:9:11: + Couldn't match type ?Int? with ?Bool? + Expected type: Q (TExp (A Bool)) + Actual type: Q (TExp (A Int)) + In the expression: y + In the Template Haskell splice $$y diff --git a/tests/th/T8577a.hs b/tests/th/T8577a.hs new file mode 100644 index 0000000..807350c --- /dev/null +++ b/tests/th/T8577a.hs @@ -0,0 +1,11 @@ +{-# LANGUAGE TemplateHaskell #-} +module T8577a where +import Language.Haskell.TH + +data A a = A + +x :: Q (TExp (A a)) +x = [|| A ||] + +y :: Q (TExp (A Int)) +y = x diff --git a/tests/th/all.T b/tests/th/all.T index a1fd6bf..05d5d90 100644 --- a/tests/th/all.T +++ b/tests/th/all.T @@ -311,3 +311,7 @@ test('T8540', extra_clean(['T8540a.hi', 'T8540a.o']), multimod_compile, ['T8540', '-v0 ' + config.ghc_th_way_flags]) +test('T8577', + extra_clean(['T8577a.hi', 'T8577a.o']), + multimod_compile_fail, + ['T8577', '-v0 ' + config.ghc_th_way_flags]) From git at git.haskell.org Thu Dec 5 10:01:54 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 5 Dec 2013 10:01:54 +0000 (UTC) Subject: [commit: ghc] branch 'wip/T8545' created Message-ID: <20131205100154.1F98B2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/T8545 Referencing: e45b9f57a9044e8a20e3cc13bcff86b12b3da405 From git at git.haskell.org Thu Dec 5 10:01:58 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 5 Dec 2013 10:01:58 +0000 (UTC) Subject: [commit: ghc] wip/T8545: Fold in testsuite.git into ghc.git (re #8545) (e45b9f5) Message-ID: <20131205100158.CFFCD2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8545 Link : http://ghc.haskell.org/trac/ghc/changeset/e45b9f57a9044e8a20e3cc13bcff86b12b3da405/ghc >--------------------------------------------------------------- commit e45b9f57a9044e8a20e3cc13bcff86b12b3da405 Author: Herbert Valerio Riedel Date: Thu Dec 5 10:54:41 2013 +0100 Fold in testsuite.git into ghc.git (re #8545) This uses the tree from [3e66489ebcef0f4cd86968c6781a1d4ad1981f94/testsuite] and inserts it into ghc.git as `testsuite/` folder. Moreover, `sync-all` and some docs are updated to reflect this change in Git repository structure. Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- e45b9f57a9044e8a20e3cc13bcff86b12b3da405 .gitignore | 1 - HACKING.md | 2 - packages | 7 +- sync-all | 8 +- testsuite/.gitignore | 1386 ++ testsuite/LICENSE | 44 + testsuite/LICENSE.GPL | 674 + testsuite/Makefile | 36 + testsuite/README.md | 43 + testsuite/config/bad.ps | 1 + testsuite/config/ghc | 226 + testsuite/config/good.ps | 1 + testsuite/driver/runtests.py | 304 + testsuite/driver/testglobals.py | 274 + testsuite/driver/testlib.py | 2224 +++ testsuite/driver/testutil.py | 51 + testsuite/mk/boilerplate.mk | 193 + testsuite/mk/ghc-config.hs | 84 + testsuite/mk/test.mk | 261 + testsuite/tests/Makefile | 19 + testsuite/tests/annotations/Makefile | 3 + .../tests/annotations/should_compile/Makefile | 3 + testsuite/tests/annotations/should_compile/all.T | 25 + .../tests/annotations/should_compile/ann01.hs | 38 + .../annotations/should_fail/Annfail04_Help.hs | 4 + .../annotations/should_fail/Annfail05_Help.hs | 3 + .../annotations/should_fail/Annfail06_Help.hs | 3 + testsuite/tests/annotations/should_fail/Makefile | 3 + testsuite/tests/annotations/should_fail/all.T | 34 + .../tests/annotations/should_fail/annfail01.hs | 5 + .../tests/annotations/should_fail/annfail01.stderr | 8 + .../tests/annotations/should_fail/annfail02.hs | 7 + .../tests/annotations/should_fail/annfail02.stderr | 8 + .../tests/annotations/should_fail/annfail03.hs | 18 + .../tests/annotations/should_fail/annfail03.stderr | 6 + .../tests/annotations/should_fail/annfail04.hs | 15 + .../tests/annotations/should_fail/annfail04.stderr | 7 + .../tests/annotations/should_fail/annfail05.hs | 12 + .../tests/annotations/should_fail/annfail05.stderr | 5 + .../tests/annotations/should_fail/annfail06.hs | 23 + .../tests/annotations/should_fail/annfail06.stderr | 7 + .../tests/annotations/should_fail/annfail07.hs | 10 + .../tests/annotations/should_fail/annfail07.stderr | 5 + .../tests/annotations/should_fail/annfail08.hs | 10 + .../tests/annotations/should_fail/annfail08.stderr | 9 + .../tests/annotations/should_fail/annfail09.hs | 12 + .../tests/annotations/should_fail/annfail09.stderr | 6 + .../tests/annotations/should_fail/annfail10.hs | 10 + .../tests/annotations/should_fail/annfail10.stderr | 25 + .../tests/annotations/should_fail/annfail11.hs | 4 + .../tests/annotations/should_fail/annfail11.stderr | 10 + .../tests/annotations/should_fail/annfail12.hs | 6 + .../tests/annotations/should_fail/annfail12.stderr | 6 + .../tests/annotations/should_fail/annfail13.hs | 6 + .../tests/annotations/should_fail/annfail13.stderr | 2 + .../tests/annotations/should_run/Annrun01_Help.hs | 27 + testsuite/tests/annotations/should_run/Makefile | 12 + testsuite/tests/annotations/should_run/all.T | 32 + testsuite/tests/annotations/should_run/annrun01.hs | 51 + .../tests/annotations/should_run/annrun01.stdout | 13 + testsuite/tests/arityanal/Main.hs | 303 + testsuite/tests/arityanal/Main.stderr | 1874 +++ testsuite/tests/arityanal/f0.hs | 6 + testsuite/tests/arityanal/f0.stderr | 12 + testsuite/tests/arityanal/f1.hs | 10 + testsuite/tests/arityanal/f1.stderr | 20 + testsuite/tests/arityanal/f10.hs | 8 + testsuite/tests/arityanal/f10.stderr | 27 + testsuite/tests/arityanal/f11.hs | 10 + testsuite/tests/arityanal/f11.stderr | 45 + testsuite/tests/arityanal/f12.hs | 5 + testsuite/tests/arityanal/f12.stderr | 8 + testsuite/tests/arityanal/f13.hs | 8 + testsuite/tests/arityanal/f13.stderr | 17 + testsuite/tests/arityanal/f14.hs | 5 + testsuite/tests/arityanal/f14.stderr | 26 + testsuite/tests/arityanal/f15.hs | 5 + testsuite/tests/arityanal/f15.stderr | 14 + testsuite/tests/arityanal/f2.hs | 7 + testsuite/tests/arityanal/f2.stderr | 18 + testsuite/tests/arityanal/f3.hs | 8 + testsuite/tests/arityanal/f3.stderr | 15 + testsuite/tests/arityanal/f4.hs | 7 + testsuite/tests/arityanal/f4.stderr | 22 + testsuite/tests/arityanal/f5.hs | 7 + testsuite/tests/arityanal/f5.stderr | 47 + testsuite/tests/arityanal/f6.hs | 5 + testsuite/tests/arityanal/f6.stderr | 16 + testsuite/tests/arityanal/f7.hs | 5 + testsuite/tests/arityanal/f7.stderr | 14 + testsuite/tests/arityanal/f8.hs | 5 + testsuite/tests/arityanal/f8.stderr | 20 + testsuite/tests/arityanal/f9.hs | 4 + testsuite/tests/arityanal/f9.stderr | 15 + testsuite/tests/arityanal/prim.hs | 7 + testsuite/tests/arityanal/prim.stderr | 15 + testsuite/tests/array/Makefile | 3 + testsuite/tests/array/should_run/Makefile | 3 + testsuite/tests/array/should_run/all.T | 26 + testsuite/tests/array/should_run/arr001.hs | 9 + testsuite/tests/array/should_run/arr001.stdout | 1 + testsuite/tests/array/should_run/arr002.hs | 23 + testsuite/tests/array/should_run/arr002.stdout | 3 + testsuite/tests/array/should_run/arr003.hs | 16 + testsuite/tests/array/should_run/arr003.stderr | 1 + .../tests/array/should_run/arr003.stderr-hugs | 1 + testsuite/tests/array/should_run/arr004.hs | 15 + testsuite/tests/array/should_run/arr004.stderr | 1 + .../tests/array/should_run/arr004.stderr-hugs | 1 + testsuite/tests/array/should_run/arr005.hs | 16 + testsuite/tests/array/should_run/arr005.stdout | 1 + testsuite/tests/array/should_run/arr006.hs | 11 + testsuite/tests/array/should_run/arr006.stdout | 1 + testsuite/tests/array/should_run/arr007.hs | 11 + testsuite/tests/array/should_run/arr007.stderr | 1 + .../tests/array/should_run/arr007.stderr-hugs | 1 + testsuite/tests/array/should_run/arr008.hs | 14 + testsuite/tests/array/should_run/arr008.stderr | 1 + .../tests/array/should_run/arr008.stderr-hugs | 1 + testsuite/tests/array/should_run/arr008.stdout | 1 + .../tests/array/should_run/arr008.stdout-hugs | 2 + testsuite/tests/array/should_run/arr009.hs | 17 + testsuite/tests/array/should_run/arr009.stdout | 2 + testsuite/tests/array/should_run/arr010.hs | 18 + testsuite/tests/array/should_run/arr010.stdout | 1 + testsuite/tests/array/should_run/arr011.hs | 20 + testsuite/tests/array/should_run/arr011.stdout | 2 + testsuite/tests/array/should_run/arr012.hs | 19 + testsuite/tests/array/should_run/arr012.stdout | 3 + testsuite/tests/array/should_run/arr013.hs | 17 + testsuite/tests/array/should_run/arr013.stdout | 1 + testsuite/tests/array/should_run/arr014.hs | 26 + testsuite/tests/array/should_run/arr015.hs | 50 + testsuite/tests/array/should_run/arr015.stdout | 5 + testsuite/tests/array/should_run/arr016.hs | 511 + testsuite/tests/array/should_run/arr016.stdout | 8 + testsuite/tests/array/should_run/arr017.hs | 30 + testsuite/tests/array/should_run/arr017.stdout | 1 + testsuite/tests/array/should_run/arr018.hs | 16 + testsuite/tests/array/should_run/arr018.stdout | 2 + testsuite/tests/array/should_run/arr019.hs | 27 + testsuite/tests/array/should_run/arr019.stdout | 14 + testsuite/tests/array/should_run/arr020.hs | 132 + testsuite/tests/array/should_run/arr020.stdout | 2 + testsuite/tests/arrows/Makefile | 3 + testsuite/tests/arrows/should_compile/Makefile | 3 + testsuite/tests/arrows/should_compile/T3964.hs | 10 + testsuite/tests/arrows/should_compile/T5022.hs | 19 + testsuite/tests/arrows/should_compile/T5267.hs | 31 + testsuite/tests/arrows/should_compile/T5283.hs | 20 + testsuite/tests/arrows/should_compile/all.T | 19 + .../tests/arrows/should_compile/arrowapply1.hs | 8 + .../tests/arrows/should_compile/arrowapply2.hs | 11 + .../tests/arrows/should_compile/arrowapply3.hs | 8 + .../tests/arrows/should_compile/arrowapply5.hs | 13 + .../tests/arrows/should_compile/arrowcase1.hs | 18 + testsuite/tests/arrows/should_compile/arrowdo1.hs | 17 + testsuite/tests/arrows/should_compile/arrowdo2.hs | 10 + testsuite/tests/arrows/should_compile/arrowdo3.hs | 222 + .../tests/arrows/should_compile/arrowform1.hs | 30 + testsuite/tests/arrows/should_compile/arrowif1.hs | 11 + testsuite/tests/arrows/should_compile/arrowlet1.hs | 8 + testsuite/tests/arrows/should_compile/arrowpat.hs | 23 + testsuite/tests/arrows/should_compile/arrowrec1.hs | 13 + testsuite/tests/arrows/should_fail/Makefile | 3 + testsuite/tests/arrows/should_fail/T2111.hs | 10 + testsuite/tests/arrows/should_fail/T2111.stderr | 8 + .../tests/arrows/should_fail/T2111.stderr-ghc-7.0 | 10 + testsuite/tests/arrows/should_fail/T5380.hs | 7 + testsuite/tests/arrows/should_fail/T5380.stderr | 27 + testsuite/tests/arrows/should_fail/all.T | 15 + testsuite/tests/arrows/should_fail/arrowfail001.hs | 21 + .../tests/arrows/should_fail/arrowfail001.stderr | 7 + testsuite/tests/arrows/should_fail/arrowfail002.hs | 7 + .../tests/arrows/should_fail/arrowfail002.stderr | 2 + testsuite/tests/arrows/should_fail/arrowfail003.hs | 9 + .../tests/arrows/should_fail/arrowfail003.stderr | 8 + testsuite/tests/arrows/should_fail/arrowfail004.hs | 12 + .../tests/arrows/should_fail/arrowfail004.stderr | 7 + testsuite/tests/arrows/should_run/Makefile | 3 + testsuite/tests/arrows/should_run/T3822.hs | 17 + testsuite/tests/arrows/should_run/T3822.stdout | 2 + testsuite/tests/arrows/should_run/all.T | 8 + testsuite/tests/arrows/should_run/arrowrun001.hs | 48 + .../tests/arrows/should_run/arrowrun001.stdout | 2 + testsuite/tests/arrows/should_run/arrowrun002.hs | 225 + .../tests/arrows/should_run/arrowrun002.stdout | 4 + testsuite/tests/arrows/should_run/arrowrun003.hs | 133 + .../tests/arrows/should_run/arrowrun003.stdout | 6 + testsuite/tests/arrows/should_run/arrowrun004.hs | 128 + .../tests/arrows/should_run/arrowrun004.stdout | 2 + testsuite/tests/boxy/Base1.hs | 30 + testsuite/tests/boxy/Church1.hs | 28 + testsuite/tests/boxy/Church2.hs | 27 + testsuite/tests/boxy/Church2.stderr | 12 + testsuite/tests/boxy/Compose.hs | 26 + testsuite/tests/boxy/Makefile | 3 + testsuite/tests/boxy/PList1.hs | 26 + testsuite/tests/boxy/PList2.hs | 27 + testsuite/tests/boxy/SystemF.hs | 21 + testsuite/tests/boxy/T2193.hs | 13 + testsuite/tests/boxy/T2193.stdout | 1 + testsuite/tests/boxy/all.T | 11 + testsuite/tests/boxy/boxy.hs | 124 + testsuite/tests/cabal/Makefile | 184 + testsuite/tests/cabal/T1750.stderr | 5 + testsuite/tests/cabal/T1750.stdout | 4 + testsuite/tests/cabal/T1750A.pkg | 4 + testsuite/tests/cabal/T1750B.pkg | 4 + testsuite/tests/cabal/all.T | 66 + testsuite/tests/cabal/cabal01/A.hs | 4 + testsuite/tests/cabal/cabal01/B/A.hs | 4 + testsuite/tests/cabal/cabal01/B/MainB.hs | 5 + testsuite/tests/cabal/cabal01/MainA.hs | 5 + testsuite/tests/cabal/cabal01/Makefile | 45 + testsuite/tests/cabal/cabal01/Setup.lhs | 2 + testsuite/tests/cabal/cabal01/all.T | 29 + testsuite/tests/cabal/cabal01/c_src/hello.c | 1 + testsuite/tests/cabal/cabal01/cabal01.stdout | 12 + .../tests/cabal/cabal01/cabal01.stdout-mingw32 | 12 + testsuite/tests/cabal/cabal01/hello.c | 1 + testsuite/tests/cabal/cabal01/test.cabal | 16 + testsuite/tests/cabal/cabal03/Makefile | 41 + testsuite/tests/cabal/cabal03/Setup.lhs | 2 + testsuite/tests/cabal/cabal03/all.T | 9 + testsuite/tests/cabal/cabal03/p/P.hs | 3 + testsuite/tests/cabal/cabal03/p/p.cabal | 5 + testsuite/tests/cabal/cabal03/q/q.cabal | 5 + testsuite/tests/cabal/cabal03/r/r.cabal | 5 + testsuite/tests/cabal/cabal04/Library.hs | 6 + testsuite/tests/cabal/cabal04/Makefile | 26 + testsuite/tests/cabal/cabal04/Setup.lhs | 2 + testsuite/tests/cabal/cabal04/TH.hs | 6 + testsuite/tests/cabal/cabal04/all.T | 26 + testsuite/tests/cabal/cabal04/thtest.cabal | 11 + testsuite/tests/cabal/ghcpkg01.stderr | 2 + testsuite/tests/cabal/ghcpkg01.stdout | 223 + testsuite/tests/cabal/ghcpkg03.stderr | 31 + testsuite/tests/cabal/ghcpkg03.stderr-mingw32 | 31 + testsuite/tests/cabal/ghcpkg03.stdout | 5 + testsuite/tests/cabal/ghcpkg04.hs | 1 + testsuite/tests/cabal/ghcpkg04.stderr | 4 + testsuite/tests/cabal/ghcpkg05.stderr | 18 + testsuite/tests/cabal/ghcpkg05.stderr-mingw32 | 18 + testsuite/tests/cabal/ghcpkg05.stdout | 6 + testsuite/tests/cabal/ghcpkg06.stderr | 2 + testsuite/tests/cabal/ghcpkg06.stdout | 2 + testsuite/tests/cabal/pkg01.hs | 3 + testsuite/tests/cabal/pkg02/A.hs | 5 + testsuite/tests/cabal/pkg02/Foreign.hs | 2 + testsuite/tests/cabal/pkg02/Makefile | 4 + testsuite/tests/cabal/pkg02/all.T | 10 + testsuite/tests/cabal/shadow.stderr | 4 + testsuite/tests/cabal/shadow.stdout | 10 + testsuite/tests/cabal/shadow1.pkg | 4 + testsuite/tests/cabal/shadow2.pkg | 4 + testsuite/tests/cabal/shadow3.pkg | 4 + testsuite/tests/cabal/test.pkg | 19 + testsuite/tests/cabal/test2.pkg | 19 + testsuite/tests/cabal/test3.pkg | 19 + testsuite/tests/cabal/test4.pkg | 19 + testsuite/tests/cabal/test5.pkg | 18 + testsuite/tests/cabal/testdup.pkg | 5 + testsuite/tests/codeGen/Makefile | 3 + testsuite/tests/codeGen/should_compile/Makefile | 7 + testsuite/tests/codeGen/should_compile/T1916.hs | 3 + testsuite/tests/codeGen/should_compile/T2388.hs | 14 + testsuite/tests/codeGen/should_compile/T2578.hs | 17 + testsuite/tests/codeGen/should_compile/T3132.hs | 6 + testsuite/tests/codeGen/should_compile/T3286.hs | 45 + testsuite/tests/codeGen/should_compile/T3286b.hs | 15 + testsuite/tests/codeGen/should_compile/T3579.hs | 7 + testsuite/tests/codeGen/should_compile/T7237.hs | 10 + testsuite/tests/codeGen/should_compile/T7574.cmm | 11 + testsuite/tests/codeGen/should_compile/T8205.hs | 10 + testsuite/tests/codeGen/should_compile/all.T | 24 + testsuite/tests/codeGen/should_compile/cg001.hs | 15 + testsuite/tests/codeGen/should_compile/cg002.hs | 5 + testsuite/tests/codeGen/should_compile/cg003.hs | 7 + testsuite/tests/codeGen/should_compile/cg004.hs | 30 + testsuite/tests/codeGen/should_compile/cg005.hs | 20 + testsuite/tests/codeGen/should_compile/cg006.hs | 8 + testsuite/tests/codeGen/should_compile/cg007.hs | 26 + testsuite/tests/codeGen/should_compile/cg008.hs | 21 + testsuite/tests/codeGen/should_compile/jmp_tbl.hs | 138 + .../tests/codeGen/should_compile/massive_array.hs | 520 + testsuite/tests/codeGen/should_gen_asm/Makefile | 3 + testsuite/tests/codeGen/should_gen_asm/all.T | 6 + .../should_gen_asm/memcpy-unroll-conprop.asm | 21 + .../should_gen_asm/memcpy-unroll-conprop.cmm | 14 + .../tests/codeGen/should_gen_asm/memcpy-unroll.asm | 18 + .../tests/codeGen/should_gen_asm/memcpy-unroll.cmm | 8 + testsuite/tests/codeGen/should_gen_asm/memcpy.asm | 9 + testsuite/tests/codeGen/should_gen_asm/memcpy.cmm | 8 + testsuite/tests/codeGen/should_run/Cgrun067A.hs | 14 + testsuite/tests/codeGen/should_run/Makefile | 4 + testsuite/tests/codeGen/should_run/T1852.hs | 19 + testsuite/tests/codeGen/should_run/T1852.stdout | 1 + testsuite/tests/codeGen/should_run/T1861.hs | 9 + testsuite/tests/codeGen/should_run/T1861.stdout | 3 + testsuite/tests/codeGen/should_run/T2080.hs | 25 + testsuite/tests/codeGen/should_run/T2080.stdout | 1 + testsuite/tests/codeGen/should_run/T2838.hs | 9 + testsuite/tests/codeGen/should_run/T2838.stdout | 1 + .../tests/codeGen/should_run/T2838.stdout-ws-64 | 1 + testsuite/tests/codeGen/should_run/T3207.hs | 29 + testsuite/tests/codeGen/should_run/T3207.stdout | 1 + testsuite/tests/codeGen/should_run/T3561.hs | 10 + testsuite/tests/codeGen/should_run/T3561.stdout | 1 + testsuite/tests/codeGen/should_run/T3677.hs | 15 + testsuite/tests/codeGen/should_run/T3677.stdout | 1 + testsuite/tests/codeGen/should_run/T4441.hs | 20 + testsuite/tests/codeGen/should_run/T4441.stdout | 2 + testsuite/tests/codeGen/should_run/T5129.hs | 21 + testsuite/tests/codeGen/should_run/T5149.hs | 8 + testsuite/tests/codeGen/should_run/T5149.stdout | 1 + testsuite/tests/codeGen/should_run/T5149_cmm.cmm | 23 + testsuite/tests/codeGen/should_run/T5626.hs | 11 + testsuite/tests/codeGen/should_run/T5626.stderr | 1 + testsuite/tests/codeGen/should_run/T5747.hs | 1 + testsuite/tests/codeGen/should_run/T5747.stdout | 1 + testsuite/tests/codeGen/should_run/T5785.hs | 40 + testsuite/tests/codeGen/should_run/T5785.stdout | 24 + testsuite/tests/codeGen/should_run/T5900.hs | 25 + testsuite/tests/codeGen/should_run/T5900.stderr | 1 + testsuite/tests/codeGen/should_run/T5900.stdout | 1 + testsuite/tests/codeGen/should_run/T6084.hs | 28 + testsuite/tests/codeGen/should_run/T6084.stdout | 3 + testsuite/tests/codeGen/should_run/T6146.hs | 20 + testsuite/tests/codeGen/should_run/T6146.stdin | 2 + testsuite/tests/codeGen/should_run/T6146.stdout | 3 + testsuite/tests/codeGen/should_run/T7163.hs | 10 + testsuite/tests/codeGen/should_run/T7163.stdout | 1 + testsuite/tests/codeGen/should_run/T7319.hs | 11 + testsuite/tests/codeGen/should_run/T7319.stderr | 1 + testsuite/tests/codeGen/should_run/T7361.hs | 12 + testsuite/tests/codeGen/should_run/T7361.stdout | 1 + testsuite/tests/codeGen/should_run/T7600.hs | 111 + testsuite/tests/codeGen/should_run/T7600.stdout | 2 + testsuite/tests/codeGen/should_run/T7600_A.hs | 83 + testsuite/tests/codeGen/should_run/T7953.hs | 67 + testsuite/tests/codeGen/should_run/T7953.stdout | 5 + testsuite/tests/codeGen/should_run/T8103.hs | 8 + testsuite/tests/codeGen/should_run/T8103.stdout | 1 + testsuite/tests/codeGen/should_run/T8103_A.hs | 7 + testsuite/tests/codeGen/should_run/T8256.hs | 48 + testsuite/tests/codeGen/should_run/T8256.stdout | 1 + testsuite/tests/codeGen/should_run/Word2Float32.hs | 17 + .../tests/codeGen/should_run/Word2Float32.stdout | 4 + testsuite/tests/codeGen/should_run/Word2Float64.hs | 17 + .../tests/codeGen/should_run/Word2Float64.stdout | 4 + testsuite/tests/codeGen/should_run/all.T | 118 + testsuite/tests/codeGen/should_run/cgrun001.hs | 6 + testsuite/tests/codeGen/should_run/cgrun001.stdout | 1 + testsuite/tests/codeGen/should_run/cgrun002.hs | 12 + testsuite/tests/codeGen/should_run/cgrun002.stdout | 1 + testsuite/tests/codeGen/should_run/cgrun003.hs | 11 + testsuite/tests/codeGen/should_run/cgrun003.stdout | 1 + testsuite/tests/codeGen/should_run/cgrun004.hs | 1 + testsuite/tests/codeGen/should_run/cgrun004.stdout | 1 + testsuite/tests/codeGen/should_run/cgrun005.hs | 6 + testsuite/tests/codeGen/should_run/cgrun005.stdout | 1 + testsuite/tests/codeGen/should_run/cgrun006.hs | 6 + testsuite/tests/codeGen/should_run/cgrun006.stdout | 1 + testsuite/tests/codeGen/should_run/cgrun007.hs | 14 + testsuite/tests/codeGen/should_run/cgrun007.stdout | 1 + testsuite/tests/codeGen/should_run/cgrun008.hs | 12 + testsuite/tests/codeGen/should_run/cgrun008.stdout | 1 + testsuite/tests/codeGen/should_run/cgrun009.hs | 7 + testsuite/tests/codeGen/should_run/cgrun009.stdout | 1 + testsuite/tests/codeGen/should_run/cgrun010.hs | 5 + testsuite/tests/codeGen/should_run/cgrun010.stdout | 1 + testsuite/tests/codeGen/should_run/cgrun011.hs | 29 + testsuite/tests/codeGen/should_run/cgrun011.stdout | 1 + testsuite/tests/codeGen/should_run/cgrun012.hs | 39 + testsuite/tests/codeGen/should_run/cgrun012.stdout | 1 + testsuite/tests/codeGen/should_run/cgrun013.hs | 78 + testsuite/tests/codeGen/should_run/cgrun013.stdout | 1 + testsuite/tests/codeGen/should_run/cgrun014.hs | 3 + testsuite/tests/codeGen/should_run/cgrun014.stdout | 1 + testsuite/tests/codeGen/should_run/cgrun015.hs | 31 + testsuite/tests/codeGen/should_run/cgrun015.stdout | 1 + testsuite/tests/codeGen/should_run/cgrun016.hs | 9 + testsuite/tests/codeGen/should_run/cgrun016.stderr | 1 + testsuite/tests/codeGen/should_run/cgrun017.hs | 33 + testsuite/tests/codeGen/should_run/cgrun017.stdout | 1 + testsuite/tests/codeGen/should_run/cgrun018.hs | 25 + testsuite/tests/codeGen/should_run/cgrun018.stdout | 1 + testsuite/tests/codeGen/should_run/cgrun019.hs | 3 + testsuite/tests/codeGen/should_run/cgrun019.stdout | 1 + testsuite/tests/codeGen/should_run/cgrun020.hs | 3 + testsuite/tests/codeGen/should_run/cgrun020.stdout | 1 + testsuite/tests/codeGen/should_run/cgrun021.hs | 60 + testsuite/tests/codeGen/should_run/cgrun021.stdout | 1 + testsuite/tests/codeGen/should_run/cgrun022.hs | 10 + testsuite/tests/codeGen/should_run/cgrun022.stdout | 1 + testsuite/tests/codeGen/should_run/cgrun023.stdout | 1 + testsuite/tests/codeGen/should_run/cgrun024.hs | 8 + testsuite/tests/codeGen/should_run/cgrun024.stdout | 1 + testsuite/tests/codeGen/should_run/cgrun025.hs | 23 + testsuite/tests/codeGen/should_run/cgrun025.stderr | 28 + testsuite/tests/codeGen/should_run/cgrun026.hs | 250 + testsuite/tests/codeGen/should_run/cgrun026.stdout | 12 + testsuite/tests/codeGen/should_run/cgrun027.hs | 13 + testsuite/tests/codeGen/should_run/cgrun027.stdout | 1 + testsuite/tests/codeGen/should_run/cgrun028.hs | 10 + testsuite/tests/codeGen/should_run/cgrun028.stdout | 1 + testsuite/tests/codeGen/should_run/cgrun031.hs | 45 + testsuite/tests/codeGen/should_run/cgrun031.stdout | 2 + testsuite/tests/codeGen/should_run/cgrun032.hs | 22 + testsuite/tests/codeGen/should_run/cgrun032.stdout | 1 + testsuite/tests/codeGen/should_run/cgrun033.hs | 79 + testsuite/tests/codeGen/should_run/cgrun033.stdout | 1 + testsuite/tests/codeGen/should_run/cgrun034.hs | 161 + testsuite/tests/codeGen/should_run/cgrun034.stdout | 12 + testsuite/tests/codeGen/should_run/cgrun035.hs | 15 + testsuite/tests/codeGen/should_run/cgrun035.stdout | 1 + testsuite/tests/codeGen/should_run/cgrun036.hs | 16 + testsuite/tests/codeGen/should_run/cgrun036.stdout | 1 + testsuite/tests/codeGen/should_run/cgrun037.hs | 6 + testsuite/tests/codeGen/should_run/cgrun037.stdout | Bin 0 -> 13 bytes testsuite/tests/codeGen/should_run/cgrun038.hs | 13 + testsuite/tests/codeGen/should_run/cgrun039.hs | 14 + testsuite/tests/codeGen/should_run/cgrun039.stdout | 1 + testsuite/tests/codeGen/should_run/cgrun040.hs | 16 + testsuite/tests/codeGen/should_run/cgrun040.stdout | 1 + testsuite/tests/codeGen/should_run/cgrun043.hs | 18 + testsuite/tests/codeGen/should_run/cgrun044.hs | 196 + testsuite/tests/codeGen/should_run/cgrun044.stdout | 264 + testsuite/tests/codeGen/should_run/cgrun045.hs | 8 + testsuite/tests/codeGen/should_run/cgrun045.stderr | 1 + testsuite/tests/codeGen/should_run/cgrun046.hs | 10 + testsuite/tests/codeGen/should_run/cgrun046.stdout | 1 + testsuite/tests/codeGen/should_run/cgrun047.hs | 18 + testsuite/tests/codeGen/should_run/cgrun047.stdout | 1 + testsuite/tests/codeGen/should_run/cgrun048.hs | 24 + testsuite/tests/codeGen/should_run/cgrun048.stdout | 1 + testsuite/tests/codeGen/should_run/cgrun049.hs | 22 + testsuite/tests/codeGen/should_run/cgrun049.stdout | 1 + testsuite/tests/codeGen/should_run/cgrun050.hs | 23 + testsuite/tests/codeGen/should_run/cgrun050.stdout | 1 + testsuite/tests/codeGen/should_run/cgrun051.hs | 9 + testsuite/tests/codeGen/should_run/cgrun051.stderr | 1 + testsuite/tests/codeGen/should_run/cgrun052.hs | 13 + testsuite/tests/codeGen/should_run/cgrun052.stdout | 1 + testsuite/tests/codeGen/should_run/cgrun053.hs | 3 + testsuite/tests/codeGen/should_run/cgrun054.hs | 29 + testsuite/tests/codeGen/should_run/cgrun054.stdout | 1 + testsuite/tests/codeGen/should_run/cgrun055.hs | 46 + testsuite/tests/codeGen/should_run/cgrun055.stdout | 7 + testsuite/tests/codeGen/should_run/cgrun056.hs | 8 + testsuite/tests/codeGen/should_run/cgrun056.stdout | 2 + testsuite/tests/codeGen/should_run/cgrun057.hs | 7 + testsuite/tests/codeGen/should_run/cgrun057.stderr | 6 + testsuite/tests/codeGen/should_run/cgrun058.hs | 30 + testsuite/tests/codeGen/should_run/cgrun058.stdout | 1 + testsuite/tests/codeGen/should_run/cgrun059.hs | 34 + testsuite/tests/codeGen/should_run/cgrun059.stderr | 1 + testsuite/tests/codeGen/should_run/cgrun059.stdout | 1 + testsuite/tests/codeGen/should_run/cgrun060.hs | 18 + testsuite/tests/codeGen/should_run/cgrun060.stdout | 1 + testsuite/tests/codeGen/should_run/cgrun061.hs | 17 + testsuite/tests/codeGen/should_run/cgrun061.stdout | 2 + testsuite/tests/codeGen/should_run/cgrun062.hs | 17 + testsuite/tests/codeGen/should_run/cgrun062.stdout | 2 + testsuite/tests/codeGen/should_run/cgrun063.hs | 20 + testsuite/tests/codeGen/should_run/cgrun063.stdout | 9 + testsuite/tests/codeGen/should_run/cgrun064.hs | 229 + testsuite/tests/codeGen/should_run/cgrun064.stdout | 16 + testsuite/tests/codeGen/should_run/cgrun065.hs | 33 + testsuite/tests/codeGen/should_run/cgrun065.stdout | 4 + testsuite/tests/codeGen/should_run/cgrun066.hs | 21 + testsuite/tests/codeGen/should_run/cgrun066.stdout | 1 + testsuite/tests/codeGen/should_run/cgrun067.hs | 11 + testsuite/tests/codeGen/should_run/cgrun067.stdout | 1 + testsuite/tests/codeGen/should_run/cgrun068.hs | 387 + testsuite/tests/codeGen/should_run/cgrun068.stdout | 2 + testsuite/tests/codeGen/should_run/cgrun069.hs | 82 + testsuite/tests/codeGen/should_run/cgrun069.stdout | 2 + .../tests/codeGen/should_run/cgrun069_cmm.cmm | 214 + testsuite/tests/codeGen/should_run/cgrun070.hs | 241 + testsuite/tests/codeGen/should_run/cgrun070.stdout | 12 + testsuite/tests/codeGen/should_run/cgrun071.hs | 78 + testsuite/tests/codeGen/should_run/cgrun071.stdout | 6 + testsuite/tests/codeGen/should_run/cgrun072.hs | 101 + testsuite/tests/codeGen/should_run/cgrun072.stdout | 9 + testsuite/tests/codeGen/should_run/setByteArray.hs | 23 + .../tests/codeGen/should_run/setByteArray.stdout | 8 + testsuite/tests/concurrent/Makefile | 3 + testsuite/tests/concurrent/T2317/Makefile | 3 + testsuite/tests/concurrent/T2317/T2317.hs | 34 + testsuite/tests/concurrent/T2317/T2317.stdout | 2 + testsuite/tests/concurrent/T2317/all.T | 5 + testsuite/tests/concurrent/prog001/Arithmetic.hs | 235 + testsuite/tests/concurrent/prog001/Converter.hs | 130 + testsuite/tests/concurrent/prog001/Main.hs | 3 + testsuite/tests/concurrent/prog001/Makefile | 3 + testsuite/tests/concurrent/prog001/Mult.hs | 237 + testsuite/tests/concurrent/prog001/Stream.hs | 156 + testsuite/tests/concurrent/prog001/Thread.hs | 114 + testsuite/tests/concurrent/prog001/Trit.hs | 112 + testsuite/tests/concurrent/prog001/Utilities.hs | 17 + testsuite/tests/concurrent/prog001/all.T | 26 + .../tests/concurrent/prog001/concprog001.stdout | 1 + testsuite/tests/concurrent/prog002/Event.hs | 6 + testsuite/tests/concurrent/prog002/FileIO.hs | 9 + testsuite/tests/concurrent/prog002/Makefile | 3 + testsuite/tests/concurrent/prog002/Scheduler.hs | 74 + testsuite/tests/concurrent/prog002/Server.hs | 18 + testsuite/tests/concurrent/prog002/Thread.hs | 38 + testsuite/tests/concurrent/prog002/all.T | 23 + .../tests/concurrent/prog002/concprog002.stderr | 1 + .../tests/concurrent/prog002/concprog002.stdout | 1 + testsuite/tests/concurrent/prog003/BackList2.lhs | 185 + testsuite/tests/concurrent/prog003/CASList.hs | 254 + testsuite/tests/concurrent/prog003/Collate.hs | 64 + testsuite/tests/concurrent/prog003/Collection.hs | 11 + testsuite/tests/concurrent/prog003/IOList.lhs | 138 + testsuite/tests/concurrent/prog003/ImmList.hs | 71 + .../concurrent/prog003/MVarListLockCoupling.hs | 183 + testsuite/tests/concurrent/prog003/Main.lhs | 217 + .../tests/concurrent/prog003/MainMVarList.lhs | 237 + testsuite/tests/concurrent/prog003/Makefile | 3 + testsuite/tests/concurrent/prog003/RefInterface.hs | 15 + testsuite/tests/concurrent/prog003/TestData.hs | 32 + .../tests/concurrent/prog003/TestDataParser.hs | 103 + testsuite/tests/concurrent/prog003/TestRun.hs | 219 + testsuite/tests/concurrent/prog003/all.T | 34 + .../tests/concurrent/prog003/concprog003.stdout | 2 + .../concurrent/prog003/test-8-3000-3000-2-1-4 | 13 + testsuite/tests/concurrent/should_run/Makefile | 6 + testsuite/tests/concurrent/should_run/T1980.hs | 13 + testsuite/tests/concurrent/should_run/T2910.hs | 9 + testsuite/tests/concurrent/should_run/T2910.stdout | 2 + testsuite/tests/concurrent/should_run/T2910a.hs | 9 + .../tests/concurrent/should_run/T2910a.stdout | 2 + testsuite/tests/concurrent/should_run/T3279.hs | 25 + testsuite/tests/concurrent/should_run/T3279.stdout | 1 + testsuite/tests/concurrent/should_run/T3429.hs | 22 + testsuite/tests/concurrent/should_run/T3429.stdout | 1 + testsuite/tests/concurrent/should_run/T367.hs | 10 + testsuite/tests/concurrent/should_run/T367.stdout | 1 + .../concurrent/should_run/T367_letnoescape.hs | 23 + .../concurrent/should_run/T367_letnoescape.stdout | 1 + testsuite/tests/concurrent/should_run/T4030.hs | 8 + testsuite/tests/concurrent/should_run/T4030.stderr | 1 + testsuite/tests/concurrent/should_run/T4262.hs | 27 + testsuite/tests/concurrent/should_run/T4262.stdout | 1 + testsuite/tests/concurrent/should_run/T4811.hs | 14 + testsuite/tests/concurrent/should_run/T4813.hs | 12 + testsuite/tests/concurrent/should_run/T5238.hs | 12 + testsuite/tests/concurrent/should_run/T5238.stdout | 1 + testsuite/tests/concurrent/should_run/T5421.hs | 17 + testsuite/tests/concurrent/should_run/T5558.hs | 25 + testsuite/tests/concurrent/should_run/T5611.hs | 34 + testsuite/tests/concurrent/should_run/T5611.stderr | 1 + testsuite/tests/concurrent/should_run/T5611.stdout | 2 + testsuite/tests/concurrent/should_run/T5866.hs | 10 + testsuite/tests/concurrent/should_run/T5866.stderr | 1 + testsuite/tests/concurrent/should_run/T7970.hs | 20 + testsuite/tests/concurrent/should_run/T7970.stdout | 4 + testsuite/tests/concurrent/should_run/all.T | 247 + .../concurrent/should_run/allowinterrupt001.hs | 13 + testsuite/tests/concurrent/should_run/async001.hs | 19 + .../tests/concurrent/should_run/async001.stdout | 1 + .../tests/concurrent/should_run/compareAndSwap.hs | 78 + .../concurrent/should_run/compareAndSwap.stdout | 9 + testsuite/tests/concurrent/should_run/conc001.hs | 15 + .../tests/concurrent/should_run/conc001.stdout | 1 + testsuite/tests/concurrent/should_run/conc002.hs | 14 + .../tests/concurrent/should_run/conc002.stdout | 1 + testsuite/tests/concurrent/should_run/conc003.hs | 28 + .../tests/concurrent/should_run/conc003.stdout | 1 + testsuite/tests/concurrent/should_run/conc004.hs | 19 + .../tests/concurrent/should_run/conc004.stdout | 1 + testsuite/tests/concurrent/should_run/conc006.hs | 23 + .../tests/concurrent/should_run/conc006.stdout | 1 + testsuite/tests/concurrent/should_run/conc007.hs | 23 + .../tests/concurrent/should_run/conc007.stdout | 1 + testsuite/tests/concurrent/should_run/conc008.hs | 12 + .../tests/concurrent/should_run/conc008.stdout | 1 + testsuite/tests/concurrent/should_run/conc009.hs | 9 + .../tests/concurrent/should_run/conc009.stderr | 1 + testsuite/tests/concurrent/should_run/conc010.hs | 28 + .../tests/concurrent/should_run/conc010.stdout | 1 + testsuite/tests/concurrent/should_run/conc012.hs | 23 + .../tests/concurrent/should_run/conc012.stdout | 1 + testsuite/tests/concurrent/should_run/conc013.hs | 10 + .../tests/concurrent/should_run/conc013.stdout | 1 + testsuite/tests/concurrent/should_run/conc014.hs | 27 + .../tests/concurrent/should_run/conc014.stdout | 2 + testsuite/tests/concurrent/should_run/conc015.hs | 43 + .../tests/concurrent/should_run/conc015.stdout | 5 + testsuite/tests/concurrent/should_run/conc015a.hs | 47 + .../tests/concurrent/should_run/conc015a.stdout | 5 + testsuite/tests/concurrent/should_run/conc016.hs | 27 + .../tests/concurrent/should_run/conc016.stdout | 1 + testsuite/tests/concurrent/should_run/conc017.hs | 44 + .../tests/concurrent/should_run/conc017.stdout | 2 + testsuite/tests/concurrent/should_run/conc017a.hs | 44 + .../tests/concurrent/should_run/conc017a.stdout | 2 + testsuite/tests/concurrent/should_run/conc018.hs | 26 + .../tests/concurrent/should_run/conc018.stdout | 1 + testsuite/tests/concurrent/should_run/conc019.hs | 14 + .../tests/concurrent/should_run/conc019.stdout | 1 + testsuite/tests/concurrent/should_run/conc020.hs | 10 + .../tests/concurrent/should_run/conc020.stderr | 1 + testsuite/tests/concurrent/should_run/conc021.hs | 11 + .../tests/concurrent/should_run/conc021.stderr | 1 + testsuite/tests/concurrent/should_run/conc022.hs | 40 + .../tests/concurrent/should_run/conc022.stdout | 2 + testsuite/tests/concurrent/should_run/conc023.hs | 22 + testsuite/tests/concurrent/should_run/conc024.hs | 18 + .../tests/concurrent/should_run/conc024.stdout | 1 + testsuite/tests/concurrent/should_run/conc025.hs | 16 + .../tests/concurrent/should_run/conc025.stdout | 1 + testsuite/tests/concurrent/should_run/conc026.hs | 8 + testsuite/tests/concurrent/should_run/conc027.hs | 9 + testsuite/tests/concurrent/should_run/conc028.hs | 11 + .../tests/concurrent/should_run/conc028.stdout | 2 + testsuite/tests/concurrent/should_run/conc029.hs | 14 + .../tests/concurrent/should_run/conc029.stdout | 1 + testsuite/tests/concurrent/should_run/conc030.hs | 18 + .../tests/concurrent/should_run/conc030.stdout | 1 + testsuite/tests/concurrent/should_run/conc031.hs | 30 + .../tests/concurrent/should_run/conc031.stderr | 1 + testsuite/tests/concurrent/should_run/conc032.hs | 74 + .../tests/concurrent/should_run/conc032.stdout | 9 + testsuite/tests/concurrent/should_run/conc033.hs | 10 + .../tests/concurrent/should_run/conc033.stdout | 1 + testsuite/tests/concurrent/should_run/conc034.hs | 34 + .../tests/concurrent/should_run/conc034.stdout | 1 + testsuite/tests/concurrent/should_run/conc035.hs | 49 + .../tests/concurrent/should_run/conc035.stdout | 5 + testsuite/tests/concurrent/should_run/conc036.hs | 35 + .../tests/concurrent/should_run/conc036.stdout | 4 + testsuite/tests/concurrent/should_run/conc037.hs | 27 + .../tests/concurrent/should_run/conc037.stdout | 6 + testsuite/tests/concurrent/should_run/conc038.hs | 37 + .../tests/concurrent/should_run/conc038.stdout | 7 + testsuite/tests/concurrent/should_run/conc039.hs | 32 + testsuite/tests/concurrent/should_run/conc040.hs | 29 + .../tests/concurrent/should_run/conc040.stderr | 1 + testsuite/tests/concurrent/should_run/conc041.hs | 9 + .../tests/concurrent/should_run/conc041.stdout | 2 + testsuite/tests/concurrent/should_run/conc042.hs | 11 + .../tests/concurrent/should_run/conc042.stdout | 2 + testsuite/tests/concurrent/should_run/conc043.hs | 13 + .../tests/concurrent/should_run/conc043.stdout | 2 + testsuite/tests/concurrent/should_run/conc044.hs | 13 + .../tests/concurrent/should_run/conc044.stdout | 2 + testsuite/tests/concurrent/should_run/conc045.hs | 39 + .../tests/concurrent/should_run/conc045.stdout | 2 + testsuite/tests/concurrent/should_run/conc051.hs | 32 + testsuite/tests/concurrent/should_run/conc058.hs | 13 + .../tests/concurrent/should_run/conc058.stderr | 1 + testsuite/tests/concurrent/should_run/conc059.hs | 26 + .../tests/concurrent/should_run/conc059.stdout | 3 + testsuite/tests/concurrent/should_run/conc059_c.c | 30 + testsuite/tests/concurrent/should_run/conc064.hs | 30 + .../tests/concurrent/should_run/conc064.stderr | 1 + testsuite/tests/concurrent/should_run/conc065.hs | 13 + testsuite/tests/concurrent/should_run/conc066.hs | 13 + testsuite/tests/concurrent/should_run/conc067.hs | 16 + testsuite/tests/concurrent/should_run/conc068.hs | 14 + .../tests/concurrent/should_run/conc068.stderr | 1 + testsuite/tests/concurrent/should_run/conc069.hs | 19 + .../tests/concurrent/should_run/conc069.stdout | 4 + testsuite/tests/concurrent/should_run/conc069a.hs | 19 + .../tests/concurrent/should_run/conc069a.stdout | 4 + testsuite/tests/concurrent/should_run/conc070.hs | 18 + .../tests/concurrent/should_run/conc070.stdout | 1 + testsuite/tests/concurrent/should_run/conc071.hs | 11 + .../tests/concurrent/should_run/conc071.stdout | 3 + testsuite/tests/concurrent/should_run/conc072.hs | 9 + .../tests/concurrent/should_run/conc072.stdout | 2 + testsuite/tests/concurrent/should_run/conc073.hs | 20 + .../tests/concurrent/should_run/conc073.stdout | 1 + .../concurrent/should_run/foreignInterruptible.hs | 40 + .../should_run/foreignInterruptible.stdout | 5 + testsuite/tests/concurrent/should_run/mask001.hs | 70 + testsuite/tests/concurrent/should_run/mask002.hs | 33 + .../tests/concurrent/should_run/mask002.stdout | 2 + .../tests/concurrent/should_run/numsparks001.hs | 11 + .../concurrent/should_run/numsparks001.stdout | 5 + testsuite/tests/concurrent/should_run/readMVar1.hs | 17 + testsuite/tests/concurrent/should_run/readMVar2.hs | 13 + testsuite/tests/concurrent/should_run/readMVar3.hs | 15 + .../concurrent/should_run/setnumcapabilities001.hs | 34 + .../should_run/setnumcapabilities001.stdout | 1 + .../tests/concurrent/should_run/throwto001.hs | 38 + .../tests/concurrent/should_run/throwto002.hs | 24 + .../tests/concurrent/should_run/throwto002.stdout | 1 + .../tests/concurrent/should_run/throwto003.hs | 16 + .../tests/concurrent/should_run/tryReadMVar1.hs | 10 + testsuite/tests/cpranal/Makefile | 3 + testsuite/tests/cpranal/should_compile/Cpr001.hs | 16 + .../tests/cpranal/should_compile/Cpr001_imp.hs | 65 + testsuite/tests/cpranal/should_compile/Makefile | 3 + testsuite/tests/cpranal/should_compile/all.T | 10 + testsuite/tests/cpranal/should_run/CPRRepeat.hs | 4 + .../tests/cpranal/should_run/CPRRepeat.stdout | 1 + testsuite/tests/cpranal/should_run/Makefile | 3 + testsuite/tests/cpranal/should_run/all.T | 7 + testsuite/tests/cps/all.T | 35 + testsuite/tests/cps/cmm001.cmm | 5 + testsuite/tests/cps/cmm002.cmm | 8 + testsuite/tests/cps/cps001.cmm | 9 + testsuite/tests/cps/cps002.cmm | 7 + testsuite/tests/cps/cps003.cmm | 15 + testsuite/tests/cps/cps004.cmm | 17 + testsuite/tests/cps/cps005.cmm | 7 + testsuite/tests/cps/cps006.cmm | 7 + testsuite/tests/cps/cps007.cmm | 4 + testsuite/tests/cps/cps008.cmm | 9 + testsuite/tests/cps/cps009.cmm | 7 + testsuite/tests/cps/cps010.cmm | 9 + testsuite/tests/cps/cps011.cmm | 7 + testsuite/tests/cps/cps012.cmm | 23 + testsuite/tests/cps/cps013.cmm | 21 + testsuite/tests/cps/cps014.cmm | 14 + testsuite/tests/cps/cps015.cmm | 17 + testsuite/tests/cps/cps016.cmm | 14 + testsuite/tests/cps/cps017.cmm | 16 + testsuite/tests/cps/cps018.cmm | 9 + testsuite/tests/cps/cps019.cmm | 12 + testsuite/tests/cps/cps020.cmm | 15 + testsuite/tests/cps/cps021.cmm | 11 + testsuite/tests/cps/cps022.cmm | 18 + testsuite/tests/cps/cps023.cmm | 18 + testsuite/tests/cps/cps024.cmm | 12 + testsuite/tests/cps/cps025.cmm | 3 + testsuite/tests/cps/cps026.cmm | 18 + testsuite/tests/cps/cps027.cmm | 29 + testsuite/tests/cps/cps028.cmm | 17 + testsuite/tests/deSugar/Makefile | 3 + .../tests/deSugar/should_compile/GadtOverlap.hs | 20 + .../deSugar/should_compile/GadtOverlap.stderr | 4 + testsuite/tests/deSugar/should_compile/Makefile | 16 + testsuite/tests/deSugar/should_compile/T2395.hs | 13 + .../tests/deSugar/should_compile/T2395.stderr | 4 + testsuite/tests/deSugar/should_compile/T2409.hs | 11 + testsuite/tests/deSugar/should_compile/T2431.hs | 8 + .../tests/deSugar/should_compile/T2431.stderr | 23 + testsuite/tests/deSugar/should_compile/T3263-1.hs | 36 + .../tests/deSugar/should_compile/T3263-1.stderr | 10 + testsuite/tests/deSugar/should_compile/T3263-2.hs | 38 + .../tests/deSugar/should_compile/T3263-2.stderr | 10 + testsuite/tests/deSugar/should_compile/T4371.hs | 12 + testsuite/tests/deSugar/should_compile/T4439.hs | 15 + testsuite/tests/deSugar/should_compile/T4488.hs | 29 + .../tests/deSugar/should_compile/T4488.stderr | 20 + testsuite/tests/deSugar/should_compile/T4870.hs | 10 + testsuite/tests/deSugar/should_compile/T4870a.hs | 8 + testsuite/tests/deSugar/should_compile/T5001.hs | 10 + testsuite/tests/deSugar/should_compile/T5001a.hs | 16 + testsuite/tests/deSugar/should_compile/T5117.hs | 17 + .../tests/deSugar/should_compile/T5117.stderr | 4 + testsuite/tests/deSugar/should_compile/T5252.hs | 13 + .../tests/deSugar/should_compile/T5252Take2.hs | 5 + .../tests/deSugar/should_compile/T5252Take2a.hs | 8 + testsuite/tests/deSugar/should_compile/T5252a.hs | 5 + testsuite/tests/deSugar/should_compile/T5455.hs | 13 + .../tests/deSugar/should_compile/T5455.stderr | 4 + testsuite/tests/deSugar/should_compile/T7669.hs | 11 + testsuite/tests/deSugar/should_compile/T8470.hs | 11 + testsuite/tests/deSugar/should_compile/all.T | 105 + .../tests/deSugar/should_compile/ds-wildcard.hs | 3 + testsuite/tests/deSugar/should_compile/ds001.hs | 25 + testsuite/tests/deSugar/should_compile/ds002.hs | 16 + .../tests/deSugar/should_compile/ds002.stderr-ghc | 10 + testsuite/tests/deSugar/should_compile/ds003.hs | 8 + .../tests/deSugar/should_compile/ds003.stderr-ghc | 6 + testsuite/tests/deSugar/should_compile/ds004.hs | 9 + testsuite/tests/deSugar/should_compile/ds005.hs | 15 + testsuite/tests/deSugar/should_compile/ds006.hs | 6 + testsuite/tests/deSugar/should_compile/ds007.hs | 6 + testsuite/tests/deSugar/should_compile/ds008.hs | 11 + testsuite/tests/deSugar/should_compile/ds009.hs | 13 + testsuite/tests/deSugar/should_compile/ds010.hs | 15 + testsuite/tests/deSugar/should_compile/ds011.hs | 11 + testsuite/tests/deSugar/should_compile/ds012.hs | 10 + testsuite/tests/deSugar/should_compile/ds013.hs | 23 + testsuite/tests/deSugar/should_compile/ds014.hs | 76 + testsuite/tests/deSugar/should_compile/ds015.hs | 9 + testsuite/tests/deSugar/should_compile/ds016.hs | 15 + testsuite/tests/deSugar/should_compile/ds017.hs | 12 + testsuite/tests/deSugar/should_compile/ds018.hs | 57 + testsuite/tests/deSugar/should_compile/ds019.hs | 8 + .../tests/deSugar/should_compile/ds019.stderr-ghc | 7 + testsuite/tests/deSugar/should_compile/ds020.hs | 57 + .../tests/deSugar/should_compile/ds020.stderr-ghc | 18 + testsuite/tests/deSugar/should_compile/ds021.hs | 8 + testsuite/tests/deSugar/should_compile/ds022.hs | 32 + .../tests/deSugar/should_compile/ds022.stderr-ghc | 6 + testsuite/tests/deSugar/should_compile/ds023.hs | 7 + testsuite/tests/deSugar/should_compile/ds024.hs | 11 + testsuite/tests/deSugar/should_compile/ds025.hs | 16 + testsuite/tests/deSugar/should_compile/ds026.hs | 14 + testsuite/tests/deSugar/should_compile/ds027.hs | 9 + testsuite/tests/deSugar/should_compile/ds028.hs | 13 + testsuite/tests/deSugar/should_compile/ds029.hs | 9 + testsuite/tests/deSugar/should_compile/ds030.hs | 5 + testsuite/tests/deSugar/should_compile/ds031.hs | 7 + testsuite/tests/deSugar/should_compile/ds032.hs | 17 + testsuite/tests/deSugar/should_compile/ds033.hs | 15 + testsuite/tests/deSugar/should_compile/ds034.hs | 11 + testsuite/tests/deSugar/should_compile/ds035.hs | 23 + testsuite/tests/deSugar/should_compile/ds036.hs | 47 + testsuite/tests/deSugar/should_compile/ds037.hs | 6 + testsuite/tests/deSugar/should_compile/ds038.hs | 12 + testsuite/tests/deSugar/should_compile/ds039.hs | 7 + testsuite/tests/deSugar/should_compile/ds040.hs | 18 + testsuite/tests/deSugar/should_compile/ds041.hs | 17 + .../tests/deSugar/should_compile/ds041.stderr-ghc | 8 + testsuite/tests/deSugar/should_compile/ds042.hs | 8 + testsuite/tests/deSugar/should_compile/ds043.hs | 11 + .../tests/deSugar/should_compile/ds043.stderr-ghc | 4 + testsuite/tests/deSugar/should_compile/ds044.hs | 10 + testsuite/tests/deSugar/should_compile/ds045.hs | 18 + testsuite/tests/deSugar/should_compile/ds046.hs | 41 + testsuite/tests/deSugar/should_compile/ds047.hs | 9 + testsuite/tests/deSugar/should_compile/ds048.hs | 7 + testsuite/tests/deSugar/should_compile/ds050.hs | 8 + testsuite/tests/deSugar/should_compile/ds051.hs | 33 + .../tests/deSugar/should_compile/ds051.stderr-ghc | 12 + testsuite/tests/deSugar/should_compile/ds052.hs | 7 + testsuite/tests/deSugar/should_compile/ds053.hs | 5 + .../tests/deSugar/should_compile/ds053.stderr-ghc | 2 + testsuite/tests/deSugar/should_compile/ds054.hs | 8 + testsuite/tests/deSugar/should_compile/ds055.hs | 29 + testsuite/tests/deSugar/should_compile/ds056.hs | 14 + .../tests/deSugar/should_compile/ds056.stderr | 4 + testsuite/tests/deSugar/should_compile/ds057.hs | 13 + testsuite/tests/deSugar/should_compile/ds058.hs | 8 + .../tests/deSugar/should_compile/ds058.stderr | 4 + testsuite/tests/deSugar/should_compile/ds059.hs | 33 + testsuite/tests/deSugar/should_compile/ds060.hs | 25 + testsuite/tests/deSugar/should_compile/ds062.hs | 11 + testsuite/tests/deSugar/should_compile/ds063.hs | 11 + testsuite/tests/deSugar/should_run/DsLambdaCase.hs | 14 + .../tests/deSugar/should_run/DsLambdaCase.stdout | 1 + testsuite/tests/deSugar/should_run/DsMultiWayIf.hs | 28 + .../tests/deSugar/should_run/DsMultiWayIf.stdout | 2 + testsuite/tests/deSugar/should_run/Makefile | 3 + testsuite/tests/deSugar/should_run/T246.hs | 25 + testsuite/tests/deSugar/should_run/T246.stdout | 2 + testsuite/tests/deSugar/should_run/T3126.hs | 54 + testsuite/tests/deSugar/should_run/T3126.stdout | 4 + testsuite/tests/deSugar/should_run/T3382.hs | 14 + testsuite/tests/deSugar/should_run/T3382.stdout | 2 + testsuite/tests/deSugar/should_run/T5472.stdout | 1 + testsuite/tests/deSugar/should_run/T5742.hs | 105 + testsuite/tests/deSugar/should_run/T5742.stdout | 1 + testsuite/tests/deSugar/should_run/all.T | 42 + testsuite/tests/deSugar/should_run/dsrun001.hs | 12 + testsuite/tests/deSugar/should_run/dsrun001.stdout | 1 + testsuite/tests/deSugar/should_run/dsrun002.hs | 14 + testsuite/tests/deSugar/should_run/dsrun002.stdout | 1 + testsuite/tests/deSugar/should_run/dsrun003.hs | 13 + testsuite/tests/deSugar/should_run/dsrun003.stdout | 1 + testsuite/tests/deSugar/should_run/dsrun004.hs | 13 + testsuite/tests/deSugar/should_run/dsrun004.stdout | 2 + testsuite/tests/deSugar/should_run/dsrun005.hs | 46 + testsuite/tests/deSugar/should_run/dsrun005.stderr | 2 + .../tests/deSugar/should_run/dsrun005.stderr-hugs | 1 + testsuite/tests/deSugar/should_run/dsrun006.hs | 33 + testsuite/tests/deSugar/should_run/dsrun006.stdout | 1 + testsuite/tests/deSugar/should_run/dsrun007.hs | 5 + testsuite/tests/deSugar/should_run/dsrun007.stderr | 2 + .../tests/deSugar/should_run/dsrun007.stderr-hugs | 1 + testsuite/tests/deSugar/should_run/dsrun008.hs | 2 + testsuite/tests/deSugar/should_run/dsrun008.stderr | 2 + .../tests/deSugar/should_run/dsrun008.stderr-hugs | 1 + testsuite/tests/deSugar/should_run/dsrun009.hs | 16 + testsuite/tests/deSugar/should_run/dsrun009.stdout | 1 + testsuite/tests/deSugar/should_run/dsrun010.hs | 22 + testsuite/tests/deSugar/should_run/dsrun010.stdout | 1 + testsuite/tests/deSugar/should_run/dsrun011.hs | 93 + testsuite/tests/deSugar/should_run/dsrun011.stdout | 1 + testsuite/tests/deSugar/should_run/dsrun012.hs | 12 + testsuite/tests/deSugar/should_run/dsrun012.stdout | 1 + testsuite/tests/deSugar/should_run/dsrun013.hs | 16 + testsuite/tests/deSugar/should_run/dsrun013.stdout | 1 + testsuite/tests/deSugar/should_run/dsrun014.hs | 16 + testsuite/tests/deSugar/should_run/dsrun014.stderr | 2 + testsuite/tests/deSugar/should_run/dsrun014.stdout | 1 + testsuite/tests/deSugar/should_run/dsrun015.hs | 34 + testsuite/tests/deSugar/should_run/dsrun015.stdout | 2 + testsuite/tests/deSugar/should_run/dsrun016.hs | 14 + testsuite/tests/deSugar/should_run/dsrun016.stdout | 1 + testsuite/tests/deSugar/should_run/dsrun017.hs | 13 + testsuite/tests/deSugar/should_run/dsrun017.stdout | 1 + testsuite/tests/deSugar/should_run/dsrun018.hs | 18 + testsuite/tests/deSugar/should_run/dsrun018.stdout | 1 + testsuite/tests/deSugar/should_run/dsrun019.hs | 11 + testsuite/tests/deSugar/should_run/dsrun019.stdout | 1 + testsuite/tests/deSugar/should_run/dsrun020.hs | 14 + testsuite/tests/deSugar/should_run/dsrun020.stdout | 1 + testsuite/tests/deSugar/should_run/dsrun021.hs | 22 + testsuite/tests/deSugar/should_run/dsrun021.stdout | 1 + testsuite/tests/deSugar/should_run/dsrun022.hs | 26 + testsuite/tests/deSugar/should_run/dsrun022.stdout | 2 + testsuite/tests/deSugar/should_run/dsrun023.hs | 41 + testsuite/tests/deSugar/should_run/dsrun023.stdout | 1 + testsuite/tests/deSugar/should_run/mc01.hs | 26 + testsuite/tests/deSugar/should_run/mc01.stdout | 2 + testsuite/tests/deSugar/should_run/mc02.hs | 22 + testsuite/tests/deSugar/should_run/mc02.stdout | 1 + testsuite/tests/deSugar/should_run/mc03.hs | 41 + testsuite/tests/deSugar/should_run/mc03.stdout | 1 + testsuite/tests/deSugar/should_run/mc04.hs | 14 + testsuite/tests/deSugar/should_run/mc04.stdout | 1 + testsuite/tests/deSugar/should_run/mc05.hs | 11 + testsuite/tests/deSugar/should_run/mc05.stdout | 1 + testsuite/tests/deSugar/should_run/mc06.hs | 18 + testsuite/tests/deSugar/should_run/mc06.stdout | 1 + testsuite/tests/deSugar/should_run/mc07.hs | 14 + testsuite/tests/deSugar/should_run/mc07.stdout | 1 + testsuite/tests/deSugar/should_run/mc08.hs | 13 + testsuite/tests/deSugar/should_run/mc08.stdout | 1 + testsuite/tests/deriving/Makefile | 3 + .../deriving/should_compile/AutoDeriveTypeable.hs | 19 + testsuite/tests/deriving/should_compile/Makefile | 9 + testsuite/tests/deriving/should_compile/T1133.hs | 8 + .../tests/deriving/should_compile/T1133.hs-boot | 4 + testsuite/tests/deriving/should_compile/T2378.hs | 10 + testsuite/tests/deriving/should_compile/T2856.hs | 28 + testsuite/tests/deriving/should_compile/T3012.hs | 10 + testsuite/tests/deriving/should_compile/T3057.hs | 8 + testsuite/tests/deriving/should_compile/T3057A.hs | 4 + testsuite/tests/deriving/should_compile/T3965.hs | 18 + testsuite/tests/deriving/should_compile/T4220.hs | 7 + testsuite/tests/deriving/should_compile/T4302.hs | 18 + testsuite/tests/deriving/should_compile/T4325.hs | 7 + .../tests/deriving/should_compile/T4325.stderr | 3 + testsuite/tests/deriving/should_compile/T4816.hs | 10 + testsuite/tests/deriving/should_compile/T4966.hs | 44 + .../tests/deriving/should_compile/T4966.stderr | 8 + testsuite/tests/deriving/should_compile/T6031.hs | 7 + testsuite/tests/deriving/should_compile/T6031a.hs | 3 + testsuite/tests/deriving/should_compile/T7704.hs | 27 + testsuite/tests/deriving/should_compile/T7710.hs | 21 + testsuite/tests/deriving/should_compile/T8138.hs | 48 + testsuite/tests/deriving/should_compile/all.T | 44 + .../tests/deriving/should_compile/deriving-1935.hs | 22 + .../deriving/should_compile/deriving-1935.stderr | 15 + .../should_compile/drv-foldable-traversable1.hs | 33 + .../drv-foldable-traversable1.stderr | 3 + .../tests/deriving/should_compile/drv-functor1.hs | 65 + .../deriving/should_compile/drv-functor1.stderr | 3 + .../tests/deriving/should_compile/drv-functor2.hs | 9 + testsuite/tests/deriving/should_compile/drv001.hs | 21 + testsuite/tests/deriving/should_compile/drv002.hs | 14 + testsuite/tests/deriving/should_compile/drv003.hs | 17 + .../tests/deriving/should_compile/drv003.stderr | 10 + testsuite/tests/deriving/should_compile/drv004.hs | 9 + testsuite/tests/deriving/should_compile/drv005.hs | 6 + testsuite/tests/deriving/should_compile/drv006.hs | 9 + testsuite/tests/deriving/should_compile/drv007.hs | 6 + testsuite/tests/deriving/should_compile/drv008.hs | 7 + testsuite/tests/deriving/should_compile/drv009.hs | 6 + testsuite/tests/deriving/should_compile/drv010.hs | 4 + testsuite/tests/deriving/should_compile/drv011.hs | 6 + testsuite/tests/deriving/should_compile/drv012.hs | 10 + testsuite/tests/deriving/should_compile/drv013.hs | 11 + testsuite/tests/deriving/should_compile/drv014.hs | 11 + testsuite/tests/deriving/should_compile/drv015.hs | 14 + testsuite/tests/deriving/should_compile/drv020.hs | 44 + testsuite/tests/deriving/should_compile/drv021.hs | 16 + .../tests/deriving/should_compile/drv021.stderr | 13 + testsuite/tests/deriving/should_compile/drv022.hs | 10 + testsuite/tests/deriving/should_fail/Makefile | 16 + testsuite/tests/deriving/should_fail/T1133A.hs | 6 + .../tests/deriving/should_fail/T1133A.hs-boot | 4 + testsuite/tests/deriving/should_fail/T1133A.stderr | 7 + testsuite/tests/deriving/should_fail/T1496.hs | 16 + testsuite/tests/deriving/should_fail/T1496.stderr | 11 + testsuite/tests/deriving/should_fail/T2394.hs | 9 + testsuite/tests/deriving/should_fail/T2394.stderr | 6 + testsuite/tests/deriving/should_fail/T2604.hs | 9 + testsuite/tests/deriving/should_fail/T2604.stderr | 10 + .../tests/deriving/should_fail/T2604.stderr-7.0 | 11 + testsuite/tests/deriving/should_fail/T2701.hs | 10 + testsuite/tests/deriving/should_fail/T2701.stderr | 5 + testsuite/tests/deriving/should_fail/T2721.hs | 15 + testsuite/tests/deriving/should_fail/T2721.stderr | 6 + testsuite/tests/deriving/should_fail/T2851.hs | 9 + testsuite/tests/deriving/should_fail/T2851.stderr | 8 + testsuite/tests/deriving/should_fail/T3101.hs | 9 + testsuite/tests/deriving/should_fail/T3101.stderr | 6 + testsuite/tests/deriving/should_fail/T3621.hs | 36 + testsuite/tests/deriving/should_fail/T3621.stderr | 8 + testsuite/tests/deriving/should_fail/T3833.hs | 9 + testsuite/tests/deriving/should_fail/T3833.stderr | 6 + testsuite/tests/deriving/should_fail/T3834.hs | 9 + testsuite/tests/deriving/should_fail/T3834.stderr | 6 + testsuite/tests/deriving/should_fail/T4528.hs | 11 + testsuite/tests/deriving/should_fail/T4528.stderr | 14 + testsuite/tests/deriving/should_fail/T4846.hs | 37 + testsuite/tests/deriving/should_fail/T4846.stderr | 14 + testsuite/tests/deriving/should_fail/T5287.hs | 14 + testsuite/tests/deriving/should_fail/T5287.stderr | 11 + testsuite/tests/deriving/should_fail/T5478.hs | 6 + testsuite/tests/deriving/should_fail/T5478.stderr | 5 + testsuite/tests/deriving/should_fail/T5686.hs | 7 + testsuite/tests/deriving/should_fail/T5686.stderr | 5 + testsuite/tests/deriving/should_fail/T5863a.hs | 12 + testsuite/tests/deriving/should_fail/T5863a.stderr | 10 + testsuite/tests/deriving/should_fail/T5922.hs | 3 + testsuite/tests/deriving/should_fail/T5922.stderr | 4 + testsuite/tests/deriving/should_fail/T7148.hs | 39 + testsuite/tests/deriving/should_fail/T7148.stderr | 24 + testsuite/tests/deriving/should_fail/T7148a.hs | 37 + testsuite/tests/deriving/should_fail/T7148a.stderr | 11 + testsuite/tests/deriving/should_fail/T7800.hs | 7 + testsuite/tests/deriving/should_fail/T7800.stderr | 6 + testsuite/tests/deriving/should_fail/T7800a.hs | 4 + testsuite/tests/deriving/should_fail/T7959.hs | 6 + testsuite/tests/deriving/should_fail/T7959.stderr | 8 + testsuite/tests/deriving/should_fail/all.T | 49 + .../should_fail/drvfail-foldable-traversable1.hs | 21 + .../drvfail-foldable-traversable1.stderr | 26 + .../tests/deriving/should_fail/drvfail-functor1.hs | 6 + .../deriving/should_fail/drvfail-functor1.stderr | 5 + .../tests/deriving/should_fail/drvfail-functor2.hs | 26 + .../deriving/should_fail/drvfail-functor2.stderr | 31 + testsuite/tests/deriving/should_fail/drvfail001.hs | 26 + .../tests/deriving/should_fail/drvfail001.stderr | 8 + testsuite/tests/deriving/should_fail/drvfail002.hs | 20 + .../tests/deriving/should_fail/drvfail002.stderr | 8 + .../deriving/should_fail/drvfail002.stderr-hugs | 1 + testsuite/tests/deriving/should_fail/drvfail003.hs | 16 + .../tests/deriving/should_fail/drvfail003.stderr | 8 + .../deriving/should_fail/drvfail003.stderr-hugs | 1 + testsuite/tests/deriving/should_fail/drvfail004.hs | 9 + .../tests/deriving/should_fail/drvfail004.stderr | 8 + .../deriving/should_fail/drvfail004.stderr-hugs | 4 + testsuite/tests/deriving/should_fail/drvfail005.hs | 4 + .../tests/deriving/should_fail/drvfail005.stderr | 5 + testsuite/tests/deriving/should_fail/drvfail006.hs | 11 + .../tests/deriving/should_fail/drvfail006.stderr | 6 + .../deriving/should_fail/drvfail006.stderr-hugs | 1 + testsuite/tests/deriving/should_fail/drvfail007.hs | 4 + .../tests/deriving/should_fail/drvfail007.stderr | 8 + .../deriving/should_fail/drvfail007.stderr-hugs | 1 + testsuite/tests/deriving/should_fail/drvfail008.hs | 14 + .../tests/deriving/should_fail/drvfail008.stderr | 6 + testsuite/tests/deriving/should_fail/drvfail009.hs | 20 + .../tests/deriving/should_fail/drvfail009.stderr | 23 + .../deriving/should_fail/drvfail009.stderr-hugs | 1 + testsuite/tests/deriving/should_fail/drvfail011.hs | 8 + .../tests/deriving/should_fail/drvfail011.stderr | 10 + testsuite/tests/deriving/should_fail/drvfail012.hs | 8 + .../tests/deriving/should_fail/drvfail012.stderr | 8 + testsuite/tests/deriving/should_fail/drvfail013.hs | 6 + .../tests/deriving/should_fail/drvfail013.stderr | 16 + testsuite/tests/deriving/should_fail/drvfail014.hs | 13 + .../tests/deriving/should_fail/drvfail014.stderr | 9 + testsuite/tests/deriving/should_fail/drvfail015.hs | 13 + .../tests/deriving/should_fail/drvfail015.stderr | 13 + .../deriving/should_fail/drvfail015.stderr-7.0 | 12 + .../tests/deriving/should_fail/drvfail016.hs-boot | 7 + .../tests/deriving/should_fail/drvfail016.stderr | 4 + .../tests/deriving/should_fail/drvfail016.stdout | 1 + testsuite/tests/deriving/should_run/Makefile | 3 + testsuite/tests/deriving/should_run/T2529.hs | 21 + testsuite/tests/deriving/should_run/T2529.stdout | 2 + testsuite/tests/deriving/should_run/T3087.hs | 33 + testsuite/tests/deriving/should_run/T3087.stdout | 4 + testsuite/tests/deriving/should_run/T4136.hs | 9 + testsuite/tests/deriving/should_run/T4136.stdout | 2 + testsuite/tests/deriving/should_run/T4528a.hs | 7 + testsuite/tests/deriving/should_run/T4528a.stdout | 1 + testsuite/tests/deriving/should_run/T5041.hs | 10 + testsuite/tests/deriving/should_run/T5041.stdout | 1 + testsuite/tests/deriving/should_run/T5628.hs | 11 + testsuite/tests/deriving/should_run/T5628.stderr | 1 + testsuite/tests/deriving/should_run/T5712.hs | 14 + testsuite/tests/deriving/should_run/T5712.stdout | 1 + testsuite/tests/deriving/should_run/T7931.hs | 10 + testsuite/tests/deriving/should_run/T7931.stdout | 1 + testsuite/tests/deriving/should_run/T8280.hs | 8 + testsuite/tests/deriving/should_run/T8280.stdout | 1 + testsuite/tests/deriving/should_run/all.T | 39 + .../tests/deriving/should_run/drvrun-foldable1.hs | 15 + .../deriving/should_run/drvrun-foldable1.stdout | 1 + .../tests/deriving/should_run/drvrun-functor1.hs | 49 + .../deriving/should_run/drvrun-functor1.stdout | 8 + testsuite/tests/deriving/should_run/drvrun001.hs | 13 + .../tests/deriving/should_run/drvrun001.stdout | 1 + testsuite/tests/deriving/should_run/drvrun002.hs | 17 + .../tests/deriving/should_run/drvrun002.stdout | 2 + testsuite/tests/deriving/should_run/drvrun003.hs | 30 + .../tests/deriving/should_run/drvrun003.stdout | 3 + testsuite/tests/deriving/should_run/drvrun004.hs | 10 + .../tests/deriving/should_run/drvrun004.stdout | 2 + testsuite/tests/deriving/should_run/drvrun005.hs | 27 + .../tests/deriving/should_run/drvrun005.stdout | 2 + testsuite/tests/deriving/should_run/drvrun006.hs | 49 + .../tests/deriving/should_run/drvrun006.stdout | 6 + testsuite/tests/deriving/should_run/drvrun007.hs | 6 + .../tests/deriving/should_run/drvrun007.stdout | 1 + testsuite/tests/deriving/should_run/drvrun008.hs | 8 + .../tests/deriving/should_run/drvrun008.stdout | 1 + testsuite/tests/deriving/should_run/drvrun009.hs | 20 + .../tests/deriving/should_run/drvrun009.stdout | 2 + testsuite/tests/deriving/should_run/drvrun010.hs | 12 + .../tests/deriving/should_run/drvrun010.stdout | 1 + testsuite/tests/deriving/should_run/drvrun011.hs | 16 + .../tests/deriving/should_run/drvrun011.stdout | 2 + testsuite/tests/deriving/should_run/drvrun012.hs | 11 + .../tests/deriving/should_run/drvrun012.stdout | 1 + testsuite/tests/deriving/should_run/drvrun013.hs | 19 + .../tests/deriving/should_run/drvrun013.stdout | 1 + testsuite/tests/deriving/should_run/drvrun014.hs | 19 + .../tests/deriving/should_run/drvrun014.stdout | 1 + testsuite/tests/deriving/should_run/drvrun015.hs | 8 + .../tests/deriving/should_run/drvrun015.stdout | 1 + testsuite/tests/deriving/should_run/drvrun016.hs | 18 + .../tests/deriving/should_run/drvrun016.stdout | 1 + testsuite/tests/deriving/should_run/drvrun017.hs | 10 + .../tests/deriving/should_run/drvrun017.stdout | 1 + testsuite/tests/deriving/should_run/drvrun018.hs | 9 + .../tests/deriving/should_run/drvrun018.stdout | 2 + testsuite/tests/deriving/should_run/drvrun019.hs | 15 + .../tests/deriving/should_run/drvrun019.stdout | 1 + testsuite/tests/deriving/should_run/drvrun020.hs | 46 + .../tests/deriving/should_run/drvrun020.stdout | 1 + testsuite/tests/deriving/should_run/drvrun021.hs | 20 + .../tests/deriving/should_run/drvrun021.stdout | 5 + testsuite/tests/deriving/should_run/drvrun022.hs | 12 + .../tests/deriving/should_run/drvrun022.stdout | 1 + testsuite/tests/dph/Makefile | 3 + testsuite/tests/dph/classes/DefsVect.hs | 53 + testsuite/tests/dph/classes/Main.hs | 15 + testsuite/tests/dph/classes/Makefile | 3 + .../tests/dph/classes/dph-classes-copy-fast.stdout | 1 + .../tests/dph/classes/dph-classes-vseg-fast.stdout | 1 + testsuite/tests/dph/classes/dph-classes.T | 10 + testsuite/tests/dph/diophantine/DiophantineVect.hs | 39 + testsuite/tests/dph/diophantine/Main.hs | 42 + testsuite/tests/dph/diophantine/Makefile | 3 + .../diophantine/dph-diophantine-copy-fast.stdout | 3 + .../diophantine/dph-diophantine-copy-opt.stdout | 3 + testsuite/tests/dph/diophantine/dph-diophantine.T | 11 + testsuite/tests/dph/dotp/DotPVect.hs | 15 + testsuite/tests/dph/dotp/Main.hs | 54 + testsuite/tests/dph/dotp/Makefile | 3 + testsuite/tests/dph/dotp/dph-dotp-copy-fast.stdout | 2 + testsuite/tests/dph/dotp/dph-dotp-copy-opt.stdout | 2 + testsuite/tests/dph/dotp/dph-dotp-vseg-fast.stdout | 2 + testsuite/tests/dph/dotp/dph-dotp-vseg-opt.stdout | 2 + testsuite/tests/dph/dotp/dph-dotp.T | 20 + testsuite/tests/dph/enumfromto/EnumFromToP.hs | 24 + testsuite/tests/dph/enumfromto/Makefile | 3 + testsuite/tests/dph/enumfromto/dph-enumfromto.T | 9 + testsuite/tests/dph/modules/ExportList.hs | 33 + testsuite/tests/dph/modules/Makefile | 3 + .../dph/modules/dph-ExportList-vseg-fast.stderr | 6 + testsuite/tests/dph/modules/dph-modules.T | 8 + testsuite/tests/dph/nbody/Body.hs | 85 + testsuite/tests/dph/nbody/Config.hs | 50 + testsuite/tests/dph/nbody/Dump.hs | 46 + testsuite/tests/dph/nbody/Generate.hs | 98 + testsuite/tests/dph/nbody/Main.hs | 103 + testsuite/tests/dph/nbody/Makefile | 3 + testsuite/tests/dph/nbody/Randomish.hs | 82 + testsuite/tests/dph/nbody/Solver.hs | 156 + testsuite/tests/dph/nbody/Types.hs | 52 + testsuite/tests/dph/nbody/Util.hs | 18 + testsuite/tests/dph/nbody/World.hs | 47 + .../tests/dph/nbody/dph-nbody-copy-fast.stdout | 100 + .../tests/dph/nbody/dph-nbody-copy-opt.stdout | 100 + .../tests/dph/nbody/dph-nbody-vseg-fast.stdout | 100 + .../tests/dph/nbody/dph-nbody-vseg-opt.stdout | 100 + testsuite/tests/dph/nbody/dph-nbody.T | 19 + testsuite/tests/dph/primespj/Main.hs | 30 + testsuite/tests/dph/primespj/Makefile | 3 + testsuite/tests/dph/primespj/PrimesVect.hs | 25 + .../dph/primespj/dph-primespj-copy-fast.stdout | 3 + .../dph/primespj/dph-primespj-copy-opt.stdout | 3 + .../dph/primespj/dph-primespj-vseg-fast.stdout | 3 + .../dph/primespj/dph-primespj-vseg-opt.stdout | 3 + testsuite/tests/dph/primespj/dph-primespj.T | 11 + testsuite/tests/dph/quickhull/Main.hs | 43 + testsuite/tests/dph/quickhull/Makefile | 3 + testsuite/tests/dph/quickhull/QuickHullVect.hs | 41 + testsuite/tests/dph/quickhull/SVG.hs | 34 + testsuite/tests/dph/quickhull/TestData.hs | 92 + testsuite/tests/dph/quickhull/Types.hs | 33 + .../dph/quickhull/dph-quickhull-copy-fast.stdout | 1019 ++ .../dph/quickhull/dph-quickhull-copy-opt.stdout | 1019 ++ .../dph/quickhull/dph-quickhull-vseg-fast.stdout | 1019 ++ .../dph/quickhull/dph-quickhull-vseg-opt.stdout | 1019 ++ testsuite/tests/dph/quickhull/dph-quickhull.T | 20 + testsuite/tests/dph/smvm/Main.hs | 60 + testsuite/tests/dph/smvm/Makefile | 3 + testsuite/tests/dph/smvm/SMVMVect.hs | 17 + testsuite/tests/dph/smvm/dph-smvm-copy.stdout | 1 + testsuite/tests/dph/smvm/dph-smvm-vseg.stdout | 1 + testsuite/tests/dph/smvm/dph-smvm.T | 41 + testsuite/tests/dph/smvm/result-i386.txt | 101 + testsuite/tests/dph/smvm/result-sparc.txt | 101 + testsuite/tests/dph/smvm/result-x86_64.txt | 101 + testsuite/tests/dph/smvm/test-i386.dat | Bin 0 -> 22384 bytes testsuite/tests/dph/smvm/test-sparc.dat | Bin 0 -> 11632 bytes testsuite/tests/dph/smvm/test-x86_64.dat | Bin 0 -> 16416 bytes testsuite/tests/dph/sumnats/Main.hs | 21 + testsuite/tests/dph/sumnats/Makefile | 3 + testsuite/tests/dph/sumnats/SumNatsVect.hs | 14 + .../tests/dph/sumnats/dph-sumnats-copy.stdout | 3 + .../tests/dph/sumnats/dph-sumnats-vseg.stdout | 3 + testsuite/tests/dph/sumnats/dph-sumnats.T | 20 + testsuite/tests/dph/words/Main.hs | 37 + testsuite/tests/dph/words/Makefile | 3 + testsuite/tests/dph/words/WordsVect.hs | 125 + .../tests/dph/words/dph-words-copy-fast.stdout | 3 + .../tests/dph/words/dph-words-copy-opt.stdout | 3 + .../tests/dph/words/dph-words-vseg-fast.stdout | 3 + .../tests/dph/words/dph-words-vseg-opt.stdout | 3 + testsuite/tests/dph/words/dph-words.T | 20 + testsuite/tests/driver/A011.hs | 1 + testsuite/tests/driver/A012.hs | 1 + testsuite/tests/driver/A013.hs | 1 + testsuite/tests/driver/A014.hs | 1 + testsuite/tests/driver/A015.hs | 1 + testsuite/tests/driver/A031.hs | 1 + testsuite/tests/driver/A032.hs | 1 + testsuite/tests/driver/A033.hs | 1 + testsuite/tests/driver/A061a.hs | 1 + testsuite/tests/driver/A061b.hs | 1 + testsuite/tests/driver/A063.hs | 1 + testsuite/tests/driver/A064.hs | 1 + testsuite/tests/driver/A065.hs | 1 + testsuite/tests/driver/A066.hs | 1 + testsuite/tests/driver/A067.hs | 1 + testsuite/tests/driver/A070.hs | 1 + testsuite/tests/driver/A071.hs | 1 + testsuite/tests/driver/A200.hs | 1 + testsuite/tests/driver/B021/C.hs | 1 + testsuite/tests/driver/B022/C.hs | 1 + testsuite/tests/driver/B023/C.hs | 1 + testsuite/tests/driver/B024/C.hs | 1 + testsuite/tests/driver/B025/C.hs | 1 + testsuite/tests/driver/B027/F.hs | 5 + testsuite/tests/driver/B028/F.hs | 5 + testsuite/tests/driver/B041/C.hs | 1 + testsuite/tests/driver/B042/C.hs | 1 + testsuite/tests/driver/B043/C.hs | 1 + testsuite/tests/driver/B044/F.hs | 5 + testsuite/tests/driver/B045/F.hs | 5 + testsuite/tests/driver/B200/C.hs | 1 + testsuite/tests/driver/D063.hs | 2 + testsuite/tests/driver/D200.hs | 2 + testsuite/tests/driver/F016.hs | 5 + testsuite/tests/driver/F017.hs | 5 + testsuite/tests/driver/F018.hs | 5 + testsuite/tests/driver/F018a.hs | 5 + testsuite/tests/driver/F019.hs | 5 + testsuite/tests/driver/F034.hs | 5 + testsuite/tests/driver/F035.hs | 5 + testsuite/tests/driver/Makefile | 556 + testsuite/tests/driver/Shared001.hs | 9 + testsuite/tests/driver/Static001.hs | 5 + testsuite/tests/driver/T1372/Makefile | 41 + testsuite/tests/driver/T1372/T1372.stderr | 2 + testsuite/tests/driver/T1372/all.T | 5 + testsuite/tests/driver/T1372/p1/A1.hs | 2 + testsuite/tests/driver/T1372/p1/A2.hs | 2 + testsuite/tests/driver/T1372/p1/Setup.hs | 6 + testsuite/tests/driver/T1372/p1/p1.cabal | 4 + testsuite/tests/driver/T1372/p2/Main.hs | 7 + testsuite/tests/driver/T1372/p2/Setup.hs | 6 + testsuite/tests/driver/T1372/p2/p2.cabal | 5 + testsuite/tests/driver/T1959/B.hs | 6 + testsuite/tests/driver/T1959/C.hs | 5 + testsuite/tests/driver/T1959/D.hs | 7 + testsuite/tests/driver/T1959/E1.hs | 4 + testsuite/tests/driver/T1959/E2.hs | 4 + testsuite/tests/driver/T1959/Makefile | 29 + testsuite/tests/driver/T1959/T1959.stdout | 2 + testsuite/tests/driver/T1959/test.T | 5 + testsuite/tests/driver/T2464.hs | 12 + testsuite/tests/driver/T2464.stderr | 3 + testsuite/tests/driver/T2499.hs | 2 + testsuite/tests/driver/T2499.stderr | 4 + testsuite/tests/driver/T2507.hs | 5 + testsuite/tests/driver/T2507.stderr | 5 + testsuite/tests/driver/T2566.stderr | 3 + testsuite/tests/driver/T3007/A/A.cabal | 7 + testsuite/tests/driver/T3007/A/A.hs | 7 + testsuite/tests/driver/T3007/A/Internal.hs | 7 + .../tests/driver/T3007/A}/Setup.hs | 0 testsuite/tests/driver/T3007/B/B.cabal | 8 + testsuite/tests/driver/T3007/B/B.hs | 7 + testsuite/tests/driver/T3007/B/Internal.hs | 3 + testsuite/tests/driver/T3007/B/Internal.hs-boot | 1 + .../tests/driver/T3007/B}/Setup.hs | 0 testsuite/tests/driver/T3007/Makefile | 21 + testsuite/tests/driver/T3007/all.T | 5 + testsuite/tests/driver/T3364.stderr | 2 + testsuite/tests/driver/T3389.hs | 12 + testsuite/tests/driver/T3389.stdout | 1 + testsuite/tests/driver/T3674.hs | 5 + testsuite/tests/driver/T3674_pre.hs | 5 + testsuite/tests/driver/T437/Makefile | 27 + testsuite/tests/driver/T437/T437.stdout | 10 + testsuite/tests/driver/T437/Test.hs | 6 + testsuite/tests/driver/T437/Test2.hs | 5 + testsuite/tests/driver/T437/all.T | 7 + testsuite/tests/driver/T4437.hs | 51 + testsuite/tests/driver/T5147/A.hs | 7 + testsuite/tests/driver/T5147/B1.hs | 8 + testsuite/tests/driver/T5147/B2.hs | 9 + testsuite/tests/driver/T5147/Makefile | 25 + testsuite/tests/driver/T5147/T5147.stderr | 5 + testsuite/tests/driver/T5147/all.T | 5 + testsuite/tests/driver/T5198.hs | 6 + testsuite/tests/driver/T5313.hs | 18 + testsuite/tests/driver/T5584_in/A.hs-boot | 3 + testsuite/tests/driver/T6037.hs | 5 + testsuite/tests/driver/T6037.stderr | 5 + testsuite/tests/driver/T703.hs | 1 + testsuite/tests/driver/T706.stdout | 1 + testsuite/tests/driver/T7060.hs | 8 + testsuite/tests/driver/T706a.hs | 7 + testsuite/tests/driver/T706b.hs | 3 + testsuite/tests/driver/T7130.hs | 1 + testsuite/tests/driver/T7130.stderr | 6 + testsuite/tests/driver/T7373/D.hs | 9 + testsuite/tests/driver/T7373/Makefile | 16 + testsuite/tests/driver/T7373/all.T | 8 + testsuite/tests/driver/T7373/pkg/A.hs | 4 + testsuite/tests/driver/T7373/pkg/B.hs | 12 + testsuite/tests/driver/T7373/pkg/B.hs-boot | 6 + testsuite/tests/driver/T7373/pkg/C.hs | 9 + .../tests/driver/T7373/pkg}/Setup.hs | 0 testsuite/tests/driver/T7373/pkg/pkg.cabal | 6 + testsuite/tests/driver/T7563.hs | 2 + testsuite/tests/driver/T7563.stderr | 2 + testsuite/tests/driver/T7835/Makefile | 9 + testsuite/tests/driver/T7835/T7835.stdout | 1 + testsuite/tests/driver/T7835/Test.hs | 4 + testsuite/tests/driver/T7835/TestPrim.hs | 17 + testsuite/tests/driver/T7835/all.T | 7 + testsuite/tests/driver/T7835/test-prims.cmm | 10 + testsuite/tests/driver/T8101.hs | 8 + testsuite/tests/driver/T8101.stderr | 7 + testsuite/tests/driver/T8184/A.hs | 5 + testsuite/tests/driver/T8184/B.hs | 8 + testsuite/tests/driver/T8184/B.hs-boot | 3 + testsuite/tests/driver/T8184/C.hs | 7 + testsuite/tests/driver/T8184/Makefile | 11 + testsuite/tests/driver/T8184/all.T | 2 + testsuite/tests/driver/T8526/A.hs | 4 + testsuite/tests/driver/T8526/T8526.T | 1 + testsuite/tests/driver/T8526/T8526.script | 10 + testsuite/tests/driver/T8526/T8526.stdout | 6 + testsuite/tests/driver/all.T | 392 + testsuite/tests/driver/bug1677/Bar.hs | 2 + testsuite/tests/driver/bug1677/Foo.hs | 1 + testsuite/tests/driver/bug1677/Makefile | 7 + testsuite/tests/driver/bug1677/all.T | 1 + testsuite/tests/driver/bug1677/bug1677.stderr | 5 + testsuite/tests/driver/conflicting_flags/Makefile | 7 + .../conflicting_flags/conflicting_flags.stdout | 1 + testsuite/tests/driver/conflicting_flags/test.T | 3 + testsuite/tests/driver/d026/P/Q.hs | 1 + testsuite/tests/driver/d051_1/P/Q.hs | 1 + testsuite/tests/driver/d051_2/R/S.hs | 2 + testsuite/tests/driver/d052_1/P/Q.hs | 1 + testsuite/tests/driver/d052_2/R/S.hs | 2 + testsuite/tests/driver/d053_1/P/Q.hs | 1 + testsuite/tests/driver/d053_2/R/S.hs | 2 + testsuite/tests/driver/driver062a.stdout | 1 + testsuite/tests/driver/driver062b.stdout | 1 + testsuite/tests/driver/driver062c.stdout | 1 + testsuite/tests/driver/driver062d.stdout | 1 + testsuite/tests/driver/driver062e.stdout | 1 + testsuite/tests/driver/driver063.stderr | 4 + testsuite/tests/driver/dynHelloWorld.hs | 5 + testsuite/tests/driver/dynHelloWorld.stdout | 1 + testsuite/tests/driver/dynamicToo/A003.hs | 6 + testsuite/tests/driver/dynamicToo/Makefile | 15 + testsuite/tests/driver/dynamicToo/all.T | 9 + .../tests/driver/dynamicToo/dynamicToo001/A.hs | 6 + .../tests/driver/dynamicToo/dynamicToo001/B.hs | 6 + .../tests/driver/dynamicToo/dynamicToo001/B1.hs | 6 + .../tests/driver/dynamicToo/dynamicToo001/B2.hs | 6 + .../tests/driver/dynamicToo/dynamicToo001/C.hs | 9 + .../tests/driver/dynamicToo/dynamicToo001/Makefile | 23 + .../dynamicToo/dynamicToo001/dynamicToo001.stdout | 4 + .../tests/driver/dynamicToo/dynamicToo001/test.T | 13 + .../tests/driver/dynamicToo/dynamicToo002/A.hs | 6 + .../tests/driver/dynamicToo/dynamicToo002/B.hs | 6 + .../tests/driver/dynamicToo/dynamicToo002/C.hs | 9 + .../tests/driver/dynamicToo/dynamicToo002/Makefile | 23 + .../tests/driver/dynamicToo/dynamicToo002/test.T | 11 + .../tests/driver/dynamicToo/dynamicToo004/Makefile | 55 + .../driver/dynamicToo/dynamicToo004}/Setup.hs | 0 .../driver/dynamicToo/dynamicToo004/pkg1/A.hs | 5 + .../dynamicToo/dynamicToo004/pkg1/pkg1.cabal | 7 + .../driver/dynamicToo/dynamicToo004/pkg1dyn/A.hs | 5 + .../dynamicToo/dynamicToo004/pkg1dyn/pkg1.cabal | 7 + .../driver/dynamicToo/dynamicToo004/pkg2/B.hs | 5 + .../driver/dynamicToo/dynamicToo004/pkg2/C.hs | 9 + .../dynamicToo/dynamicToo004/pkg2/pkg2.cabal | 7 + .../tests/driver/dynamicToo/dynamicToo004/prog.hs | 7 + .../tests/driver/dynamicToo/dynamicToo004/test.T | 9 + testsuite/tests/driver/dynamic_flags_001/A.hs | 13 + testsuite/tests/driver/dynamic_flags_001/B.hs | 13 + testsuite/tests/driver/dynamic_flags_001/C.hs | 17 + testsuite/tests/driver/dynamic_flags_001/Makefile | 14 + testsuite/tests/driver/dynamic_flags_001/all.T | 6 + .../tests/driver/dynamic_flags_002/A_First.hs | 5 + testsuite/tests/driver/dynamic_flags_002/A_Main.hs | 6 + .../tests/driver/dynamic_flags_002/A_Second.hs | 6 + .../tests/driver/dynamic_flags_002/B_First.hs | 6 + testsuite/tests/driver/dynamic_flags_002/B_Main.hs | 6 + .../tests/driver/dynamic_flags_002/B_Second.hs | 5 + .../tests/driver/dynamic_flags_002/C_Child.hs | 5 + testsuite/tests/driver/dynamic_flags_002/C_Main.hs | 8 + .../tests/driver/dynamic_flags_002/D_Child.hs | 6 + testsuite/tests/driver/dynamic_flags_002/D_Main.hs | 7 + testsuite/tests/driver/dynamic_flags_002/Makefile | 4 + .../tests/driver/dynamic_flags_002/ManyFirst.hs | 6 + .../tests/driver/dynamic_flags_002/ManySecond.hs | 5 + .../tests/driver/dynamic_flags_002/ManyThird.hs | 6 + testsuite/tests/driver/dynamic_flags_002/all.T | 12 + testsuite/tests/driver/mode001.stdout | 8 + testsuite/tests/driver/objc/Makefile | 4 + testsuite/tests/driver/objc/all.T | 19 + testsuite/tests/driver/objc/objc-hi.m | 35 + testsuite/tests/driver/objc/objc-hi.stdout | 1 + testsuite/tests/driver/objc/objcpp-hi.mm | 35 + testsuite/tests/driver/objc/objcpp-hi.stdout | 1 + testsuite/tests/driver/overlap/List.hs | 1 + testsuite/tests/driver/overlap/Overlap.hs | 2 + testsuite/tests/driver/pragma001.hs | 29 + testsuite/tests/driver/pragma002.hs | 10 + testsuite/tests/driver/recomp001/A.hs | 4 + testsuite/tests/driver/recomp001/B1.hs | 3 + testsuite/tests/driver/recomp001/B2.hs | 3 + testsuite/tests/driver/recomp001/C.hs | 6 + testsuite/tests/driver/recomp001/Makefile | 23 + testsuite/tests/driver/recomp001/all.T | 6 + testsuite/tests/driver/recomp001/recomp001.stderr | 2 + testsuite/tests/driver/recomp002/Makefile | 20 + testsuite/tests/driver/recomp002/Q.hs | 5 + testsuite/tests/driver/recomp002/W.hs | 5 + testsuite/tests/driver/recomp002/W.hs-boot | 3 + testsuite/tests/driver/recomp002/all.T | 6 + testsuite/tests/driver/recomp002/recomp002.stderr | 1 + testsuite/tests/driver/recomp002/recomp002.stdout | 3 + testsuite/tests/driver/recomp003/A.hs | 3 + testsuite/tests/driver/recomp003/Makefile | 22 + testsuite/tests/driver/recomp003/all.T | 6 + testsuite/tests/driver/recomp004/Main.hs | 10 + testsuite/tests/driver/recomp004/Makefile | 29 + testsuite/tests/driver/recomp004/all.T | 5 + testsuite/tests/driver/recomp004/c.h | 5 + testsuite/tests/driver/recomp004/c1.c | 6 + testsuite/tests/driver/recomp004/c2.c | 6 + testsuite/tests/driver/recomp004/recomp004.stdout | 2 + testsuite/tests/driver/recomp005/A.hs | 4 + testsuite/tests/driver/recomp005/B.hs | 5 + testsuite/tests/driver/recomp005/C1.hs | 5 + testsuite/tests/driver/recomp005/C2.hs | 7 + testsuite/tests/driver/recomp005/D.hs | 3 + testsuite/tests/driver/recomp005/E.hs | 7 + testsuite/tests/driver/recomp005/Makefile | 20 + testsuite/tests/driver/recomp005/all.T | 5 + testsuite/tests/driver/recomp005/recomp005.stderr | 4 + testsuite/tests/driver/recomp005/recomp005.stdout | 8 + testsuite/tests/driver/recomp006/A.hs | 9 + testsuite/tests/driver/recomp006/B1.hs | 8 + testsuite/tests/driver/recomp006/B2.hs | 8 + testsuite/tests/driver/recomp006/Makefile | 20 + testsuite/tests/driver/recomp006/all.T | 4 + testsuite/tests/driver/recomp006/recomp006.stderr | 6 + testsuite/tests/driver/recomp006/recomp006.stdout | 2 + testsuite/tests/driver/recomp007/Makefile | 28 + .../tests/driver/recomp007}/Setup.hs | 0 testsuite/tests/driver/recomp007/a1/A.hs | 3 + testsuite/tests/driver/recomp007/a1/a.cabal | 7 + testsuite/tests/driver/recomp007/a2/A.hs | 3 + testsuite/tests/driver/recomp007/a2/a.cabal | 7 + testsuite/tests/driver/recomp007/all.T | 9 + testsuite/tests/driver/recomp007/b/B.hs | 5 + testsuite/tests/driver/recomp007/b/Main.hs | 5 + testsuite/tests/driver/recomp007/b/b.cabal | 10 + testsuite/tests/driver/recomp007/recomp007.stdout | 5 + testsuite/tests/driver/recomp008/A1.hs | 8 + testsuite/tests/driver/recomp008/A2.hs | 8 + testsuite/tests/driver/recomp008/B.hs | 4 + testsuite/tests/driver/recomp008/Main.hs | 5 + testsuite/tests/driver/recomp008/Makefile | 32 + testsuite/tests/driver/recomp008/all.T | 7 + testsuite/tests/driver/recomp008/recomp008.stdout | 2 + testsuite/tests/driver/recomp009/Main.hs | 4 + testsuite/tests/driver/recomp009/Makefile | 26 + testsuite/tests/driver/recomp009/Sub1.hs | 3 + testsuite/tests/driver/recomp009/Sub2.hs | 3 + testsuite/tests/driver/recomp009/all.T | 7 + testsuite/tests/driver/recomp009/recomp009.stdout | 2 + testsuite/tests/driver/recomp010/Main.hs | 7 + testsuite/tests/driver/recomp010/Makefile | 26 + testsuite/tests/driver/recomp010/X1.hs | 10 + testsuite/tests/driver/recomp010/X2.hs | 10 + testsuite/tests/driver/recomp010/all.T | 7 + testsuite/tests/driver/recomp010/recomp010.stdout | 2 + testsuite/tests/driver/recomp011/Main.hs | 5 + testsuite/tests/driver/recomp011/Makefile | 32 + testsuite/tests/driver/recomp011/all.T | 7 + testsuite/tests/driver/recomp011/recomp011.stdout | 10 + testsuite/tests/driver/recomp012/Makefile | 30 + testsuite/tests/driver/recomp012/all.T | 7 + testsuite/tests/driver/recomp012/recomp012.stdout | 2 + testsuite/tests/driver/recomp013/A.hs | 1 + testsuite/tests/driver/recomp013/B.hs | 1 + testsuite/tests/driver/recomp013/C.hs | 1 + testsuite/tests/driver/recomp013/Makefile | 25 + testsuite/tests/driver/recomp013/all.T | 7 + testsuite/tests/driver/recomp013/recomp013.stdout | 7 + testsuite/tests/driver/rtsOpts.hs | 3 + testsuite/tests/driver/rtsopts001.stdout | 3 + testsuite/tests/driver/rtsopts002.hs | 1 + testsuite/tests/driver/rtsopts002.stderr | 2 + testsuite/tests/driver/rtsopts002.stdout | 2 + testsuite/tests/driver/shared001.stderr | 1 + testsuite/tests/driver/spacesInArgs.hs | 10 + testsuite/tests/driver/spacesInArgs.stdout | 2 + testsuite/tests/driver/werror.hs | 13 + testsuite/tests/driver/werror.stderr | 28 + testsuite/tests/driver/withRtsOpts.hs | 3 + testsuite/tests/driver/withRtsOpts.stdout | 1 + testsuite/tests/dynlibs/Makefile | 54 + testsuite/tests/dynlibs/T3807-export.c | 21 + testsuite/tests/dynlibs/T3807-load.c | 39 + testsuite/tests/dynlibs/T3807.stdout | 1 + testsuite/tests/dynlibs/T3807Export.hs | 11 + testsuite/tests/dynlibs/T4464.stderr | 6 + testsuite/tests/dynlibs/T4464.stdout | 4 + testsuite/tests/dynlibs/T4464B.c | 25 + testsuite/tests/dynlibs/T4464C.c | 15 + testsuite/tests/dynlibs/T4464H.hs | 7 + testsuite/tests/dynlibs/T5373.stdout | 3 + testsuite/tests/dynlibs/T5373A.hs | 4 + testsuite/tests/dynlibs/T5373B.hs | 4 + testsuite/tests/dynlibs/T5373C.hs | 4 + testsuite/tests/dynlibs/T5373D.hs | 4 + testsuite/tests/dynlibs/all.T | 32 + testsuite/tests/esc/F123.hs | 28 + testsuite/tests/esc/Makefile | 3 + testsuite/tests/esc/Sum.hs | 22 + testsuite/tests/esc/TestData.hs | 37 + testsuite/tests/esc/TestDataCon.hs | 25 + testsuite/tests/esc/TestImport.hs | 27 + testsuite/tests/esc/TestList.hs | 24 + testsuite/tests/esc/all.T | 5 + testsuite/tests/esc/synonym.hs | 10 + testsuite/tests/ext-core/Makefile | 29 + testsuite/tests/ext-core/T7239.hs | 8 + testsuite/tests/ext-core/all.T | 3 + testsuite/tests/eyeball/IOList.lhs | 64 + testsuite/tests/eyeball/Makefile | 3 + testsuite/tests/eyeball/README | 5 + testsuite/tests/eyeball/T3116.hs | 34 + testsuite/tests/eyeball/dead1.hs | 42 + .../tests/eyeball/dmd-on-polymorphic-floatouts.hs | 23 + testsuite/tests/eyeball/inline1.hs | 37 + testsuite/tests/eyeball/inline2.hs | 40 + testsuite/tests/eyeball/inline3.hs | 35 + testsuite/tests/eyeball/inline4.hs | 40 + testsuite/tests/eyeball/record1.hs | 17 + testsuite/tests/eyeball/spec-constr1.hs | 36 + testsuite/tests/eyeball/state-hack.hs | 19 + testsuite/tests/ffi/Makefile | 3 + testsuite/tests/ffi/should_compile/Makefile | 3 + testsuite/tests/ffi/should_compile/T1357.hs | 5 + testsuite/tests/ffi/should_compile/T1357.stderr | 3 + testsuite/tests/ffi/should_compile/T3624.hs | 4 + testsuite/tests/ffi/should_compile/T3742.hs | 12 + testsuite/tests/ffi/should_compile/all.T | 40 + testsuite/tests/ffi/should_compile/cc001.hs | 21 + testsuite/tests/ffi/should_compile/cc004.hs | 68 + testsuite/tests/ffi/should_compile/cc005.hs | 108 + testsuite/tests/ffi/should_compile/cc007.hs | 4 + testsuite/tests/ffi/should_compile/cc008.hs | 8 + testsuite/tests/ffi/should_compile/cc009.hs | 8 + testsuite/tests/ffi/should_compile/cc009_inc.h | 1 + testsuite/tests/ffi/should_compile/cc010.hs | 5 + testsuite/tests/ffi/should_compile/cc011.hs | 9 + .../tests/ffi/should_compile/cc011.stderr-hugs | 2 + testsuite/tests/ffi/should_compile/cc012.hs | 6 + testsuite/tests/ffi/should_compile/cc013.hs | 14 + testsuite/tests/ffi/should_compile/cc014.hs | 4 + testsuite/tests/ffi/should_compile/cc015.hs | 46 + testsuite/tests/ffi/should_compile/cc016.hs | 15 + testsuite/tests/ffi/should_compile/ffi-deriv1.hs | 25 + testsuite/tests/ffi/should_fail/Ccfail004A.hs | 7 + testsuite/tests/ffi/should_fail/Makefile | 3 + testsuite/tests/ffi/should_fail/T3066.hs | 7 + testsuite/tests/ffi/should_fail/T3066.stderr | 6 + testsuite/tests/ffi/should_fail/T5664.hs | 25 + testsuite/tests/ffi/should_fail/T5664.stderr | 13 + testsuite/tests/ffi/should_fail/T7506.hs | 6 + testsuite/tests/ffi/should_fail/T7506.stderr | 7 + testsuite/tests/ffi/should_fail/all.T | 18 + .../tests/ffi/should_fail/capi_value_function.hs | 9 + .../ffi/should_fail/capi_value_function.stderr | 6 + testsuite/tests/ffi/should_fail/ccall_value.hs | 12 + testsuite/tests/ffi/should_fail/ccall_value.stderr | 2 + testsuite/tests/ffi/should_fail/ccall_value_c.h | 3 + testsuite/tests/ffi/should_fail/ccfail001.hs | 10 + testsuite/tests/ffi/should_fail/ccfail001.stderr | 6 + testsuite/tests/ffi/should_fail/ccfail002.hs | 11 + testsuite/tests/ffi/should_fail/ccfail002.stderr | 7 + testsuite/tests/ffi/should_fail/ccfail003.hs | 11 + testsuite/tests/ffi/should_fail/ccfail003.stderr | 10 + testsuite/tests/ffi/should_fail/ccfail004.hs | 16 + testsuite/tests/ffi/should_fail/ccfail004.stderr | 26 + testsuite/tests/ffi/should_fail/ccfail005.hs | 16 + testsuite/tests/ffi/should_fail/ccfail005.stderr | 10 + testsuite/tests/ffi/should_run/Capi_Ctype_001.hsc | 46 + .../tests/ffi/should_run/Capi_Ctype_001.stdout | 2 + testsuite/tests/ffi/should_run/Capi_Ctype_002.hs | 19 + .../tests/ffi/should_run/Capi_Ctype_002.stdout | 1 + .../tests/ffi/should_run/Capi_Ctype_A_001.hsc | 27 + .../tests/ffi/should_run/Capi_Ctype_A_002.hsc | 28 + testsuite/tests/ffi/should_run/Makefile | 40 + testsuite/tests/ffi/should_run/T1288.hs | 6 + testsuite/tests/ffi/should_run/T1288.stdout | 1 + testsuite/tests/ffi/should_run/T1288_c.c | 6 + testsuite/tests/ffi/should_run/T1288_ghci.hs | 6 + testsuite/tests/ffi/should_run/T1288_ghci.stdout | 1 + testsuite/tests/ffi/should_run/T1288_ghci_c.c | 6 + testsuite/tests/ffi/should_run/T1679.hs | 19 + testsuite/tests/ffi/should_run/T1679.stdout | 2 + testsuite/tests/ffi/should_run/T2276.hs | 7 + testsuite/tests/ffi/should_run/T2276.stdout | 1 + testsuite/tests/ffi/should_run/T2276_c.c | 6 + testsuite/tests/ffi/should_run/T2276_ghci.hs | 7 + testsuite/tests/ffi/should_run/T2276_ghci.stdout | 1 + testsuite/tests/ffi/should_run/T2276_ghci_c.c | 6 + testsuite/tests/ffi/should_run/T2469.hs | 15 + testsuite/tests/ffi/should_run/T2594.hs | 38 + testsuite/tests/ffi/should_run/T2594.stdout | 4 + testsuite/tests/ffi/should_run/T2594_c.c | 7 + testsuite/tests/ffi/should_run/T2594_c.h | 15 + testsuite/tests/ffi/should_run/T2917a.hs | 42 + testsuite/tests/ffi/should_run/T4012.hs | 10 + testsuite/tests/ffi/should_run/T4012.stdout | 3 + testsuite/tests/ffi/should_run/T4012_A.hs | 14 + testsuite/tests/ffi/should_run/T4012_B.hs | 11 + testsuite/tests/ffi/should_run/T4038.hs | 33 + testsuite/tests/ffi/should_run/T4038.stdout | 1 + testsuite/tests/ffi/should_run/T4221.hs | 42 + testsuite/tests/ffi/should_run/T4221.stdout | 1003 ++ testsuite/tests/ffi/should_run/T4221_c.c | 26 + testsuite/tests/ffi/should_run/T5402.hs | 4 + testsuite/tests/ffi/should_run/T5402_main.c | 13 + testsuite/tests/ffi/should_run/T5594.hs | 6 + testsuite/tests/ffi/should_run/T5594.stdout | 1 + testsuite/tests/ffi/should_run/T5594_c.c | 12 + testsuite/tests/ffi/should_run/T7170.hs | 21 + testsuite/tests/ffi/should_run/T7170.stderr | 1 + testsuite/tests/ffi/should_run/T7170.stdout | 1 + testsuite/tests/ffi/should_run/T8083.hs | 17 + testsuite/tests/ffi/should_run/T8083.stdout | 1 + testsuite/tests/ffi/should_run/T8083_c.c | 10 + testsuite/tests/ffi/should_run/all.T | 227 + testsuite/tests/ffi/should_run/capi_ctype_001.h | 16 + testsuite/tests/ffi/should_run/capi_ctype_001_c.c | 7 + testsuite/tests/ffi/should_run/capi_ctype_002_A.h | 12 + testsuite/tests/ffi/should_run/capi_ctype_002_B.h | 8 + testsuite/tests/ffi/should_run/capi_value.hs | 14 + testsuite/tests/ffi/should_run/capi_value.stdout | 2 + testsuite/tests/ffi/should_run/capi_value_c.c | 4 + testsuite/tests/ffi/should_run/capi_value_c.h | 3 + testsuite/tests/ffi/should_run/fed001.hs | 30 + testsuite/tests/ffi/should_run/fed001.stdout | 1 + testsuite/tests/ffi/should_run/ffi001.hs | 19 + testsuite/tests/ffi/should_run/ffi001.stdout | 1 + testsuite/tests/ffi/should_run/ffi002.hs | 12 + testsuite/tests/ffi/should_run/ffi002.stdout | 5 + testsuite/tests/ffi/should_run/ffi002_c.c | 19 + testsuite/tests/ffi/should_run/ffi003.hs | 8 + testsuite/tests/ffi/should_run/ffi003.stdout | 1 + testsuite/tests/ffi/should_run/ffi004.hs | 22 + testsuite/tests/ffi/should_run/ffi004.stdout | 1 + testsuite/tests/ffi/should_run/ffi005.hs | 111 + testsuite/tests/ffi/should_run/ffi005.stdout | 19 + testsuite/tests/ffi/should_run/ffi006.hs | 27 + testsuite/tests/ffi/should_run/ffi006.stdout | 2 + testsuite/tests/ffi/should_run/ffi007.hs | 14 + testsuite/tests/ffi/should_run/ffi007.stdout | 1 + testsuite/tests/ffi/should_run/ffi008.hs | 14 + testsuite/tests/ffi/should_run/ffi008.stderr | 1 + testsuite/tests/ffi/should_run/ffi009.hs | 552 + testsuite/tests/ffi/should_run/ffi009.stdout | 165 + testsuite/tests/ffi/should_run/ffi010.hs | 9 + testsuite/tests/ffi/should_run/ffi011.hs | 19 + testsuite/tests/ffi/should_run/ffi011.stdout | 2 + testsuite/tests/ffi/should_run/ffi012.hs | 53 + testsuite/tests/ffi/should_run/ffi012.stdout | 4 + testsuite/tests/ffi/should_run/ffi013.hs | 26 + testsuite/tests/ffi/should_run/ffi013.stdout | 1 + testsuite/tests/ffi/should_run/ffi014.hs | 29 + testsuite/tests/ffi/should_run/ffi014.stdout | 100 + testsuite/tests/ffi/should_run/ffi014_cbits.c | 6 + testsuite/tests/ffi/should_run/ffi014_cbits.h | 3 + testsuite/tests/ffi/should_run/ffi015.hs | 12 + testsuite/tests/ffi/should_run/ffi015.stdout | 1 + testsuite/tests/ffi/should_run/ffi015_cbits.c | 1 + testsuite/tests/ffi/should_run/ffi015_cbits.h | 1 + testsuite/tests/ffi/should_run/ffi016.hs | 28 + testsuite/tests/ffi/should_run/ffi016.stdout | 1 + testsuite/tests/ffi/should_run/ffi017.hs | 13 + testsuite/tests/ffi/should_run/ffi018.h | 4 + testsuite/tests/ffi/should_run/ffi018.hs | 10 + testsuite/tests/ffi/should_run/ffi018.stdout | 1 + testsuite/tests/ffi/should_run/ffi018_c.c | 7 + testsuite/tests/ffi/should_run/ffi018_ghci.h | 4 + testsuite/tests/ffi/should_run/ffi018_ghci.hs | 10 + testsuite/tests/ffi/should_run/ffi018_ghci.stdout | 1 + testsuite/tests/ffi/should_run/ffi018_ghci_c.c | 7 + testsuite/tests/ffi/should_run/ffi019.hs | 28 + testsuite/tests/ffi/should_run/ffi019.stdout | 2 + testsuite/tests/ffi/should_run/ffi020.hs | 25 + testsuite/tests/ffi/should_run/ffi020.stderr | 4 + testsuite/tests/ffi/should_run/ffi021.hs | 22 + testsuite/tests/ffi/should_run/ffi021.stdout | 1 + testsuite/tests/ffi/should_run/ffi022.hs | 36 + testsuite/tests/ffi/should_run/ffi022.stdout | 1 + testsuite/tests/ffi/should_run/ffi_parsing_001.hs | 8 + .../tests/ffi/should_run/ffi_parsing_001.stdout | 1 + testsuite/tests/ffi/should_run/ffi_parsing_001_c.c | 8 + testsuite/tests/ffi/should_run/fptr01.h | 10 + testsuite/tests/ffi/should_run/fptr01.hs | 40 + testsuite/tests/ffi/should_run/fptr01.stdout | 12 + testsuite/tests/ffi/should_run/fptr01_c.c | 29 + testsuite/tests/ffi/should_run/fptr02.hs | 10 + testsuite/tests/ffi/should_run/fptrfail01.h | 6 + testsuite/tests/ffi/should_run/fptrfail01.hs | 19 + testsuite/tests/ffi/should_run/fptrfail01.stderr | 1 + testsuite/tests/ffi/should_run/fptrfail01.stdout | 1 + testsuite/tests/ffi/should_run/fptrfail01_c.c | 11 + testsuite/tests/gadt/Arith.hs | 146 + testsuite/tests/gadt/CasePrune.hs | 28 + testsuite/tests/gadt/CasePrune.stderr | 11 + testsuite/tests/gadt/FloatEq.hs | 17 + testsuite/tests/gadt/Gadt17_help.hs | 34 + testsuite/tests/gadt/Gadt23_AST.hs | 10 + testsuite/tests/gadt/Makefile | 27 + testsuite/tests/gadt/Nilsson.hs | 293 + testsuite/tests/gadt/Session.hs | 45 + testsuite/tests/gadt/Session.stdout | 1 + testsuite/tests/gadt/T1999.hs | 12 + testsuite/tests/gadt/T1999a.hs | 10 + testsuite/tests/gadt/T2040.hs | 27 + testsuite/tests/gadt/T2151.hs | 13 + testsuite/tests/gadt/T2587.hs | 18 + testsuite/tests/gadt/T3013.hs | 13 + testsuite/tests/gadt/T3163.hs | 9 + testsuite/tests/gadt/T3163.stderr | 5 + testsuite/tests/gadt/T3169.hs | 16 + testsuite/tests/gadt/T3169.stderr | 18 + testsuite/tests/gadt/T3638.hs | 11 + testsuite/tests/gadt/T3651.hs | 17 + testsuite/tests/gadt/T3651.stderr | 21 + testsuite/tests/gadt/T5424.hs | 13 + testsuite/tests/gadt/T5424a.hs | 4 + testsuite/tests/gadt/T7205.hs | 15 + testsuite/tests/gadt/T7293.hs | 24 + testsuite/tests/gadt/T7293.stderr | 9 + testsuite/tests/gadt/T7294.hs | 25 + testsuite/tests/gadt/T7294.stderr | 9 + testsuite/tests/gadt/T7321.hs | 6 + testsuite/tests/gadt/T7321a.hs | 5 + testsuite/tests/gadt/T7558.hs | 8 + testsuite/tests/gadt/T7558.stderr | 13 + testsuite/tests/gadt/T7974.hs | 8 + testsuite/tests/gadt/all.T | 124 + testsuite/tests/gadt/arrow.hs | 24 + testsuite/tests/gadt/data1.hs | 17 + testsuite/tests/gadt/data2.hs | 19 + testsuite/tests/gadt/doaitse.hs | 55 + testsuite/tests/gadt/equal.hs | 30 + testsuite/tests/gadt/gadt-dim1.hs | 11 + testsuite/tests/gadt/gadt-dim2.hs | 11 + testsuite/tests/gadt/gadt-dim3.hs | 25 + testsuite/tests/gadt/gadt-dim4.hs | 21 + testsuite/tests/gadt/gadt-dim5.hs | 13 + testsuite/tests/gadt/gadt-dim6.hs | 13 + testsuite/tests/gadt/gadt-dim7.hs | 24 + testsuite/tests/gadt/gadt-dim8.hs | 26 + testsuite/tests/gadt/gadt-escape1.hs | 23 + testsuite/tests/gadt/gadt-escape1.stderr | 17 + testsuite/tests/gadt/gadt-fd.hs | 23 + testsuite/tests/gadt/gadt1.hs | 7 + testsuite/tests/gadt/gadt10.hs | 6 + testsuite/tests/gadt/gadt10.stderr | 7 + testsuite/tests/gadt/gadt11.hs | 13 + testsuite/tests/gadt/gadt11.stderr | 6 + testsuite/tests/gadt/gadt13.hs | 17 + testsuite/tests/gadt/gadt13.stderr | 16 + testsuite/tests/gadt/gadt14.hs | 8 + testsuite/tests/gadt/gadt15.hs | 11 + testsuite/tests/gadt/gadt16.hs | 57 + testsuite/tests/gadt/gadt17.hs | 14 + testsuite/tests/gadt/gadt18.hs | 18 + testsuite/tests/gadt/gadt19.hs | 16 + testsuite/tests/gadt/gadt2.hs | 18 + testsuite/tests/gadt/gadt2.stdout | 2 + testsuite/tests/gadt/gadt20.hs | 19 + testsuite/tests/gadt/gadt21.hs | 23 + testsuite/tests/gadt/gadt21.stderr | 19 + testsuite/tests/gadt/gadt22.hs | 26 + testsuite/tests/gadt/gadt23.hs | 15 + testsuite/tests/gadt/gadt24.hs | 14 + testsuite/tests/gadt/gadt25.hs | 41 + testsuite/tests/gadt/gadt3.hs | 18 + testsuite/tests/gadt/gadt4.hs | 18 + testsuite/tests/gadt/gadt4.stdout | 1 + testsuite/tests/gadt/gadt5.hs | 23 + testsuite/tests/gadt/gadt5.stdout | 1 + testsuite/tests/gadt/gadt6.hs | 9 + testsuite/tests/gadt/gadt7.hs | 35 + testsuite/tests/gadt/gadt7.stderr | 19 + testsuite/tests/gadt/gadt8.hs | 15 + testsuite/tests/gadt/gadt9.hs | 15 + testsuite/tests/gadt/gadtSyntax001.hs | 9 + testsuite/tests/gadt/gadtSyntaxFail001.hs | 9 + testsuite/tests/gadt/gadtSyntaxFail001.stderr | 7 + testsuite/tests/gadt/gadtSyntaxFail002.hs | 9 + testsuite/tests/gadt/gadtSyntaxFail002.stderr | 7 + testsuite/tests/gadt/gadtSyntaxFail003.hs | 9 + testsuite/tests/gadt/gadtSyntaxFail003.stderr | 7 + testsuite/tests/gadt/josef.hs | 69 + testsuite/tests/gadt/karl1.hs | 79 + testsuite/tests/gadt/karl2.hs | 136 + testsuite/tests/gadt/lazypat.hs | 7 + testsuite/tests/gadt/lazypat.stderr | 7 + testsuite/tests/gadt/lazypatok.hs | 14 + testsuite/tests/gadt/nbe.hs | 186 + testsuite/tests/gadt/nbe.stdout | 1 + testsuite/tests/gadt/records-fail1.hs | 11 + testsuite/tests/gadt/records-fail1.stderr | 5 + testsuite/tests/gadt/records.hs | 25 + testsuite/tests/gadt/records.stdout | 2 + testsuite/tests/gadt/red-black.hs | 41 + testsuite/tests/gadt/rw.hs | 29 + testsuite/tests/gadt/rw.stderr | 27 + testsuite/tests/gadt/scoped.hs | 33 + testsuite/tests/gadt/set.hs | 45 + testsuite/tests/gadt/tc.hs | 122 + testsuite/tests/gadt/tc.stdout | 1 + testsuite/tests/gadt/tdpe.hs | 24 + testsuite/tests/gadt/termination.hs | 183 + testsuite/tests/gadt/type-rep.hs | 38 + testsuite/tests/gadt/type-rep.stdout | 1 + testsuite/tests/gadt/ubx-records.hs | 30 + testsuite/tests/gadt/ubx-records.stdout | 3 + testsuite/tests/gadt/while.hs | 216 + testsuite/tests/gadt/while.stdout | 1 + testsuite/tests/generics/GEq/GEq1.hs | 51 + testsuite/tests/generics/GEq/GEq1.stdout | 5 + testsuite/tests/generics/GEq/GEq1A.hs | 44 + testsuite/tests/generics/GEq/GEq2.hs | 78 + testsuite/tests/generics/GEq/GEq2.stdout | 4 + testsuite/tests/generics/GEq/Makefile | 3 + testsuite/tests/generics/GEq/test.T | 5 + testsuite/tests/generics/GFunctor/GFunctor.hs | 55 + testsuite/tests/generics/GFunctor/GFunctor1.stdout | 1 + testsuite/tests/generics/GFunctor/Main.hs | 29 + testsuite/tests/generics/GFunctor/Makefile | 3 + testsuite/tests/generics/GFunctor/test.T | 4 + testsuite/tests/generics/GMap/GMap.hs | 41 + testsuite/tests/generics/GMap/GMap1.stdout | 3 + testsuite/tests/generics/GMap/Main.hs | 27 + testsuite/tests/generics/GMap/Makefile | 3 + testsuite/tests/generics/GMap/test.T | 4 + testsuite/tests/generics/GShow/GShow.hs | 124 + testsuite/tests/generics/GShow/GShow1.stdout | 3 + testsuite/tests/generics/GShow/Main.hs | 23 + testsuite/tests/generics/GShow/Makefile | 3 + testsuite/tests/generics/GShow/test.T | 4 + testsuite/tests/generics/GenCanDoRep0.hs | 22 + testsuite/tests/generics/GenCanDoRep1.hs | 33 + testsuite/tests/generics/GenCannotDoRep0_0.hs | 30 + testsuite/tests/generics/GenCannotDoRep0_0.stderr | 23 + testsuite/tests/generics/GenCannotDoRep0_1.hs | 8 + testsuite/tests/generics/GenCannotDoRep0_1.stderr | 8 + testsuite/tests/generics/GenCannotDoRep0_2.hs | 13 + testsuite/tests/generics/GenCannotDoRep0_2.stderr | 5 + testsuite/tests/generics/GenCannotDoRep1_0.hs | 9 + testsuite/tests/generics/GenCannotDoRep1_0.stderr | 5 + testsuite/tests/generics/GenCannotDoRep1_1.hs | 8 + testsuite/tests/generics/GenCannotDoRep1_1.stderr | 8 + testsuite/tests/generics/GenCannotDoRep1_2.hs | 13 + testsuite/tests/generics/GenCannotDoRep1_2.stderr | 5 + testsuite/tests/generics/GenCannotDoRep1_3.hs | 11 + testsuite/tests/generics/GenCannotDoRep1_3.stderr | 6 + testsuite/tests/generics/GenCannotDoRep1_4.hs | 8 + testsuite/tests/generics/GenCannotDoRep1_4.stderr | 6 + testsuite/tests/generics/GenCannotDoRep1_6.hs | 9 + testsuite/tests/generics/GenCannotDoRep1_6.stderr | 6 + testsuite/tests/generics/GenCannotDoRep1_7.hs | 9 + testsuite/tests/generics/GenCannotDoRep1_7.stderr | 6 + testsuite/tests/generics/GenCannotDoRep1_8.hs | 12 + testsuite/tests/generics/GenCannotDoRep1_8.stderr | 6 + testsuite/tests/generics/GenDeprecated.stderr | 3 + testsuite/tests/generics/GenDerivOutput.hs | 13 + testsuite/tests/generics/GenDerivOutput.stderr | 191 + testsuite/tests/generics/GenDerivOutput1_0.hs | 8 + testsuite/tests/generics/GenDerivOutput1_0.stderr | 66 + testsuite/tests/generics/GenDerivOutput1_1.hs | 26 + testsuite/tests/generics/GenDerivOutput1_1.stderr | 351 + testsuite/tests/generics/GenNewtype.hs | 10 + testsuite/tests/generics/GenNewtype.stdout | 1 + testsuite/tests/generics/GenShouldFail0.hs | 11 + testsuite/tests/generics/GenShouldFail0.stderr | 5 + testsuite/tests/generics/GenShouldFail1_0.hs | 11 + testsuite/tests/generics/GenShouldFail1_0.stderr | 5 + testsuite/tests/generics/Makefile | 3 + testsuite/tests/generics/T5884.hs | 9 + testsuite/tests/generics/T7878.hs | 3 + testsuite/tests/generics/T7878A.hs | 7 + testsuite/tests/generics/T7878A.hs-boot | 3 + testsuite/tests/generics/T7878B.hs | 3 + testsuite/tests/generics/T8468.hs | 7 + testsuite/tests/generics/T8468.stderr | 5 + testsuite/tests/generics/T8479.hs | 12 + testsuite/tests/generics/Uniplate/GUniplate.hs | 53 + .../tests/generics/Uniplate/GUniplate1.stdout | 1 + testsuite/tests/generics/Uniplate/Main.hs | 20 + testsuite/tests/generics/Uniplate/Makefile | 3 + testsuite/tests/generics/Uniplate/test.T | 5 + testsuite/tests/generics/all.T | 34 + testsuite/tests/ghc-api/Makefile | 14 + testsuite/tests/ghc-api/T4891/Makefile | 13 + testsuite/tests/ghc-api/T4891/T4891.hs | 68 + testsuite/tests/ghc-api/T4891/T4891.stdout | 20 + testsuite/tests/ghc-api/T4891/X.hs | 5 + testsuite/tests/ghc-api/T4891/all.T | 3 + testsuite/tests/ghc-api/T6145.hs | 43 + testsuite/tests/ghc-api/T6145.stdout | 1 + testsuite/tests/ghc-api/T7478/A.hs | 6 + testsuite/tests/ghc-api/T7478/B.hs | 4 + testsuite/tests/ghc-api/T7478/C.hs | 4 + testsuite/tests/ghc-api/T7478/Makefile | 11 + testsuite/tests/ghc-api/T7478/T7478.hs | 61 + testsuite/tests/ghc-api/T7478/T7478.stdout | 8 + testsuite/tests/ghc-api/T7478/all.T | 8 + testsuite/tests/ghc-api/all.T | 4 + testsuite/tests/ghc-api/apirecomp001/A.hs | 9 + testsuite/tests/ghc-api/apirecomp001/B.hs | 5 + testsuite/tests/ghc-api/apirecomp001/Makefile | 11 + testsuite/tests/ghc-api/apirecomp001/all.T | 4 + .../tests/ghc-api/apirecomp001/apirecomp001.stderr | 32 + .../tests/ghc-api/apirecomp001/apirecomp001.stdout | 4 + testsuite/tests/ghc-api/apirecomp001/myghc.hs | 56 + testsuite/tests/ghc-api/dynCompileExpr/Makefile | 4 + testsuite/tests/ghc-api/dynCompileExpr/all.T | 5 + .../tests/ghc-api/dynCompileExpr/dynCompileExpr.hs | 18 + .../ghc-api/dynCompileExpr/dynCompileExpr.stdout | 1 + testsuite/tests/ghc-api/ghcApi.hs | 8 + testsuite/tests/ghc-api/ghcApi.stdout | 1 + testsuite/tests/ghc-e/should_fail/Makefile | 6 + testsuite/tests/ghc-e/should_fail/all.T | 3 + testsuite/tests/ghc-e/should_run/Makefile | 32 + testsuite/tests/ghc-e/should_run/T2228.hs | 4 + testsuite/tests/ghc-e/should_run/T2228.stdout | 2 + testsuite/tests/ghc-e/should_run/T2636.hs | 2 + testsuite/tests/ghc-e/should_run/T2636.stderr | 4 + testsuite/tests/ghc-e/should_run/T3890.hs | 9 + testsuite/tests/ghc-e/should_run/T3890.stdout | 1 + testsuite/tests/ghc-e/should_run/all.T | 16 + testsuite/tests/ghc-e/should_run/ghc-e002.hs | 3 + testsuite/tests/ghc-e/should_run/ghc-e002.stdout | 1 + testsuite/tests/ghc-e/should_run/ghc-e003.stdout | 2 + testsuite/tests/ghc-e/should_run/ghc-e004.stdout | 1 + testsuite/tests/ghc-e/should_run/ghc-e005.hs | 13 + testsuite/tests/ghc-e/should_run/ghc-e005.stderr | 1 + testsuite/tests/ghc-e/should_run/ghc-e005.stdout | 3 + testsuite/tests/ghci.debugger/GADT.hs | 20 + testsuite/tests/ghci.debugger/HappyTest.hs | 535 + testsuite/tests/ghci.debugger/Makefile | 3 + testsuite/tests/ghci.debugger/QSort.hs | 11 + testsuite/tests/ghci.debugger/Test.hs | 40 + testsuite/tests/ghci.debugger/Test2.hs | 5 + testsuite/tests/ghci.debugger/Test3.hs | 4 + testsuite/tests/ghci.debugger/Test4.hs | 3 + testsuite/tests/ghci.debugger/Test6.hs | 5 + testsuite/tests/ghci.debugger/Test7.hs | 2 + testsuite/tests/ghci.debugger/Unboxed.hs | 12 + testsuite/tests/ghci.debugger/getargs.hs | 3 + testsuite/tests/ghci.debugger/mdo.hs | 37 + testsuite/tests/ghci.debugger/scripts/Break007.hs | 4 + testsuite/tests/ghci.debugger/scripts/Break020b.hs | 4 + testsuite/tests/ghci.debugger/scripts/Makefile | 3 + testsuite/tests/ghci.debugger/scripts/T2740.hs | 4 + testsuite/tests/ghci.debugger/scripts/T2740.script | 8 + testsuite/tests/ghci.debugger/scripts/T2740.stdout | 10 + testsuite/tests/ghci.debugger/scripts/T7386.hs | 10 + testsuite/tests/ghci.debugger/scripts/T7386.script | 3 + testsuite/tests/ghci.debugger/scripts/T7386.stdout | 1 + testsuite/tests/ghci.debugger/scripts/T8557.hs | 8 + testsuite/tests/ghci.debugger/scripts/T8557.script | 2 + testsuite/tests/ghci.debugger/scripts/T8557.stdout | 1 + testsuite/tests/ghci.debugger/scripts/TupleN.hs | 10 + testsuite/tests/ghci.debugger/scripts/all.T | 89 + .../tests/ghci.debugger/scripts/break001.script | 14 + .../tests/ghci.debugger/scripts/break001.stdout | 19 + .../tests/ghci.debugger/scripts/break002.script | 5 + .../tests/ghci.debugger/scripts/break002.stdout | 2 + .../tests/ghci.debugger/scripts/break003.script | 10 + .../tests/ghci.debugger/scripts/break003.stderr | 4 + .../tests/ghci.debugger/scripts/break003.stdout | 6 + .../tests/ghci.debugger/scripts/break004.script | 5 + .../tests/ghci.debugger/scripts/break005.script | 5 + .../tests/ghci.debugger/scripts/break005.stdout | 9 + .../tests/ghci.debugger/scripts/break006.script | 14 + .../tests/ghci.debugger/scripts/break006.stderr | 26 + .../tests/ghci.debugger/scripts/break006.stdout | 20 + .../tests/ghci.debugger/scripts/break007.script | 5 + .../tests/ghci.debugger/scripts/break007.stdout | 1 + .../tests/ghci.debugger/scripts/break008.script | 5 + .../tests/ghci.debugger/scripts/break008.stdout | 3 + .../tests/ghci.debugger/scripts/break009.script | 7 + .../tests/ghci.debugger/scripts/break009.stdout | 4 + .../tests/ghci.debugger/scripts/break010.script | 6 + .../tests/ghci.debugger/scripts/break010.stdout | 5 + .../tests/ghci.debugger/scripts/break011.script | 18 + .../tests/ghci.debugger/scripts/break011.stdout | 23 + testsuite/tests/ghci.debugger/scripts/break012.hs | 5 + .../tests/ghci.debugger/scripts/break012.script | 9 + .../tests/ghci.debugger/scripts/break012.stdout | 16 + testsuite/tests/ghci.debugger/scripts/break013.hs | 4 + .../tests/ghci.debugger/scripts/break013.script | 5 + .../tests/ghci.debugger/scripts/break013.stdout | 11 + testsuite/tests/ghci.debugger/scripts/break014.hs | 4 + .../tests/ghci.debugger/scripts/break014.script | 5 + .../tests/ghci.debugger/scripts/break014.stdout | 5 + testsuite/tests/ghci.debugger/scripts/break015.hs | 3 + .../tests/ghci.debugger/scripts/break015.script | 8 + testsuite/tests/ghci.debugger/scripts/break016.hs | 4 + .../tests/ghci.debugger/scripts/break016.script | 11 + .../tests/ghci.debugger/scripts/break016.stdout | 3 + .../tests/ghci.debugger/scripts/break017.script | 11 + .../tests/ghci.debugger/scripts/break017.stdout | 12 + .../tests/ghci.debugger/scripts/break018.script | 9 + .../tests/ghci.debugger/scripts/break018.stdout | 13 + .../tests/ghci.debugger/scripts/break019.script | 3 + .../tests/ghci.debugger/scripts/break019.stderr | 2 + testsuite/tests/ghci.debugger/scripts/break020.hs | 15 + .../tests/ghci.debugger/scripts/break020.script | 8 + .../tests/ghci.debugger/scripts/break020.stdout | 42 + .../tests/ghci.debugger/scripts/break021.script | 23 + .../tests/ghci.debugger/scripts/break021.stdout | 135 + .../tests/ghci.debugger/scripts/break022/A1.hs | 4 + .../tests/ghci.debugger/scripts/break022/B.hs | 5 + .../tests/ghci.debugger/scripts/break022/B.hs-boot | 3 + .../tests/ghci.debugger/scripts/break022/C.hs | 5 + .../tests/ghci.debugger/scripts/break022/Makefile | 3 + .../tests/ghci.debugger/scripts/break022/all.T | 4 + .../ghci.debugger/scripts/break022/break022.script | 21 + .../ghci.debugger/scripts/break022/break022.stdout | 8 + .../tests/ghci.debugger/scripts/break023/A1.hs | 2 + .../tests/ghci.debugger/scripts/break023/B.hs | 5 + .../tests/ghci.debugger/scripts/break023/B.hs-boot | 3 + .../tests/ghci.debugger/scripts/break023/C.hs | 5 + .../tests/ghci.debugger/scripts/break023/Makefile | 3 + .../tests/ghci.debugger/scripts/break023/all.T | 4 + .../ghci.debugger/scripts/break023/break023.script | 18 + .../ghci.debugger/scripts/break023/break023.stdout | 2 + testsuite/tests/ghci.debugger/scripts/break024.hs | 4 + .../tests/ghci.debugger/scripts/break024.script | 16 + .../tests/ghci.debugger/scripts/break024.stdout | 19 + .../ghci.debugger/scripts/break024.stdout-ghc-7.0 | 28 + .../tests/ghci.debugger/scripts/break025.script | 4 + .../tests/ghci.debugger/scripts/break025.stdout | 3 + testsuite/tests/ghci.debugger/scripts/break026.hs | 7 + .../tests/ghci.debugger/scripts/break026.script | 23 + .../tests/ghci.debugger/scripts/break026.stdout | 58 + .../tests/ghci.debugger/scripts/break027.script | 5 + .../tests/ghci.debugger/scripts/break027.stdout | 9 + testsuite/tests/ghci.debugger/scripts/break028.hs | 15 + .../tests/ghci.debugger/scripts/break028.script | 4 + .../tests/ghci.debugger/scripts/break028.stdout | 5 + .../tests/ghci.debugger/scripts/dynbrk001.script | 22 + .../tests/ghci.debugger/scripts/dynbrk001.stderr | 4 + .../tests/ghci.debugger/scripts/dynbrk001.stdout | 5 + .../tests/ghci.debugger/scripts/dynbrk002.script | 7 + .../tests/ghci.debugger/scripts/dynbrk002.stdout | 6 + .../tests/ghci.debugger/scripts/dynbrk003.script | 2 + .../tests/ghci.debugger/scripts/dynbrk003.stdout | 1 + .../tests/ghci.debugger/scripts/dynbrk004.script | 8 + .../tests/ghci.debugger/scripts/dynbrk004.stdout | 4 + testsuite/tests/ghci.debugger/scripts/dynbrk005.hs | 5 + .../tests/ghci.debugger/scripts/dynbrk005.script | 13 + .../tests/ghci.debugger/scripts/dynbrk005.stdout | 11 + testsuite/tests/ghci.debugger/scripts/dynbrk007.hs | 6 + .../tests/ghci.debugger/scripts/dynbrk007.script | 7 + .../tests/ghci.debugger/scripts/dynbrk007.stdout | 11 + testsuite/tests/ghci.debugger/scripts/dynbrk008.hs | 4 + .../tests/ghci.debugger/scripts/dynbrk008.script | 9 + .../tests/ghci.debugger/scripts/dynbrk008.stdout | 15 + testsuite/tests/ghci.debugger/scripts/dynbrk009.hs | 8 + .../tests/ghci.debugger/scripts/dynbrk009.script | 10 + .../tests/ghci.debugger/scripts/dynbrk009.stdout | 11 + .../tests/ghci.debugger/scripts/getargs.script | 4 + .../tests/ghci.debugger/scripts/getargs.stdout | 3 + .../tests/ghci.debugger/scripts/hist001.script | 15 + .../tests/ghci.debugger/scripts/hist001.stdout | 31 + .../ghci.debugger/scripts/listCommand001.script | 13 + .../ghci.debugger/scripts/listCommand001.stdout | 15 + .../tests/ghci.debugger/scripts/listCommand002.hs | 5 + .../ghci.debugger/scripts/listCommand002.script | 4 + .../ghci.debugger/scripts/listCommand002.stdout | 6 + .../tests/ghci.debugger/scripts/print001.script | 12 + .../tests/ghci.debugger/scripts/print001.stdout | 10 + .../tests/ghci.debugger/scripts/print002.script | 19 + .../tests/ghci.debugger/scripts/print002.stdout | 8 + .../tests/ghci.debugger/scripts/print003.script | 15 + .../tests/ghci.debugger/scripts/print003.stdout | 15 + .../tests/ghci.debugger/scripts/print004.script | 28 + .../tests/ghci.debugger/scripts/print004.stdout | 19 + .../tests/ghci.debugger/scripts/print005.script | 15 + .../tests/ghci.debugger/scripts/print005.stdout | 19 + .../tests/ghci.debugger/scripts/print006.script | 17 + .../tests/ghci.debugger/scripts/print006.stdout | 10 + .../tests/ghci.debugger/scripts/print007.script | 30 + .../tests/ghci.debugger/scripts/print007.stderr | 3 + .../tests/ghci.debugger/scripts/print007.stdout | 6 + .../tests/ghci.debugger/scripts/print008.script | 14 + .../tests/ghci.debugger/scripts/print008.stdout | 7 + .../tests/ghci.debugger/scripts/print009.script | 8 + .../tests/ghci.debugger/scripts/print009.stdout | 3 + .../tests/ghci.debugger/scripts/print010.script | 12 + .../tests/ghci.debugger/scripts/print010.stdout | 6 + .../tests/ghci.debugger/scripts/print011.script | 13 + .../tests/ghci.debugger/scripts/print011.stdout | 7 + .../tests/ghci.debugger/scripts/print012.script | 11 + .../tests/ghci.debugger/scripts/print012.stdout | 6 + .../tests/ghci.debugger/scripts/print013.script | 10 + .../tests/ghci.debugger/scripts/print013.stdout | 3 + .../tests/ghci.debugger/scripts/print014.script | 7 + .../tests/ghci.debugger/scripts/print014.stdout | 1 + .../tests/ghci.debugger/scripts/print015.script | 8 + .../tests/ghci.debugger/scripts/print015.stdout | 5 + .../tests/ghci.debugger/scripts/print016.script | 10 + .../tests/ghci.debugger/scripts/print016.stdout | 5 + .../tests/ghci.debugger/scripts/print017.script | 12 + .../tests/ghci.debugger/scripts/print017.stdout | 7 + .../tests/ghci.debugger/scripts/print018.script | 15 + .../tests/ghci.debugger/scripts/print018.stdout | 12 + .../tests/ghci.debugger/scripts/print019.script | 11 + .../tests/ghci.debugger/scripts/print019.stderr | 12 + .../tests/ghci.debugger/scripts/print019.stdout | 9 + .../tests/ghci.debugger/scripts/print020.script | 5 + .../tests/ghci.debugger/scripts/print020.stdout | 14 + testsuite/tests/ghci.debugger/scripts/print021.hs | 18 + .../tests/ghci.debugger/scripts/print021.script | 3 + .../tests/ghci.debugger/scripts/print021.stdout | 2 + testsuite/tests/ghci.debugger/scripts/print022.hs | 11 + .../tests/ghci.debugger/scripts/print022.script | 9 + .../tests/ghci.debugger/scripts/print022.stdout | 10 + .../tests/ghci.debugger/scripts/print023.script | 8 + .../tests/ghci.debugger/scripts/print023.stdout | 2 + .../tests/ghci.debugger/scripts/print024.script | 10 + .../tests/ghci.debugger/scripts/print024.stdout | 3 + testsuite/tests/ghci.debugger/scripts/print025.hs | 2 + .../tests/ghci.debugger/scripts/print025.script | 8 + .../tests/ghci.debugger/scripts/print025.stdout | 8 + .../tests/ghci.debugger/scripts/print026.script | 8 + .../tests/ghci.debugger/scripts/print026.stdout | 6 + .../tests/ghci.debugger/scripts/print027.script | 8 + .../tests/ghci.debugger/scripts/print027.stdout | 6 + .../tests/ghci.debugger/scripts/print028.script | 8 + .../tests/ghci.debugger/scripts/print028.stdout | 6 + testsuite/tests/ghci.debugger/scripts/print029.hs | 7 + .../tests/ghci.debugger/scripts/print029.script | 10 + .../tests/ghci.debugger/scripts/print029.stdout | 8 + .../tests/ghci.debugger/scripts/print030.script | 10 + .../tests/ghci.debugger/scripts/print030.stdout | 7 + testsuite/tests/ghci.debugger/scripts/print031.hs | 7 + .../tests/ghci.debugger/scripts/print031.script | 10 + .../tests/ghci.debugger/scripts/print031.stdout | 8 + .../tests/ghci.debugger/scripts/print032.script | 8 + .../tests/ghci.debugger/scripts/print032.stdout | 8 + .../tests/ghci.debugger/scripts/print033.script | 5 + .../tests/ghci.debugger/scripts/print033.stdout | 1 + .../tests/ghci.debugger/scripts/print034.script | 11 + .../tests/ghci.debugger/scripts/print034.stdout | 4 + .../tests/ghci.debugger/scripts/print035.script | 10 + .../tests/ghci.debugger/scripts/print035.stdout | 5 + testsuite/tests/ghci.debugger/scripts/result001.hs | 3 + .../tests/ghci.debugger/scripts/result001.script | 5 + .../tests/ghci.debugger/scripts/result001.stdout | 4 + testsuite/tests/ghci/Makefile | 3 + testsuite/tests/ghci/linking/Makefile | 123 + testsuite/tests/ghci/linking/T3333.c | 4 + testsuite/tests/ghci/linking/T3333.hs | 5 + testsuite/tests/ghci/linking/T3333.stdout | 1 + testsuite/tests/ghci/linking/TestLink.hs | 8 + testsuite/tests/ghci/linking/all.T | 47 + testsuite/tests/ghci/linking/f.c | 4 + testsuite/tests/ghci/linking/ghcilink001.stdout | 1 + .../tests/ghci/linking/ghcilink002.stderr-mingw32 | 1 + testsuite/tests/ghci/linking/ghcilink002.stdout | 1 + testsuite/tests/ghci/linking/ghcilink004.stdout | 1 + .../tests/ghci/linking/ghcilink005.stderr-mingw32 | 1 + testsuite/tests/ghci/linking/ghcilink005.stdout | 1 + testsuite/tests/ghci/prog001/A.hs | 5 + testsuite/tests/ghci/prog001/B.hs | 5 + testsuite/tests/ghci/prog001/C1.hs | 9 + testsuite/tests/ghci/prog001/D1.hs | 5 + testsuite/tests/ghci/prog001/D2.hs | 5 + testsuite/tests/ghci/prog001/Makefile | 3 + testsuite/tests/ghci/prog001/prog001.T | 5 + testsuite/tests/ghci/prog001/prog001.script | 41 + testsuite/tests/ghci/prog001/prog001.stdout | 4 + testsuite/tests/ghci/prog002/A1.hs | 6 + testsuite/tests/ghci/prog002/A2.hs | 6 + testsuite/tests/ghci/prog002/B.hs | 7 + testsuite/tests/ghci/prog002/C.hs | 5 + testsuite/tests/ghci/prog002/D.hs | 5 + testsuite/tests/ghci/prog002/Makefile | 3 + testsuite/tests/ghci/prog002/prog002.T | 5 + testsuite/tests/ghci/prog002/prog002.script | 45 + testsuite/tests/ghci/prog002/prog002.stdout | 12 + testsuite/tests/ghci/prog003/A.hs | 8 + testsuite/tests/ghci/prog003/B.hs | 5 + testsuite/tests/ghci/prog003/C.hs | 6 + testsuite/tests/ghci/prog003/D1.hs | 13 + testsuite/tests/ghci/prog003/D2.hs | 13 + testsuite/tests/ghci/prog003/Makefile | 3 + testsuite/tests/ghci/prog003/prog003.T | 7 + testsuite/tests/ghci/prog003/prog003.script | 90 + testsuite/tests/ghci/prog003/prog003.stdout | 43 + testsuite/tests/ghci/prog004/Makefile | 11 + testsuite/tests/ghci/prog004/prog004.T | 11 + testsuite/tests/ghci/prog005/A1.hs | 2 + testsuite/tests/ghci/prog005/B.hs | 4 + testsuite/tests/ghci/prog005/Makefile | 3 + testsuite/tests/ghci/prog005/prog005.T | 2 + testsuite/tests/ghci/prog005/prog005.script | 18 + testsuite/tests/ghci/prog005/prog005.stdout | 2 + testsuite/tests/ghci/prog006/A.hs | 6 + testsuite/tests/ghci/prog006/Boot.hs-boot | 3 + testsuite/tests/ghci/prog006/Boot1.hs | 5 + testsuite/tests/ghci/prog006/Boot2.hs | 6 + testsuite/tests/ghci/prog006/Makefile | 3 + testsuite/tests/ghci/prog006/prog006.T | 1 + testsuite/tests/ghci/prog006/prog006.script | 6 + testsuite/tests/ghci/prog006/prog006.stderr | 4 + testsuite/tests/ghci/prog007/A.hs | 8 + testsuite/tests/ghci/prog007/B.hs | 7 + testsuite/tests/ghci/prog007/C.hs | 10 + testsuite/tests/ghci/prog007/C.hs-boot | 2 + testsuite/tests/ghci/prog007/ghci.prog007.script | 2 + testsuite/tests/ghci/prog007/ghci.prog007.stdout | 1 + testsuite/tests/ghci/prog007/prog007.T | 2 + testsuite/tests/ghci/prog008/A.hs | 14 + testsuite/tests/ghci/prog008/ghci.prog008.script | 4 + testsuite/tests/ghci/prog008/ghci.prog008.stdout | 8 + testsuite/tests/ghci/prog008/prog008.T | 2 + testsuite/tests/ghci/prog009/A1.hs | 3 + testsuite/tests/ghci/prog009/A2.hs | 1 + testsuite/tests/ghci/prog009/A3.hs | 2 + testsuite/tests/ghci/prog009/B.hs | 3 + testsuite/tests/ghci/prog009/Makefile | 3 + testsuite/tests/ghci/prog009/ghci.prog009.T | 4 + testsuite/tests/ghci/prog009/ghci.prog009.script | 36 + testsuite/tests/ghci/prog009/ghci.prog009.stderr | 8 + testsuite/tests/ghci/prog009/ghci.prog009.stdout | 8 + testsuite/tests/ghci/prog010/A.hs | 5 + testsuite/tests/ghci/prog010/B.hs | 3 + testsuite/tests/ghci/prog010/ghci.prog010.script | 33 + testsuite/tests/ghci/prog010/ghci.prog010.stderr | 2 + testsuite/tests/ghci/prog010/ghci.prog010.stdout | 9 + testsuite/tests/ghci/prog011/Makefile | 3 + testsuite/tests/ghci/prog011/prog011.T | 2 + testsuite/tests/ghci/prog011/prog011.hx | 16 + testsuite/tests/ghci/prog011/prog011.script | 3 + testsuite/tests/ghci/prog011/prog011.stderr | 2 + testsuite/tests/ghci/prog011/prog011.stdout | 3 + testsuite/tests/ghci/prog012/Bar1.hs | 1 + testsuite/tests/ghci/prog012/Bar2.hs | 3 + testsuite/tests/ghci/prog012/Foo.hs | 3 + testsuite/tests/ghci/prog012/Main.hs | 4 + testsuite/tests/ghci/prog012/Makefile | 3 + testsuite/tests/ghci/prog012/all.T | 2 + testsuite/tests/ghci/prog012/prog012.script | 18 + testsuite/tests/ghci/prog012/prog012.stderr | 2 + testsuite/tests/ghci/prog012/prog012.stdout | 1 + testsuite/tests/ghci/scripts/Defer02.script | 14 + testsuite/tests/ghci/scripts/Defer02.stderr | 187 + testsuite/tests/ghci/scripts/Defer02.stdout | 1 + testsuite/tests/ghci/scripts/Ghci025B.hs | 5 + testsuite/tests/ghci/scripts/Ghci025C.hs | 9 + testsuite/tests/ghci/scripts/Ghci025D.hs | 5 + testsuite/tests/ghci/scripts/GhciKinds.hs | 6 + testsuite/tests/ghci/scripts/GhciKinds.script | 5 + testsuite/tests/ghci/scripts/GhciKinds.stdout | 5 + testsuite/tests/ghci/scripts/Makefile | 41 + testsuite/tests/ghci/scripts/T1914.script | 16 + testsuite/tests/ghci/scripts/T1914.stderr | 4 + testsuite/tests/ghci/scripts/T1914.stdout | 7 + testsuite/tests/ghci/scripts/T2452.script | 2 + testsuite/tests/ghci/scripts/T2452.stderr | 2 + testsuite/tests/ghci/scripts/T2766.script | 6 + testsuite/tests/ghci/scripts/T2766.stdout | 3 + testsuite/tests/ghci/scripts/T2816.script | 5 + testsuite/tests/ghci/scripts/T2816.stderr | 2 + testsuite/tests/ghci/scripts/T2816.stdout | 3 + testsuite/tests/ghci/scripts/T2976.script | 8 + testsuite/tests/ghci/scripts/T2976.stdout | 6 + testsuite/tests/ghci/scripts/T3263.hs | 9 + testsuite/tests/ghci/scripts/T3263.script | 1 + testsuite/tests/ghci/scripts/T3263.stderr | 5 + testsuite/tests/ghci/scripts/T4015.hs | 7 + testsuite/tests/ghci/scripts/T4015.script | 9 + testsuite/tests/ghci/scripts/T4015.stdout | 20 + testsuite/tests/ghci/scripts/T4051.hs | 2 + testsuite/tests/ghci/scripts/T4051.script | 4 + testsuite/tests/ghci/scripts/T4051.stdout | 1 + testsuite/tests/ghci/scripts/T4087.hs | 6 + testsuite/tests/ghci/scripts/T4087.script | 2 + testsuite/tests/ghci/scripts/T4087.stdout | 4 + testsuite/tests/ghci/scripts/T4127.script | 3 + testsuite/tests/ghci/scripts/T4127.stdout | 1 + testsuite/tests/ghci/scripts/T4127a.script | 2 + testsuite/tests/ghci/scripts/T4127a.stderr | 11 + testsuite/tests/ghci/scripts/T4175.hs | 34 + testsuite/tests/ghci/scripts/T4175.script | 9 + testsuite/tests/ghci/scripts/T4175.stdout | 53 + testsuite/tests/ghci/scripts/T4316.script | 23 + testsuite/tests/ghci/scripts/T4316.stdout | 5 + testsuite/tests/ghci/scripts/T4832.script | 2 + testsuite/tests/ghci/scripts/T4832.stdout | 1 + testsuite/tests/ghci/scripts/T5045.hs | 44 + testsuite/tests/ghci/scripts/T5045.script | 2 + testsuite/tests/ghci/scripts/T5130.script | 3 + testsuite/tests/ghci/scripts/T5417.hs | 10 + testsuite/tests/ghci/scripts/T5417.script | 3 + testsuite/tests/ghci/scripts/T5417.stdout | 10 + testsuite/tests/ghci/scripts/T5417a.hs | 5 + testsuite/tests/ghci/scripts/T5545.script | 2 + testsuite/tests/ghci/scripts/T5545.stdout | 2 + testsuite/tests/ghci/scripts/T5557.script | 4 + testsuite/tests/ghci/scripts/T5557.stdout | 2 + testsuite/tests/ghci/scripts/T5564.script | 4 + testsuite/tests/ghci/scripts/T5564.stderr | 9 + testsuite/tests/ghci/scripts/T5564.stdout | 2 + testsuite/tests/ghci/scripts/T5566.hs | 13 + testsuite/tests/ghci/scripts/T5566.script | 4 + testsuite/tests/ghci/scripts/T5566.stdout | 3 + testsuite/tests/ghci/scripts/T5820.hs | 3 + testsuite/tests/ghci/scripts/T5820.script | 4 + testsuite/tests/ghci/scripts/T5820.stderr | 5 + testsuite/tests/ghci/scripts/T5820.stdout | 4 + testsuite/tests/ghci/scripts/T5836.script | 1 + testsuite/tests/ghci/scripts/T5836.stderr | 4 + testsuite/tests/ghci/scripts/T5975a.script | 1 + testsuite/tests/ghci/scripts/T5979.script | 4 + testsuite/tests/ghci/scripts/T5979.stderr | 4 + testsuite/tests/ghci/scripts/T6007.script | 3 + testsuite/tests/ghci/scripts/T6007.stderr | 6 + testsuite/tests/ghci/scripts/T6027ghci.script | 3 + testsuite/tests/ghci/scripts/T6027ghci.stdout | 1 + testsuite/tests/ghci/scripts/T6091.hs | 5 + testsuite/tests/ghci/scripts/T6091.script | 2 + testsuite/tests/ghci/scripts/T6091.stdout | 2 + testsuite/tests/ghci/scripts/T6105.hs | 2 + testsuite/tests/ghci/scripts/T6105.script | 3 + testsuite/tests/ghci/scripts/T6105.stdout | 4 + testsuite/tests/ghci/scripts/T6106.script | 10 + testsuite/tests/ghci/scripts/T6106.stderr | 4 + testsuite/tests/ghci/scripts/T6106_preproc.hs | 17 + testsuite/tests/ghci/scripts/T7117.script | 4 + testsuite/tests/ghci/scripts/T7117.stdout | 1 + testsuite/tests/ghci/scripts/T7586.script | 4 + testsuite/tests/ghci/scripts/T7586.stdout | 3 + testsuite/tests/ghci/scripts/T7587.script | 3 + testsuite/tests/ghci/scripts/T7587.stdout | 1 + testsuite/tests/ghci/scripts/T7627.script | 16 + testsuite/tests/ghci/scripts/T7627.stdout | 26 + testsuite/tests/ghci/scripts/T7627b.script | 8 + testsuite/tests/ghci/scripts/T7627b.stderr | 12 + testsuite/tests/ghci/scripts/T7688.hs | 5 + testsuite/tests/ghci/scripts/T7688.script | 4 + testsuite/tests/ghci/scripts/T7688.stdout | 1 + testsuite/tests/ghci/scripts/T7872.script | 7 + testsuite/tests/ghci/scripts/T7872.stdout | 2 + testsuite/tests/ghci/scripts/T7873.script | 5 + testsuite/tests/ghci/scripts/T7873.stdout | 6 + testsuite/tests/ghci/scripts/T789.hs | 808 + testsuite/tests/ghci/scripts/T789.script | 2 + testsuite/tests/ghci/scripts/T789.stdout | 1 + testsuite/tests/ghci/scripts/T7894.script | 1 + testsuite/tests/ghci/scripts/T7894.stderr | 2 + testsuite/tests/ghci/scripts/T7939.hs | 27 + testsuite/tests/ghci/scripts/T7939.script | 13 + testsuite/tests/ghci/scripts/T7939.stdout | 23 + testsuite/tests/ghci/scripts/T8113.script | 18 + testsuite/tests/ghci/scripts/T8113.stdout | 21 + testsuite/tests/ghci/scripts/T8116.script | 2 + testsuite/tests/ghci/scripts/T8116.stdout | 1 + testsuite/tests/ghci/scripts/T8172.script | 7 + testsuite/tests/ghci/scripts/T8172.stdout | 11 + testsuite/tests/ghci/scripts/T8215.script | 2 + testsuite/tests/ghci/scripts/T8357.hs | 32 + testsuite/tests/ghci/scripts/T8357.script | 4 + testsuite/tests/ghci/scripts/T8357.stdout | 3 + testsuite/tests/ghci/scripts/T8383.hs | 8 + testsuite/tests/ghci/scripts/T8383.script | 3 + testsuite/tests/ghci/scripts/T8383.stdout | 2 + testsuite/tests/ghci/scripts/T8469.hs | 3 + testsuite/tests/ghci/scripts/T8469.script | 2 + testsuite/tests/ghci/scripts/T8469.stdout | 10 + testsuite/tests/ghci/scripts/T8469a.hs | 6 + testsuite/tests/ghci/scripts/T8485.script | 2 + testsuite/tests/ghci/scripts/T8485.stderr | 4 + testsuite/tests/ghci/scripts/T8535.script | 2 + testsuite/tests/ghci/scripts/T8535.stdout | 4 + testsuite/tests/ghci/scripts/all.T | 162 + testsuite/tests/ghci/scripts/ghci001.script | 3 + testsuite/tests/ghci/scripts/ghci001.stdout | 2 + testsuite/tests/ghci/scripts/ghci002.script | 4 + testsuite/tests/ghci/scripts/ghci002.stdout | 2 + testsuite/tests/ghci/scripts/ghci003.script | 7 + testsuite/tests/ghci/scripts/ghci003.stdout | 6 + testsuite/tests/ghci/scripts/ghci004.hs | 2 + testsuite/tests/ghci/scripts/ghci004.script | 4 + testsuite/tests/ghci/scripts/ghci004.stdout | 1 + testsuite/tests/ghci/scripts/ghci005.script | 18 + testsuite/tests/ghci/scripts/ghci005.stdout | 9 + testsuite/tests/ghci/scripts/ghci006.hs | 8 + testsuite/tests/ghci/scripts/ghci006.script | 6 + testsuite/tests/ghci/scripts/ghci006.stdout | 1 + testsuite/tests/ghci/scripts/ghci007.script | 2 + testsuite/tests/ghci/scripts/ghci007.stdout | 1 + testsuite/tests/ghci/scripts/ghci008.script | 7 + testsuite/tests/ghci/scripts/ghci008.stdout | 36 + testsuite/tests/ghci/scripts/ghci009.script | 20 + testsuite/tests/ghci/scripts/ghci009.stdout | 16 + testsuite/tests/ghci/scripts/ghci010.script | 2 + testsuite/tests/ghci/scripts/ghci010.stdout | 14 + testsuite/tests/ghci/scripts/ghci011.script | 4 + testsuite/tests/ghci/scripts/ghci011.stdout | 22 + testsuite/tests/ghci/scripts/ghci012.script | 2 + testsuite/tests/ghci/scripts/ghci012.stdout | 1 + testsuite/tests/ghci/scripts/ghci013.script | 5 + testsuite/tests/ghci/scripts/ghci013.stdout | 1 + testsuite/tests/ghci/scripts/ghci014.hs | 7 + testsuite/tests/ghci/scripts/ghci014.script | 983 ++ testsuite/tests/ghci/scripts/ghci014.stdout | 982 ++ testsuite/tests/ghci/scripts/ghci015.hs | 43 + testsuite/tests/ghci/scripts/ghci015.script | 388 + testsuite/tests/ghci/scripts/ghci015.stdout | 387 + testsuite/tests/ghci/scripts/ghci016.hs | 18 + testsuite/tests/ghci/scripts/ghci016.script | 2 + testsuite/tests/ghci/scripts/ghci016.stdout | 1 + testsuite/tests/ghci/scripts/ghci017.script | 1 + testsuite/tests/ghci/scripts/ghci017.stdout | 1 + testsuite/tests/ghci/scripts/ghci018.script | 4 + testsuite/tests/ghci/scripts/ghci018.stdout | 2 + testsuite/tests/ghci/scripts/ghci019.hs | 9 + testsuite/tests/ghci/scripts/ghci019.script | 2 + testsuite/tests/ghci/scripts/ghci019.stderr | 5 + testsuite/tests/ghci/scripts/ghci019.stdout | 2 + testsuite/tests/ghci/scripts/ghci020.script | 1 + testsuite/tests/ghci/scripts/ghci020.stdout | 3 + testsuite/tests/ghci/scripts/ghci021.script | 4 + testsuite/tests/ghci/scripts/ghci021.stderr | 2 + testsuite/tests/ghci/scripts/ghci021.stdout | 1 + testsuite/tests/ghci/scripts/ghci022.hs | 2 + testsuite/tests/ghci/scripts/ghci022.script | 2 + testsuite/tests/ghci/scripts/ghci022.stderr | 3 + testsuite/tests/ghci/scripts/ghci023.ghci | 10 + testsuite/tests/ghci/scripts/ghci023.script | 17 + testsuite/tests/ghci/scripts/ghci023.stdout | 16 + testsuite/tests/ghci/scripts/ghci024.script | 10 + testsuite/tests/ghci/scripts/ghci024.stdout | 36 + testsuite/tests/ghci/scripts/ghci025.hs | 22 + testsuite/tests/ghci/scripts/ghci025.script | 25 + testsuite/tests/ghci/scripts/ghci025.stdout | 111 + .../tests/ghci/scripts/ghci025.stdout-ghc-7.0 | 111 + testsuite/tests/ghci/scripts/ghci026.script | 6 + testsuite/tests/ghci/scripts/ghci026.stdout | 15 + testsuite/tests/ghci/scripts/ghci027.script | 8 + testsuite/tests/ghci/scripts/ghci027.stdout | 8 + testsuite/tests/ghci/scripts/ghci027_1.hs | 5 + testsuite/tests/ghci/scripts/ghci027_2.hs | 5 + testsuite/tests/ghci/scripts/ghci028.script | 4 + testsuite/tests/ghci/scripts/ghci028.stdout | 1 + testsuite/tests/ghci/scripts/ghci029.script | 11 + testsuite/tests/ghci/scripts/ghci029.stdout | 7 + testsuite/tests/ghci/scripts/ghci030.hs | 9 + testsuite/tests/ghci/scripts/ghci030.script | 3 + testsuite/tests/ghci/scripts/ghci030.stdout | 6 + testsuite/tests/ghci/scripts/ghci031.hs | 8 + testsuite/tests/ghci/scripts/ghci031.script | 2 + testsuite/tests/ghci/scripts/ghci031.stderr | 3 + testsuite/tests/ghci/scripts/ghci031.stdout | 1 + testsuite/tests/ghci/scripts/ghci032.script | 11 + testsuite/tests/ghci/scripts/ghci033.hs | 5 + testsuite/tests/ghci/scripts/ghci033.script | 2 + testsuite/tests/ghci/scripts/ghci033.stdout | 2 + testsuite/tests/ghci/scripts/ghci034.script | 3 + testsuite/tests/ghci/scripts/ghci034.stderr | 2 + testsuite/tests/ghci/scripts/ghci034.stdout | 1 + testsuite/tests/ghci/scripts/ghci035.script | 4 + testsuite/tests/ghci/scripts/ghci035.stdout | 1 + testsuite/tests/ghci/scripts/ghci036.script | 19 + testsuite/tests/ghci/scripts/ghci036.stderr | 18 + testsuite/tests/ghci/scripts/ghci036.stdout | 3 + testsuite/tests/ghci/scripts/ghci037.script | 3 + testsuite/tests/ghci/scripts/ghci037.stdout | 2 + testsuite/tests/ghci/scripts/ghci038.hs | 3 + testsuite/tests/ghci/scripts/ghci038.script | 46 + testsuite/tests/ghci/scripts/ghci038.stderr | 4 + testsuite/tests/ghci/scripts/ghci038.stdout | 31 + testsuite/tests/ghci/scripts/ghci039.script | 3 + testsuite/tests/ghci/scripts/ghci039.stdout | 1 + testsuite/tests/ghci/scripts/ghci040.script | 4 + testsuite/tests/ghci/scripts/ghci040.stdout | 2 + testsuite/tests/ghci/scripts/ghci041.script | 4 + testsuite/tests/ghci/scripts/ghci041.stdout | 1 + testsuite/tests/ghci/scripts/ghci042.script | 10 + testsuite/tests/ghci/scripts/ghci042.stdout | 7 + testsuite/tests/ghci/scripts/ghci043.script | 11 + testsuite/tests/ghci/scripts/ghci043.stdout | 2 + testsuite/tests/ghci/scripts/ghci044.script | 10 + testsuite/tests/ghci/scripts/ghci044.stderr | 13 + testsuite/tests/ghci/scripts/ghci045.script | 6 + testsuite/tests/ghci/scripts/ghci045.stdout | 2 + testsuite/tests/ghci/scripts/ghci046.script | 22 + testsuite/tests/ghci/scripts/ghci046.stdout | 4 + testsuite/tests/ghci/scripts/ghci047.script | 40 + testsuite/tests/ghci/scripts/ghci047.stderr | 16 + testsuite/tests/ghci/scripts/ghci047.stdout | 4 + testsuite/tests/ghci/scripts/ghci048.script | 5 + testsuite/tests/ghci/scripts/ghci048.stderr | 10 + testsuite/tests/ghci/scripts/ghci049.script | 9 + testsuite/tests/ghci/scripts/ghci049.stdout | 2 + testsuite/tests/ghci/scripts/ghci050.script | 7 + testsuite/tests/ghci/scripts/ghci050.stderr | 13 + testsuite/tests/ghci/scripts/ghci050.stdout | 1 + testsuite/tests/ghci/scripts/ghci051.script | 18 + testsuite/tests/ghci/scripts/ghci051.stderr | 7 + testsuite/tests/ghci/scripts/ghci051.stdout | 11 + testsuite/tests/ghci/scripts/ghci052.script | 12 + testsuite/tests/ghci/scripts/ghci052.stderr | 32 + testsuite/tests/ghci/scripts/ghci052.stdout | 2 + testsuite/tests/ghci/scripts/ghci053.script | 12 + testsuite/tests/ghci/scripts/ghci053.stderr | 16 + testsuite/tests/ghci/scripts/ghci053.stdout | 4 + testsuite/tests/ghci/scripts/ghci054.script | 4 + testsuite/tests/ghci/scripts/ghci054.stdout | 1 + testsuite/tests/ghci/scripts/ghci055.script | 7 + testsuite/tests/ghci/scripts/ghci055.stdout | 3 + testsuite/tests/ghci/scripts/ghci056.script | 2 + testsuite/tests/ghci/scripts/ghci056.stdout | 1 + testsuite/tests/ghci/scripts/ghci056_c.c | 6 + testsuite/tests/ghci/scripts/ghci057.hs | 4 + testsuite/tests/ghci/scripts/ghci057.script | 27 + testsuite/tests/ghci/scripts/ghci057.stderr | 19 + testsuite/tests/ghci/scripts/ghci057.stdout | 54 + testsuite/tests/ghci/scripts/ghci058.script | 17 + testsuite/tests/ghci/scripts/ghci058.stdout | 4 + testsuite/tests/ghci/shell.hs | 9 + testsuite/tests/ghci/should_run/Makefile | 9 + testsuite/tests/ghci/should_run/T2589.hs | 8 + testsuite/tests/ghci/should_run/T2589.stdout | 1 + testsuite/tests/ghci/should_run/T2881.hs | 8 + testsuite/tests/ghci/should_run/T2881.stdout | 1 + testsuite/tests/ghci/should_run/T3171.stdout | 1 + testsuite/tests/ghci/should_run/T8377.hs | 14 + testsuite/tests/ghci/should_run/T8377.stdout | 1 + testsuite/tests/ghci/should_run/all.T | 22 + testsuite/tests/ghci/should_run/ghcirun001.hs | 30 + testsuite/tests/ghci/should_run/ghcirun001.stdout | 1 + testsuite/tests/ghci/should_run/ghcirun002.hs | 72 + testsuite/tests/ghci/should_run/ghcirun002.stdout | 1 + testsuite/tests/ghci/should_run/ghcirun003.hs | 50 + testsuite/tests/ghci/should_run/ghcirun003.stdout | 1 + testsuite/tests/ghci/should_run/ghcirun004.hs | 5007 +++++++ testsuite/tests/ghci/should_run/ghcirun004.stdout | 1 + testsuite/tests/haddock/Makefile | 3 + testsuite/tests/haddock/haddock_examples/Hidden.hs | 4 + testsuite/tests/haddock/haddock_examples/Makefile | 3 + testsuite/tests/haddock/haddock_examples/Test.hs | 407 + .../tests/haddock/haddock_examples/Visible.hs | 3 + .../haddock/haddock_examples/haddock.Test.stderr | 166 + testsuite/tests/haddock/haddock_examples/header.h | 5 + testsuite/tests/haddock/haddock_examples/test.T | 6 + .../haddock/should_compile_flag_haddock/Makefile | 3 + .../haddock/should_compile_flag_haddock/all.T | 33 + .../should_compile_flag_haddock/haddockA001.hs | 5 + .../should_compile_flag_haddock/haddockA001.stderr | 7 + .../should_compile_flag_haddock/haddockA002.hs | 5 + .../should_compile_flag_haddock/haddockA002.stderr | 7 + .../should_compile_flag_haddock/haddockA003.hs | 5 + .../should_compile_flag_haddock/haddockA003.stderr | 7 + .../should_compile_flag_haddock/haddockA004.hs | 8 + .../should_compile_flag_haddock/haddockA004.stderr | 7 + .../should_compile_flag_haddock/haddockA005.hs | 4 + .../should_compile_flag_haddock/haddockA005.stderr | 7 + .../should_compile_flag_haddock/haddockA006.hs | 6 + .../should_compile_flag_haddock/haddockA006.stderr | 6 + .../should_compile_flag_haddock/haddockA007.hs | 5 + .../should_compile_flag_haddock/haddockA007.stderr | 7 + .../should_compile_flag_haddock/haddockA008.hs | 7 + .../should_compile_flag_haddock/haddockA008.stderr | 7 + .../should_compile_flag_haddock/haddockA009.hs | 5 + .../should_compile_flag_haddock/haddockA009.stderr | 7 + .../should_compile_flag_haddock/haddockA010.hs | 5 + .../should_compile_flag_haddock/haddockA010.stderr | 7 + .../should_compile_flag_haddock/haddockA011.hs | 8 + .../should_compile_flag_haddock/haddockA011.stderr | 7 + .../should_compile_flag_haddock/haddockA012.hs | 11 + .../should_compile_flag_haddock/haddockA012.stderr | 11 + .../should_compile_flag_haddock/haddockA013.hs | 13 + .../should_compile_flag_haddock/haddockA013.stderr | 13 + .../should_compile_flag_haddock/haddockA014.hs | 5 + .../should_compile_flag_haddock/haddockA014.stderr | 8 + .../should_compile_flag_haddock/haddockA015.hs | 14 + .../should_compile_flag_haddock/haddockA015.stderr | 14 + .../should_compile_flag_haddock/haddockA016.hs | 4 + .../should_compile_flag_haddock/haddockA016.stderr | 6 + .../should_compile_flag_haddock/haddockA017.hs | 2 + .../should_compile_flag_haddock/haddockA017.stderr | 5 + .../should_compile_flag_haddock/haddockA018.hs | 4 + .../should_compile_flag_haddock/haddockA018.stderr | 6 + .../should_compile_flag_haddock/haddockA019.hs | 7 + .../should_compile_flag_haddock/haddockA019.stderr | 7 + .../should_compile_flag_haddock/haddockA020.hs | 15 + .../should_compile_flag_haddock/haddockA020.stderr | 8 + .../should_compile_flag_haddock/haddockA021.hs | 25 + .../should_compile_flag_haddock/haddockA021.stderr | 11 + .../should_compile_flag_haddock/haddockA022.hs | 11 + .../should_compile_flag_haddock/haddockA022.stderr | 9 + .../should_compile_flag_haddock/haddockA023.hs | 6 + .../should_compile_flag_haddock/haddockA023.stderr | 10 + .../should_compile_flag_haddock/haddockA024.hs | 5 + .../should_compile_flag_haddock/haddockA024.stderr | 7 + .../should_compile_flag_haddock/haddockA025.hs | 5 + .../should_compile_flag_haddock/haddockA025.stderr | 7 + .../should_compile_flag_haddock/haddockA026.hs | 6 + .../should_compile_flag_haddock/haddockA026.stderr | 10 + .../should_compile_flag_haddock/haddockA027.hs | 7 + .../should_compile_flag_haddock/haddockA027.stderr | 11 + .../should_compile_flag_haddock/haddockA028.hs | 8 + .../should_compile_flag_haddock/haddockA028.stderr | 9 + .../should_compile_flag_haddock/haddockA029.hs | 5 + .../should_compile_flag_haddock/haddockA029.stderr | 6 + .../should_compile_flag_haddock/haddockA030.hs | 10 + .../should_compile_flag_haddock/haddockA030.stderr | 6 + .../should_compile_flag_haddock/haddockA031.hs | 6 + .../should_compile_flag_haddock/haddockA031.stderr | 9 + .../should_compile_flag_haddock/haddockA032.hs | 8 + .../should_compile_flag_haddock/haddockA032.stderr | 10 + .../should_compile_flag_haddock/haddockA033.hs | 11 + .../should_compile_flag_haddock/haddockA033.stderr | 11 + .../haddock/should_compile_flag_nohaddock/Makefile | 3 + .../haddock/should_compile_flag_nohaddock/all.T | 4 + .../should_compile_flag_nohaddock/haddockB001.hs | 3 + .../should_compile_flag_nohaddock/haddockB002.hs | 3 + .../should_compile_flag_nohaddock/haddockB003.hs | 2 + .../should_compile_flag_nohaddock/haddockB004.hs | 17 + .../haddock/should_compile_noflag_haddock/Makefile | 3 + .../haddock/should_compile_noflag_haddock/all.T | 33 + .../should_compile_noflag_haddock/haddockC001.hs | 5 + .../should_compile_noflag_haddock/haddockC002.hs | 5 + .../should_compile_noflag_haddock/haddockC003.hs | 5 + .../should_compile_noflag_haddock/haddockC004.hs | 8 + .../should_compile_noflag_haddock/haddockC005.hs | 4 + .../should_compile_noflag_haddock/haddockC006.hs | 6 + .../should_compile_noflag_haddock/haddockC007.hs | 5 + .../should_compile_noflag_haddock/haddockC008.hs | 7 + .../should_compile_noflag_haddock/haddockC009.hs | 5 + .../should_compile_noflag_haddock/haddockC010.hs | 5 + .../should_compile_noflag_haddock/haddockC011.hs | 8 + .../should_compile_noflag_haddock/haddockC012.hs | 11 + .../should_compile_noflag_haddock/haddockC013.hs | 14 + .../should_compile_noflag_haddock/haddockC014.hs | 5 + .../should_compile_noflag_haddock/haddockC015.hs | 14 + .../should_compile_noflag_haddock/haddockC016.hs | 4 + .../should_compile_noflag_haddock/haddockC017.hs | 2 + .../should_compile_noflag_haddock/haddockC018.hs | 4 + .../should_compile_noflag_haddock/haddockC019.hs | 7 + .../should_compile_noflag_haddock/haddockC020.hs | 15 + .../should_compile_noflag_haddock/haddockC021.hs | 25 + .../should_compile_noflag_haddock/haddockC022.hs | 11 + .../should_compile_noflag_haddock/haddockC023.hs | 5 + .../should_compile_noflag_haddock/haddockC024.hs | 5 + .../should_compile_noflag_haddock/haddockC025.hs | 5 + .../should_compile_noflag_haddock/haddockC026.hs | 6 + .../should_compile_noflag_haddock/haddockC027.hs | 21 + .../should_compile_noflag_haddock/haddockC028.hs | 8 + .../should_compile_noflag_haddock/haddockC029.hs | 5 + .../should_compile_noflag_haddock/haddockC030.hs | 10 + .../should_compile_noflag_haddock/haddockC031.hs | 6 + .../should_compile_noflag_haddock/haddockC032.hs | 8 + .../haddockSimplUtilsBug.hs | 44 + .../should_compile_noflag_nohaddock/Makefile | 3 + .../haddock/should_compile_noflag_nohaddock/all.T | 4 + .../should_compile_noflag_nohaddock/haddockD001.hs | 3 + .../should_compile_noflag_nohaddock/haddockD002.hs | 3 + .../should_compile_noflag_nohaddock/haddockD003.hs | 2 + .../should_compile_noflag_nohaddock/haddockD004.hs | 17 + .../haddock/should_fail_flag_haddock/Makefile | 3 + .../tests/haddock/should_fail_flag_haddock/all.T | 4 + .../should_fail_flag_haddock/haddockE001.hs | 2 + .../should_fail_flag_haddock/haddockE001.stderr | 2 + .../should_fail_flag_haddock/haddockE002.hs | 6 + .../should_fail_flag_haddock/haddockE002.stderr | 2 + .../should_fail_flag_haddock/haddockE003.hs | 9 + .../should_fail_flag_haddock/haddockE003.stderr | 2 + .../should_fail_flag_haddock/haddockE004.hs | 3 + .../should_fail_flag_haddock/haddockE004.stderr | 2 + testsuite/tests/hsc2hs/Makefile | 30 + testsuite/tests/hsc2hs/T3837.hsc | 7 + testsuite/tests/hsc2hs/all.T | 27 + testsuite/tests/hsc2hs/hsc2hs001.hsc | 6 + testsuite/tests/hsc2hs/hsc2hs002.hsc | 6 + testsuite/tests/hsc2hs/hsc2hs003.hsc | 10 + testsuite/tests/hsc2hs/hsc2hs003.stdout | 1 + testsuite/tests/hsc2hs/hsc2hs004.hsc | 10 + testsuite/tests/hsc2hs/hsc2hs004.stdout | 1 + testsuite/tests/indexed-types/Makefile | 3 + .../tests/indexed-types/should_compile/ATLoop.hs | 22 + .../indexed-types/should_compile/ATLoop_help.hs | 10 + .../tests/indexed-types/should_compile/Class1.hs | 21 + .../tests/indexed-types/should_compile/Class2.hs | 15 + .../tests/indexed-types/should_compile/Class3.hs | 11 + .../indexed-types/should_compile/Class3.stderr | 5 + .../indexed-types/should_compile/ClassEqContext.hs | 5 + .../should_compile/ClassEqContext2.hs | 6 + .../should_compile/ClassEqContext3.hs | 8 + .../indexed-types/should_compile/ClosedFam1.hs | 9 + .../should_compile/ClosedFam1.hs-boot | 7 + .../indexed-types/should_compile/ClosedFam2.hs | 9 + .../should_compile/ClosedFam2.hs-boot | 5 + .../tests/indexed-types/should_compile/CoTest3.hs | 26 + .../tests/indexed-types/should_compile/Col.hs | 16 + .../tests/indexed-types/should_compile/Col2.hs | 14 + .../indexed-types/should_compile/ColGivenCheck.hs | 20 + .../indexed-types/should_compile/ColGivenCheck2.hs | 31 + .../indexed-types/should_compile/ColInference.hs | 19 + .../indexed-types/should_compile/ColInference2.hs | 17 + .../indexed-types/should_compile/ColInference3.hs | 44 + .../indexed-types/should_compile/ColInference4.hs | 17 + .../indexed-types/should_compile/ColInference5.hs | 17 + .../indexed-types/should_compile/ColInference6.hs | 13 + .../indexed-types/should_compile/DataFamDeriv.hs | 11 + .../tests/indexed-types/should_compile/Deriving.hs | 30 + .../should_compile/DerivingNewType.hs | 16 + .../tests/indexed-types/should_compile/Exp.hs | 10 + .../tests/indexed-types/should_compile/GADT1.hs | 27 + .../tests/indexed-types/should_compile/GADT10.hs | 44 + .../tests/indexed-types/should_compile/GADT11.hs | 20 + .../tests/indexed-types/should_compile/GADT12.hs | 38 + .../tests/indexed-types/should_compile/GADT13.hs | 8 + .../tests/indexed-types/should_compile/GADT14.hs | 11 + .../tests/indexed-types/should_compile/GADT2.hs | 14 + .../tests/indexed-types/should_compile/GADT3.hs | 29 + .../tests/indexed-types/should_compile/GADT4.hs | 13 + .../tests/indexed-types/should_compile/GADT5.hs | 14 + .../tests/indexed-types/should_compile/GADT6.hs | 12 + .../tests/indexed-types/should_compile/GADT7.hs | 15 + .../tests/indexed-types/should_compile/GADT8.hs | 12 + .../tests/indexed-types/should_compile/GADT9.hs | 16 + .../tests/indexed-types/should_compile/Gentle.hs | 52 + .../indexed-types/should_compile/GivenCheck.hs | 12 + .../should_compile/GivenCheckDecomp.hs | 11 + .../indexed-types/should_compile/GivenCheckSwap.hs | 12 + .../indexed-types/should_compile/GivenCheckTop.hs | 13 + testsuite/tests/indexed-types/should_compile/HO.hs | 18 + .../tests/indexed-types/should_compile/Imp.hs | 11 + .../indexed-types/should_compile/Ind2_help.hs | 14 + .../indexed-types/should_compile/IndTypesPerf.hs | 11 + .../should_compile/IndTypesPerfMerge.hs | 120 + .../tests/indexed-types/should_compile/Infix.hs | 9 + .../should_compile/InstContextNorm.hs | 36 + .../indexed-types/should_compile/InstEqContext.hs | 17 + .../indexed-types/should_compile/InstEqContext2.hs | 15 + .../indexed-types/should_compile/InstEqContext3.hs | 20 + .../tests/indexed-types/should_compile/Kind.hs | 10 + .../tests/indexed-types/should_compile/Makefile | 43 + .../tests/indexed-types/should_compile/NewTyCo1.hs | 9 + .../tests/indexed-types/should_compile/NewTyCo2.hs | 7 + .../indexed-types/should_compile/NonLinearLHS.hs | 38 + .../tests/indexed-types/should_compile/Numerals.hs | 29 + .../tests/indexed-types/should_compile/Overlap1.hs | 13 + .../indexed-types/should_compile/Overlap12.hs | 27 + .../indexed-types/should_compile/Overlap13.hs | 15 + .../indexed-types/should_compile/Overlap14.hs | 12 + .../tests/indexed-types/should_compile/Overlap2.hs | 13 + .../indexed-types/should_compile/OversatDecomp.hs | 12 + .../should_compile/PushedInAsGivens.hs | 24 + .../tests/indexed-types/should_compile/Records.hs | 41 + .../tests/indexed-types/should_compile/Refl.hs | 17 + .../tests/indexed-types/should_compile/Refl2.hs | 19 + .../should_compile/RelaxedExamples.hs | 13 + .../tests/indexed-types/should_compile/Roman1.hs | 41 + .../tests/indexed-types/should_compile/Rules1.hs | 24 + .../tests/indexed-types/should_compile/Simple1.hs | 13 + .../tests/indexed-types/should_compile/Simple10.hs | 10 + .../tests/indexed-types/should_compile/Simple11.hs | 16 + .../tests/indexed-types/should_compile/Simple12.hs | 17 + .../tests/indexed-types/should_compile/Simple13.hs | 18 + .../tests/indexed-types/should_compile/Simple14.hs | 24 + .../indexed-types/should_compile/Simple14.stderr | 18 + .../tests/indexed-types/should_compile/Simple15.hs | 25 + .../tests/indexed-types/should_compile/Simple16.hs | 13 + .../tests/indexed-types/should_compile/Simple17.hs | 9 + .../tests/indexed-types/should_compile/Simple18.hs | 10 + .../tests/indexed-types/should_compile/Simple19.hs | 10 + .../tests/indexed-types/should_compile/Simple2.hs | 41 + .../indexed-types/should_compile/Simple2.stderr | 31 + .../tests/indexed-types/should_compile/Simple20.hs | 9 + .../indexed-types/should_compile/Simple20.stderr | 4 + .../tests/indexed-types/should_compile/Simple21.hs | 18 + .../tests/indexed-types/should_compile/Simple22.hs | 15 + .../tests/indexed-types/should_compile/Simple23.hs | 6 + .../tests/indexed-types/should_compile/Simple24.hs | 13 + .../tests/indexed-types/should_compile/Simple3.hs | 9 + .../tests/indexed-types/should_compile/Simple4.hs | 9 + .../tests/indexed-types/should_compile/Simple5.hs | 16 + .../tests/indexed-types/should_compile/Simple6.hs | 17 + .../tests/indexed-types/should_compile/Simple7.hs | 10 + .../tests/indexed-types/should_compile/Simple8.hs | 15 + .../tests/indexed-types/should_compile/Simple9.hs | 18 + .../tests/indexed-types/should_compile/T1769.hs | 12 + .../tests/indexed-types/should_compile/T1981.hs | 8 + .../tests/indexed-types/should_compile/T2102.hs | 19 + .../tests/indexed-types/should_compile/T2203b.hs | 26 + .../tests/indexed-types/should_compile/T2219.hs | 28 + .../tests/indexed-types/should_compile/T2238.hs | 39 + .../tests/indexed-types/should_compile/T2291.hs | 15 + .../tests/indexed-types/should_compile/T2448.hs | 17 + .../tests/indexed-types/should_compile/T2627.hs | 22 + .../tests/indexed-types/should_compile/T2639.hs | 17 + .../tests/indexed-types/should_compile/T2715.hs | 32 + .../tests/indexed-types/should_compile/T2767.hs | 23 + .../tests/indexed-types/should_compile/T2850.hs | 23 + .../tests/indexed-types/should_compile/T2944.hs | 12 + .../tests/indexed-types/should_compile/T3017.hs | 20 + .../indexed-types/should_compile/T3017.stderr | 26 + .../tests/indexed-types/should_compile/T3023.hs | 17 + .../indexed-types/should_compile/T3023.stderr | 4 + .../tests/indexed-types/should_compile/T3208a.hs | 14 + .../tests/indexed-types/should_compile/T3208b.hs | 33 + .../indexed-types/should_compile/T3208b.stderr | 30 + .../tests/indexed-types/should_compile/T3220.hs | 23 + .../tests/indexed-types/should_compile/T3418.hs | 4 + .../indexed-types/should_compile/T3418.stderr | 3 + .../tests/indexed-types/should_compile/T3423.hs | 12 + .../tests/indexed-types/should_compile/T3460.hs | 14 + .../tests/indexed-types/should_compile/T3484.hs | 42 + .../tests/indexed-types/should_compile/T3590.hs | 22 + .../tests/indexed-types/should_compile/T3787.hs | 475 + .../tests/indexed-types/should_compile/T3826.hs | 15 + .../tests/indexed-types/should_compile/T3851.hs | 24 + .../tests/indexed-types/should_compile/T4120.hs | 26 + .../tests/indexed-types/should_compile/T4160.hs | 18 + .../tests/indexed-types/should_compile/T4178.hs | 35 + .../tests/indexed-types/should_compile/T4185.hs | 46 + .../tests/indexed-types/should_compile/T4200.hs | 12 + .../tests/indexed-types/should_compile/T4338.hs | 23 + .../tests/indexed-types/should_compile/T4356.hs | 8 + .../tests/indexed-types/should_compile/T4358.hs | 11 + .../tests/indexed-types/should_compile/T4484.hs | 30 + .../tests/indexed-types/should_compile/T4492.hs | 12 + .../tests/indexed-types/should_compile/T4494.hs | 12 + .../tests/indexed-types/should_compile/T4497.hs | 15 + .../tests/indexed-types/should_compile/T4935.hs | 24 + .../tests/indexed-types/should_compile/T4981-V1.hs | 34 + .../tests/indexed-types/should_compile/T4981-V2.hs | 31 + .../tests/indexed-types/should_compile/T4981-V3.hs | 44 + .../tests/indexed-types/should_compile/T5002.hs | 29 + .../tests/indexed-types/should_compile/T5591a.hs | 25 + .../tests/indexed-types/should_compile/T5591b.hs | 12 + .../tests/indexed-types/should_compile/T5955.hs | 7 + .../tests/indexed-types/should_compile/T5955a.hs | 13 + .../tests/indexed-types/should_compile/T6088.hs | 18 + .../tests/indexed-types/should_compile/T6152.hs | 14 + .../tests/indexed-types/should_compile/T7082.hs | 13 + .../tests/indexed-types/should_compile/T7156.hs | 8 + .../tests/indexed-types/should_compile/T7280.hs | 13 + .../tests/indexed-types/should_compile/T7282.hs | 9 + .../tests/indexed-types/should_compile/T7474.hs | 17 + .../tests/indexed-types/should_compile/T7489.hs | 12 + .../tests/indexed-types/should_compile/T7585.hs | 20 + .../tests/indexed-types/should_compile/T7804.hs | 10 + .../tests/indexed-types/should_compile/T7837.hs | 24 + .../indexed-types/should_compile/T7837.stderr | 3 + .../tests/indexed-types/should_compile/T8002.hs | 4 + .../tests/indexed-types/should_compile/T8002a.hs | 13 + .../tests/indexed-types/should_compile/T8002b.hs | 5 + .../tests/indexed-types/should_compile/T8011.hs | 9 + .../tests/indexed-types/should_compile/T8011a.hs | 8 + .../tests/indexed-types/should_compile/T8018.hs | 8 + .../tests/indexed-types/should_compile/T8020.hs | 17 + .../tests/indexed-types/should_compile/T8500.hs | 10 + .../tests/indexed-types/should_compile/T8500a.hs | 7 + .../tests/indexed-types/should_compile/TF_GADT.hs | 21 + testsuite/tests/indexed-types/should_compile/all.T | 240 + .../indexed-types/should_compile/impexp.stderr | 2 + .../tests/indexed-types/should_compile/ind1.hs | 15 + .../tests/indexed-types/should_compile/ind2.hs | 9 + .../tests/indexed-types/should_fail/ClosedFam3.hs | 16 + .../indexed-types/should_fail/ClosedFam3.hs-boot | 13 + .../indexed-types/should_fail/ClosedFam3.stderr | 24 + .../tests/indexed-types/should_fail/ClosedFam4.hs | 5 + .../indexed-types/should_fail/ClosedFam4.stderr | 5 + .../indexed-types/should_fail/DerivUnsatFam.hs | 8 + .../indexed-types/should_fail/DerivUnsatFam.stderr | 5 + .../indexed-types/should_fail/ExtraTcsUntch.hs | 54 + .../indexed-types/should_fail/ExtraTcsUntch.stderr | 10 + .../tests/indexed-types/should_fail/GADTwrong1.hs | 12 + .../indexed-types/should_fail/GADTwrong1.stderr | 20 + testsuite/tests/indexed-types/should_fail/Makefile | 18 + .../tests/indexed-types/should_fail/NoGood.hs | 5 + .../tests/indexed-types/should_fail/NoGood.stderr | 5 + .../tests/indexed-types/should_fail/NoMatchErr.hs | 21 + .../indexed-types/should_fail/NoMatchErr.stderr | 14 + .../indexed-types/should_fail/NonLinearSigErr.hs | 8 + .../should_fail/NotRelaxedExamples.hs | 11 + .../should_fail/NotRelaxedExamples.stderr | 18 + .../tests/indexed-types/should_fail/Over.stderr | 10 + testsuite/tests/indexed-types/should_fail/OverA.hs | 8 + testsuite/tests/indexed-types/should_fail/OverB.hs | 9 + testsuite/tests/indexed-types/should_fail/OverC.hs | 9 + testsuite/tests/indexed-types/should_fail/OverD.hs | 3 + .../tests/indexed-types/should_fail/Overlap10.hs | 14 + .../indexed-types/should_fail/Overlap10.stderr | 8 + .../tests/indexed-types/should_fail/Overlap11.hs | 14 + .../indexed-types/should_fail/Overlap11.stderr | 8 + .../tests/indexed-types/should_fail/Overlap15.hs | 17 + .../indexed-types/should_fail/Overlap15.stderr | 7 + .../tests/indexed-types/should_fail/Overlap3.hs | 14 + .../indexed-types/should_fail/Overlap3.stderr | 4 + .../tests/indexed-types/should_fail/Overlap4.hs | 8 + .../indexed-types/should_fail/Overlap4.stderr | 5 + .../tests/indexed-types/should_fail/Overlap5.hs | 9 + .../indexed-types/should_fail/Overlap5.stderr | 5 + .../tests/indexed-types/should_fail/Overlap6.hs | 15 + .../indexed-types/should_fail/Overlap6.stderr | 13 + .../tests/indexed-types/should_fail/Overlap7.hs | 9 + .../indexed-types/should_fail/Overlap7.stderr | 4 + .../tests/indexed-types/should_fail/Overlap9.hs | 13 + .../indexed-types/should_fail/Overlap9.stderr | 11 + .../indexed-types/should_fail/SimpleFail10.hs | 13 + .../indexed-types/should_fail/SimpleFail11a.hs | 13 + .../indexed-types/should_fail/SimpleFail11a.stderr | 10 + .../indexed-types/should_fail/SimpleFail11b.hs | 18 + .../indexed-types/should_fail/SimpleFail11b.stderr | 10 + .../indexed-types/should_fail/SimpleFail11c.hs | 21 + .../indexed-types/should_fail/SimpleFail11c.stderr | 10 + .../indexed-types/should_fail/SimpleFail11d.hs | 10 + .../indexed-types/should_fail/SimpleFail11d.stderr | 5 + .../indexed-types/should_fail/SimpleFail12.hs | 9 + .../indexed-types/should_fail/SimpleFail12.stderr | 4 + .../indexed-types/should_fail/SimpleFail13.hs | 13 + .../indexed-types/should_fail/SimpleFail13.stderr | 8 + .../indexed-types/should_fail/SimpleFail14.hs | 6 + .../indexed-types/should_fail/SimpleFail14.stderr | 6 + .../indexed-types/should_fail/SimpleFail15.hs | 6 + .../indexed-types/should_fail/SimpleFail15.stderr | 6 + .../indexed-types/should_fail/SimpleFail16.hs | 11 + .../indexed-types/should_fail/SimpleFail16.stderr | 9 + .../indexed-types/should_fail/SimpleFail1a.hs | 4 + .../indexed-types/should_fail/SimpleFail1a.stderr | 4 + .../indexed-types/should_fail/SimpleFail1b.hs | 4 + .../indexed-types/should_fail/SimpleFail1b.stderr | 4 + .../indexed-types/should_fail/SimpleFail2a.hs | 14 + .../indexed-types/should_fail/SimpleFail2a.stderr | 6 + .../indexed-types/should_fail/SimpleFail2b.hs | 12 + .../indexed-types/should_fail/SimpleFail2b.stderr | 5 + .../indexed-types/should_fail/SimpleFail3a.hs | 10 + .../indexed-types/should_fail/SimpleFail3a.stderr | 5 + .../indexed-types/should_fail/SimpleFail3b.stderr | 3 + .../tests/indexed-types/should_fail/SimpleFail4.hs | 8 + .../indexed-types/should_fail/SimpleFail4.stderr | 6 + .../indexed-types/should_fail/SimpleFail5a.hs | 31 + .../indexed-types/should_fail/SimpleFail5a.stderr | 12 + .../indexed-types/should_fail/SimpleFail5b.hs | 31 + .../indexed-types/should_fail/SimpleFail5b.stderr | 7 + .../tests/indexed-types/should_fail/SimpleFail6.hs | 7 + .../indexed-types/should_fail/SimpleFail6.stderr | 5 + .../tests/indexed-types/should_fail/SimpleFail7.hs | 8 + .../indexed-types/should_fail/SimpleFail7.stderr | 4 + .../tests/indexed-types/should_fail/SimpleFail8.hs | 10 + .../indexed-types/should_fail/SimpleFail8.stderr | 6 + .../tests/indexed-types/should_fail/SimpleFail9.hs | 15 + .../indexed-types/should_fail/SkolemOccursLoop.hs | 32 + .../should_fail/SkolemOccursLoop.stderr | 1 + .../tests/indexed-types/should_fail/T1897b.hs | 16 + .../tests/indexed-types/should_fail/T1897b.stderr | 14 + testsuite/tests/indexed-types/should_fail/T1900.hs | 73 + .../tests/indexed-types/should_fail/T1900.stderr | 14 + .../tests/indexed-types/should_fail/T1987b.stderr | 1 + testsuite/tests/indexed-types/should_fail/T2157.hs | 7 + .../tests/indexed-types/should_fail/T2157.stderr | 4 + .../tests/indexed-types/should_fail/T2203a.hs | 15 + .../tests/indexed-types/should_fail/T2203a.stderr | 5 + testsuite/tests/indexed-types/should_fail/T2239.hs | 51 + .../tests/indexed-types/should_fail/T2239.stderr | 28 + .../tests/indexed-types/should_fail/T2334A.hs | 16 + .../tests/indexed-types/should_fail/T2334A.stderr | 17 + testsuite/tests/indexed-types/should_fail/T2544.hs | 15 + .../tests/indexed-types/should_fail/T2544.stderr | 26 + .../tests/indexed-types/should_fail/T2627b.hs | 20 + .../tests/indexed-types/should_fail/T2627b.stderr | 8 + testsuite/tests/indexed-types/should_fail/T2664.hs | 31 + .../tests/indexed-types/should_fail/T2664.stderr | 23 + .../tests/indexed-types/should_fail/T2664a.hs | 30 + testsuite/tests/indexed-types/should_fail/T2677.hs | 7 + .../tests/indexed-types/should_fail/T2677.stderr | 5 + testsuite/tests/indexed-types/should_fail/T2693.hs | 31 + .../tests/indexed-types/should_fail/T2693.stderr | 37 + testsuite/tests/indexed-types/should_fail/T2888.hs | 7 + testsuite/tests/indexed-types/should_fail/T3092.hs | 9 + .../tests/indexed-types/should_fail/T3092.stderr | 10 + .../tests/indexed-types/should_fail/T3330a.hs | 48 + .../tests/indexed-types/should_fail/T3330a.stderr | 44 + .../tests/indexed-types/should_fail/T3330b.hs | 19 + .../tests/indexed-types/should_fail/T3330b.stderr | 5 + .../tests/indexed-types/should_fail/T3330c.hs | 58 + .../tests/indexed-types/should_fail/T3330c.stderr | 24 + testsuite/tests/indexed-types/should_fail/T3440.hs | 11 + .../tests/indexed-types/should_fail/T3440.stderr | 22 + .../tests/indexed-types/should_fail/T4093a.hs | 8 + .../tests/indexed-types/should_fail/T4093a.stderr | 14 + .../tests/indexed-types/should_fail/T4093b.hs | 40 + .../tests/indexed-types/should_fail/T4093b.stderr | 41 + testsuite/tests/indexed-types/should_fail/T4099.hs | 14 + .../tests/indexed-types/should_fail/T4099.stderr | 21 + testsuite/tests/indexed-types/should_fail/T4174.hs | 60 + .../tests/indexed-types/should_fail/T4174.stderr | 7 + .../indexed-types/should_fail/T4174.stderr-ghc-7.0 | 7 + testsuite/tests/indexed-types/should_fail/T4179.hs | 26 + .../tests/indexed-types/should_fail/T4179.stderr | 20 + testsuite/tests/indexed-types/should_fail/T4246.hs | 15 + .../tests/indexed-types/should_fail/T4246.stderr | 10 + testsuite/tests/indexed-types/should_fail/T4254.hs | 21 + testsuite/tests/indexed-types/should_fail/T4272.hs | 26 + .../tests/indexed-types/should_fail/T4272.stderr | 20 + testsuite/tests/indexed-types/should_fail/T4485.hs | 66 + .../tests/indexed-types/should_fail/T4485.stderr | 30 + testsuite/tests/indexed-types/should_fail/T5439.hs | 255 + .../tests/indexed-types/should_fail/T5439.stderr | 25 + testsuite/tests/indexed-types/should_fail/T5515.hs | 17 + .../tests/indexed-types/should_fail/T5515.stderr | 8 + testsuite/tests/indexed-types/should_fail/T5934.hs | 14 + .../tests/indexed-types/should_fail/T5934.stderr | 7 + testsuite/tests/indexed-types/should_fail/T6123.hs | 10 + .../tests/indexed-types/should_fail/T6123.stderr | 7 + testsuite/tests/indexed-types/should_fail/T7010.hs | 64 + .../tests/indexed-types/should_fail/T7010.stderr | 7 + testsuite/tests/indexed-types/should_fail/T7194.hs | 20 + .../tests/indexed-types/should_fail/T7194.stderr | 13 + testsuite/tests/indexed-types/should_fail/T7354.hs | 32 + .../tests/indexed-types/should_fail/T7354.stderr | 10 + .../tests/indexed-types/should_fail/T7354a.hs | 7 + .../tests/indexed-types/should_fail/T7354a.stderr | 6 + .../tests/indexed-types/should_fail/T7354b.hs | 7 + testsuite/tests/indexed-types/should_fail/T7536.hs | 9 + .../tests/indexed-types/should_fail/T7536.stderr | 5 + testsuite/tests/indexed-types/should_fail/T7729.hs | 28 + .../tests/indexed-types/should_fail/T7729.stderr | 16 + .../tests/indexed-types/should_fail/T7729a.hs | 28 + .../tests/indexed-types/should_fail/T7729a.stderr | 17 + testsuite/tests/indexed-types/should_fail/T7786.hs | 90 + .../tests/indexed-types/should_fail/T7786.stderr | 13 + testsuite/tests/indexed-types/should_fail/T7938.hs | 12 + .../tests/indexed-types/should_fail/T7938.stderr | 6 + testsuite/tests/indexed-types/should_fail/T7967.hs | 31 + .../tests/indexed-types/should_fail/T7967.stderr | 7 + testsuite/tests/indexed-types/should_fail/T8129.hs | 9 + .../tests/indexed-types/should_fail/T8129.stdout | 2 + testsuite/tests/indexed-types/should_fail/T8155.hs | 30 + .../tests/indexed-types/should_fail/T8155.stderr | 9 + testsuite/tests/indexed-types/should_fail/T8227.hs | 37 + .../tests/indexed-types/should_fail/T8227.stderr | 15 + .../tests/indexed-types/should_fail/T8227a.hs | 7 + testsuite/tests/indexed-types/should_fail/T8368.hs | 10 + .../tests/indexed-types/should_fail/T8368.stderr | 6 + .../tests/indexed-types/should_fail/T8368a.hs | 8 + .../tests/indexed-types/should_fail/T8368a.stderr | 6 + testsuite/tests/indexed-types/should_fail/T8518.hs | 17 + .../tests/indexed-types/should_fail/T8518.stderr | 16 + .../tests/indexed-types/should_fail/TyFamArity1.hs | 4 + .../indexed-types/should_fail/TyFamArity1.stderr | 4 + .../tests/indexed-types/should_fail/TyFamArity2.hs | 4 + .../indexed-types/should_fail/TyFamArity2.stderr | 4 + .../tests/indexed-types/should_fail/TyFamUndec.hs | 8 + .../indexed-types/should_fail/TyFamUndec.stderr | 18 + testsuite/tests/indexed-types/should_fail/all.T | 122 + .../tests/indexed-types/should_run/GMapAssoc.hs | 67 + .../indexed-types/should_run/GMapAssoc.stdout | 1 + .../tests/indexed-types/should_run/GMapTop.hs | 69 + .../tests/indexed-types/should_run/GMapTop.stdout | 1 + testsuite/tests/indexed-types/should_run/Makefile | 3 + testsuite/tests/indexed-types/should_run/T2985.hs | 13 + .../tests/indexed-types/should_run/T2985.stdout | 1 + testsuite/tests/indexed-types/should_run/T4235.hs | 30 + .../tests/indexed-types/should_run/T4235.stdout | 3 + testsuite/tests/indexed-types/should_run/T5719.hs | 28 + .../tests/indexed-types/should_run/T5719.stdout | 2 + testsuite/tests/indexed-types/should_run/all.T | 9 + testsuite/tests/layout/Makefile | 15 + testsuite/tests/layout/all.T | 57 + testsuite/tests/layout/layout001.hs | 6 + testsuite/tests/layout/layout001.stdout | 9 + testsuite/tests/layout/layout002.hs | 5 + testsuite/tests/layout/layout002.stdout | 3 + testsuite/tests/layout/layout003.hs | 12 + testsuite/tests/layout/layout003.stdout | 9 + testsuite/tests/layout/layout004.hs | 10 + testsuite/tests/layout/layout004.stdout | 7 + testsuite/tests/layout/layout005.hs | 10 + testsuite/tests/layout/layout005.stdout | 3 + testsuite/tests/layout/layout006.hs | 13 + testsuite/tests/layout/layout006.stdout | 9 + testsuite/tests/layout/layout007.hs | 11 + testsuite/tests/layout/layout007.stdout | 3 + testsuite/tests/layout/layout008.hs | 22 + testsuite/tests/layout/layout008.stdout | 3 + testsuite/tests/layout/layout009.hs | 6 + testsuite/tests/layout/layout009.stdout | 3 + testsuite/tests/lib/Makefile | 3 + .../tests/lib/integer/IntegerConversionRules.hs | 20 + testsuite/tests/lib/integer/Makefile | 60 + testsuite/tests/lib/integer/all.T | 19 + testsuite/tests/lib/integer/fromToInteger.hs | 14 + testsuite/tests/lib/integer/gcdInteger.hs | 17 + testsuite/tests/lib/integer/gcdInteger.stdout | 1 + .../tests/lib/integer/gcdInteger.stdout-ws-32 | 1 + testsuite/tests/lib/integer/integerBits.hs | 134 + testsuite/tests/lib/integer/integerBits.stdout | 2 + .../tests/lib/integer/integerConstantFolding.hs | 219 + .../lib/integer/integerConstantFolding.stdout | 55 + testsuite/tests/lib/integer/integerConversions.hs | 80 + .../tests/lib/integer/integerConversions.stdout | 299 + .../lib/integer/integerConversions.stdout-ws-64 | 299 + testsuite/tests/lib/integer/integerGmpInternals.hs | 163 + .../tests/lib/integer/integerGmpInternals.stdout | 39 + testsuite/tests/llvm/Makefile | 3 + testsuite/tests/llvm/should_compile/Makefile | 3 + testsuite/tests/llvm/should_compile/T5054.hs | 55 + testsuite/tests/llvm/should_compile/T5054_2.hs | 157 + testsuite/tests/llvm/should_compile/T5486.hs | 124 + testsuite/tests/llvm/should_compile/T5681.hs | 14 + testsuite/tests/llvm/should_compile/T6158.hs | 11 + testsuite/tests/llvm/should_compile/T7571.cmm | 11 + testsuite/tests/llvm/should_compile/T7575.hs | 16 + testsuite/tests/llvm/should_compile/T8131.cmm | 7 + testsuite/tests/llvm/should_compile/all.T | 15 + testsuite/tests/mdo/Makefile | 3 + testsuite/tests/mdo/should_compile/Makefile | 3 + testsuite/tests/mdo/should_compile/all.T | 8 + testsuite/tests/mdo/should_compile/mdo001.hs | 36 + testsuite/tests/mdo/should_compile/mdo001.stdout | 5 + testsuite/tests/mdo/should_compile/mdo002.hs | 23 + testsuite/tests/mdo/should_compile/mdo002.stdout | 1 + testsuite/tests/mdo/should_compile/mdo003.hs | 16 + testsuite/tests/mdo/should_compile/mdo003.stdout | 1 + testsuite/tests/mdo/should_compile/mdo004.hs | 17 + testsuite/tests/mdo/should_compile/mdo004.stdout | 1 + testsuite/tests/mdo/should_compile/mdo005.hs | 15 + testsuite/tests/mdo/should_compile/mdo005.stdout | 1 + testsuite/tests/mdo/should_compile/mdo006.hs | 17 + testsuite/tests/mdo/should_fail/Makefile | 3 + testsuite/tests/mdo/should_fail/all.T | 8 + testsuite/tests/mdo/should_fail/mdofail001.hs | 16 + testsuite/tests/mdo/should_fail/mdofail001.stderr | 6 + .../mdo/should_fail/mdofail001.stderr-ghc-7.0 | 8 + .../tests/mdo/should_fail/mdofail001.stderr-hugs | 1 + testsuite/tests/mdo/should_fail/mdofail002.hs | 15 + testsuite/tests/mdo/should_fail/mdofail002.stderr | 5 + .../mdo/should_fail/mdofail002.stderr-ghc-7.0 | 5 + .../tests/mdo/should_fail/mdofail002.stderr-hugs | 1 + testsuite/tests/mdo/should_fail/mdofail003.hs | 15 + testsuite/tests/mdo/should_fail/mdofail003.stderr | 5 + .../mdo/should_fail/mdofail003.stderr-ghc-7.0 | 5 + .../tests/mdo/should_fail/mdofail003.stderr-hugs | 1 + testsuite/tests/mdo/should_fail/mdofail004.hs | 32 + .../mdo/should_fail/mdofail004.stderr-ghc-7.0 | 7 + .../tests/mdo/should_fail/mdofail004.stderr-hugs | 1 + testsuite/tests/mdo/should_fail/mdofail005.hs | 12 + testsuite/tests/mdo/should_fail/mdofail005.stderr | 2 + .../tests/mdo/should_fail/mdofail005.stderr-hugs | 1 + testsuite/tests/mdo/should_fail/mdofail006.hs | 12 + testsuite/tests/mdo/should_fail/mdofail006.stderr | 1 + testsuite/tests/mdo/should_run/Makefile | 3 + testsuite/tests/mdo/should_run/all.T | 7 + testsuite/tests/mdo/should_run/mdorun001.hs | 33 + testsuite/tests/mdo/should_run/mdorun001.stdout | 5 + testsuite/tests/mdo/should_run/mdorun002.hs | 56 + testsuite/tests/mdo/should_run/mdorun002.stdout | 1 + testsuite/tests/mdo/should_run/mdorun003.hs | 8 + testsuite/tests/mdo/should_run/mdorun003.stdout | 2 + testsuite/tests/mdo/should_run/mdorun004.hs | 10 + testsuite/tests/mdo/should_run/mdorun004.stdout | 2 + testsuite/tests/mdo/should_run/mdorun005.hs | 11 + testsuite/tests/mdo/should_run/mdorun005.stdout | 2 + testsuite/tests/module/Makefile | 70 + testsuite/tests/module/Mod101_AuxA.hs | 5 + testsuite/tests/module/Mod101_AuxB.hs | 6 + testsuite/tests/module/Mod102_AuxA.hs | 9 + testsuite/tests/module/Mod102_AuxB.hs | 6 + testsuite/tests/module/Mod114_Help.hs | 1 + testsuite/tests/module/Mod115_A.hs | 11 + testsuite/tests/module/Mod115_B.hs | 4 + testsuite/tests/module/Mod117_A.hs | 5 + testsuite/tests/module/Mod117_B.hs | 4 + testsuite/tests/module/Mod118_A.hs | 11 + testsuite/tests/module/Mod118_B.hs | 5 + testsuite/tests/module/Mod119_A.hs | 2 + testsuite/tests/module/Mod119_B.hs | 2 + testsuite/tests/module/Mod120_A.hs | 3 + testsuite/tests/module/Mod121_A.hs | 5 + testsuite/tests/module/Mod122_A.hs | 3 + testsuite/tests/module/Mod123_A.hs | 3 + testsuite/tests/module/Mod124_A.hs | 3 + testsuite/tests/module/Mod125_A.hs | 3 + testsuite/tests/module/Mod126_A.hs | 6 + testsuite/tests/module/Mod127_A.hs | 6 + testsuite/tests/module/Mod128_A.hs | 5 + testsuite/tests/module/Mod131_A.hs | 4 + testsuite/tests/module/Mod131_B.hs | 6 + testsuite/tests/module/Mod132_A.hs | 3 + testsuite/tests/module/Mod132_B.hs | 5 + testsuite/tests/module/Mod136_A.hs | 3 + testsuite/tests/module/Mod137_A.hs | 6 + testsuite/tests/module/Mod138_A.hs | 6 + testsuite/tests/module/Mod139_A.hs | 14 + testsuite/tests/module/Mod139_B.hs | 5 + testsuite/tests/module/Mod140_A.hs | 3 + testsuite/tests/module/Mod141_A.hs | 7 + testsuite/tests/module/Mod142_A.hs | 3 + testsuite/tests/module/Mod143_A.hs | 4 + testsuite/tests/module/Mod144_A.hs | 4 + testsuite/tests/module/Mod145_A.hs | 4 + testsuite/tests/module/Mod147_A.hs | 3 + testsuite/tests/module/Mod157_A.hs | 4 + testsuite/tests/module/Mod157_B.hs | 3 + testsuite/tests/module/Mod157_C.hs | 3 + testsuite/tests/module/Mod157_D.hs | 5 + testsuite/tests/module/Mod159_A.hs | 13 + testsuite/tests/module/Mod159_B.hs | 3 + testsuite/tests/module/Mod159_C.hs | 3 + testsuite/tests/module/Mod159_D.hs | 4 + testsuite/tests/module/Mod162_A.hs | 3 + testsuite/tests/module/Mod163_A.hs | 3 + testsuite/tests/module/Mod164_A.hs | 3 + testsuite/tests/module/Mod164_B.hs | 3 + testsuite/tests/module/Mod170_A.hs | 3 + testsuite/tests/module/Mod171_A.hs | 4 + testsuite/tests/module/Mod171_B.hs | 5 + testsuite/tests/module/Mod172_B.hs | 3 + testsuite/tests/module/Mod172_C.hs | 4 + testsuite/tests/module/Mod173_Aux.hs | 9 + testsuite/tests/module/Mod178_2.hs | 5 + testsuite/tests/module/Mod179_A.hs | 5 + testsuite/tests/module/Mod180_A.hs | 4 + testsuite/tests/module/Mod180_B.hs | 5 + testsuite/tests/module/T1074.hs | 8 + testsuite/tests/module/T1074.stderr | 5 + testsuite/tests/module/T1074a.hs | 28 + testsuite/tests/module/T1148.hs | 19 + testsuite/tests/module/T2267.hs | 12 + testsuite/tests/module/T3776.hs | 12 + testsuite/tests/module/T414.hs | 3 + testsuite/tests/module/T414.stderr | 2 + testsuite/tests/module/T414a.hs | 2 + testsuite/tests/module/T414b.hs | 2 + testsuite/tests/module/all.T | 336 + testsuite/tests/module/base01/GHC/Base.hs | 25 + testsuite/tests/module/base01/GHC/Foo.hs | 7 + testsuite/tests/module/base01/Makefile | 14 + testsuite/tests/module/base01/all.T | 9 + testsuite/tests/module/base01/base01.stdout | 1 + testsuite/tests/module/convert-tests.sh | 12 + testsuite/tests/module/mod1.hs | 3 + testsuite/tests/module/mod1.stderr | 4 + testsuite/tests/module/mod1.stderr-hugs | 1 + testsuite/tests/module/mod10.hs | 3 + testsuite/tests/module/mod10.stderr | 2 + testsuite/tests/module/mod10.stderr-hugs | 1 + testsuite/tests/module/mod100.hs | 28 + testsuite/tests/module/mod101.hs | 8 + testsuite/tests/module/mod101.stderr | 4 + testsuite/tests/module/mod101.stderr-hugs | 1 + testsuite/tests/module/mod102.hs | 8 + testsuite/tests/module/mod102.stderr | 4 + testsuite/tests/module/mod102.stderr-hugs | 1 + testsuite/tests/module/mod103.hs | 12 + testsuite/tests/module/mod104.hs | 6 + testsuite/tests/module/mod105.hs | 9 + testsuite/tests/module/mod106.hs | 8 + testsuite/tests/module/mod107.hs | 6 + testsuite/tests/module/mod108.hs | 6 + testsuite/tests/module/mod109.hs | 7 + testsuite/tests/module/mod11.hs | 2 + testsuite/tests/module/mod110.hs | 15 + testsuite/tests/module/mod110.stderr | 7 + testsuite/tests/module/mod110.stderr-hugs | 2 + testsuite/tests/module/mod111.hs | 12 + testsuite/tests/module/mod112.hs | 12 + testsuite/tests/module/mod113.hs | 7 + testsuite/tests/module/mod114.hs | 4 + testsuite/tests/module/mod114.stderr | 2 + testsuite/tests/module/mod114.stderr-hugs | 1 + testsuite/tests/module/mod115.hs | 7 + testsuite/tests/module/mod116.hs | 5 + testsuite/tests/module/mod116.stderr | 2 + testsuite/tests/module/mod116.stderr-hugs | 1 + testsuite/tests/module/mod117.hs | 7 + testsuite/tests/module/mod118.hs | 6 + testsuite/tests/module/mod119.hs | 3 + testsuite/tests/module/mod12.hs | 5 + testsuite/tests/module/mod120.hs | 5 + testsuite/tests/module/mod120.stderr | 2 + testsuite/tests/module/mod120.stderr-hugs | 1 + testsuite/tests/module/mod121.hs | 5 + testsuite/tests/module/mod121.stderr | 4 + testsuite/tests/module/mod121.stderr-hugs | 1 + testsuite/tests/module/mod122.hs | 6 + testsuite/tests/module/mod122.stderr | 2 + testsuite/tests/module/mod122.stderr-hugs | 1 + testsuite/tests/module/mod123.hs | 6 + testsuite/tests/module/mod123.stderr | 2 + testsuite/tests/module/mod123.stderr-hugs | 1 + testsuite/tests/module/mod124.hs | 7 + testsuite/tests/module/mod124.stderr | 2 + testsuite/tests/module/mod124.stderr-hugs | 1 + testsuite/tests/module/mod125.hs | 7 + testsuite/tests/module/mod125.stderr | 2 + testsuite/tests/module/mod125.stderr-hugs | 1 + testsuite/tests/module/mod126.hs | 7 + testsuite/tests/module/mod126.stderr | 2 + testsuite/tests/module/mod126.stderr-hugs | 1 + testsuite/tests/module/mod127.hs | 7 + testsuite/tests/module/mod127.stderr | 2 + testsuite/tests/module/mod127.stderr-hugs | 1 + testsuite/tests/module/mod128.hs | 5 + testsuite/tests/module/mod128.stderr-ghc | 2 + testsuite/tests/module/mod129.hs | 8 + testsuite/tests/module/mod13.hs | 5 + testsuite/tests/module/mod130.hs | 7 + testsuite/tests/module/mod130.stderr | 2 + testsuite/tests/module/mod130.stderr-hugs | 1 + testsuite/tests/module/mod131.hs | 5 + testsuite/tests/module/mod131.stderr | 9 + testsuite/tests/module/mod131.stderr-hugs | 2 + testsuite/tests/module/mod132.hs | 6 + testsuite/tests/module/mod132.stderr | 2 + testsuite/tests/module/mod132.stderr-hugs | 1 + testsuite/tests/module/mod133.hs | 17 + testsuite/tests/module/mod134.hs | 9 + testsuite/tests/module/mod134.stderr | 7 + testsuite/tests/module/mod134.stderr-hugs | 1 + testsuite/tests/module/mod135.hs | 6 + testsuite/tests/module/mod135.stderr | 2 + testsuite/tests/module/mod135.stderr-hugs | 1 + testsuite/tests/module/mod136.hs | 7 + testsuite/tests/module/mod136.stderr | 6 + testsuite/tests/module/mod136.stderr-hugs | 1 + testsuite/tests/module/mod137.hs | 9 + testsuite/tests/module/mod138.hs | 9 + testsuite/tests/module/mod138.stderr | 2 + testsuite/tests/module/mod138.stderr-hugs | 1 + testsuite/tests/module/mod139.hs | 11 + testsuite/tests/module/mod14.hs | 5 + testsuite/tests/module/mod14.stderr-ghc | 3 + testsuite/tests/module/mod140.hs | 6 + testsuite/tests/module/mod141.hs | 7 + testsuite/tests/module/mod142.hs | 6 + testsuite/tests/module/mod142.stderr | 7 + testsuite/tests/module/mod142.stderr-hugs | 2 + testsuite/tests/module/mod143.hs | 7 + testsuite/tests/module/mod143.stderr | 7 + testsuite/tests/module/mod143.stderr-hugs | 2 + testsuite/tests/module/mod144.hs | 7 + testsuite/tests/module/mod144.stderr | 7 + testsuite/tests/module/mod144.stderr-hugs | 2 + testsuite/tests/module/mod145.hs | 9 + testsuite/tests/module/mod145.stderr | 7 + testsuite/tests/module/mod145.stderr-hugs | 2 + testsuite/tests/module/mod146.hs | 8 + testsuite/tests/module/mod146.stderr | 7 + testsuite/tests/module/mod146.stderr-hugs | 2 + testsuite/tests/module/mod147.hs | 6 + testsuite/tests/module/mod147.stderr | 2 + testsuite/tests/module/mod147.stderr-hugs | 1 + testsuite/tests/module/mod148.hs | 5 + testsuite/tests/module/mod149.hs | 4 + testsuite/tests/module/mod15.hs | 5 + testsuite/tests/module/mod150.hs | 2 + testsuite/tests/module/mod150.stderr | 7 + testsuite/tests/module/mod150.stderr-hugs | 2 + testsuite/tests/module/mod151.hs | 2 + testsuite/tests/module/mod151.stderr | 7 + testsuite/tests/module/mod151.stderr-hugs | 3 + testsuite/tests/module/mod152.hs | 2 + testsuite/tests/module/mod152.stderr | 14 + testsuite/tests/module/mod152.stderr-hugs | 3 + testsuite/tests/module/mod153.hs | 2 + testsuite/tests/module/mod153.stderr | 7 + testsuite/tests/module/mod153.stderr-hugs | 3 + testsuite/tests/module/mod154.hs | 9 + testsuite/tests/module/mod155.hs | 5 + testsuite/tests/module/mod155.stderr | 7 + testsuite/tests/module/mod155.stderr-hugs | 2 + testsuite/tests/module/mod156.hs | 2 + testsuite/tests/module/mod157.hs | 13 + testsuite/tests/module/mod158.hs | 14 + testsuite/tests/module/mod158.stderr | 3 + testsuite/tests/module/mod158.stderr-hugs | 1 + testsuite/tests/module/mod159.hs | 10 + testsuite/tests/module/mod16.hs | 5 + testsuite/tests/module/mod160.hs | 12 + testsuite/tests/module/mod160.stderr | 6 + testsuite/tests/module/mod160.stderr-hugs | 1 + testsuite/tests/module/mod161.hs | 3 + testsuite/tests/module/mod161.stderr | 2 + testsuite/tests/module/mod161.stderr-hugs | 1 + testsuite/tests/module/mod162.hs | 6 + testsuite/tests/module/mod163.hs | 6 + testsuite/tests/module/mod164.hs | 10 + testsuite/tests/module/mod164.stderr | 9 + testsuite/tests/module/mod164.stderr-hugs | 3 + testsuite/tests/module/mod165.hs | 10 + testsuite/tests/module/mod165.stderr | 7 + testsuite/tests/module/mod165.stderr-hugs | 3 + testsuite/tests/module/mod166.hs | 10 + testsuite/tests/module/mod167.hs | 9 + testsuite/tests/module/mod168.hs | 20 + testsuite/tests/module/mod169.hs | 5 + testsuite/tests/module/mod17.hs | 5 + testsuite/tests/module/mod17.stderr | 4 + testsuite/tests/module/mod17.stderr-hugs | 1 + testsuite/tests/module/mod170.hs | 7 + testsuite/tests/module/mod171.hs | 11 + testsuite/tests/module/mod172.hs | 5 + testsuite/tests/module/mod173.hs | 12 + testsuite/tests/module/mod174.hs | 9 + testsuite/tests/module/mod174.stderr | 3 + testsuite/tests/module/mod175/Makefile | 19 + testsuite/tests/module/mod175/Test.hs | 7 + testsuite/tests/module/mod175/Test2.hs | 6 + testsuite/tests/module/mod175/all.T | 7 + testsuite/tests/module/mod175/mod175.stdout | 2 + testsuite/tests/module/mod176.hs | 10 + testsuite/tests/module/mod176.stderr | 4 + testsuite/tests/module/mod177.hs | 7 + testsuite/tests/module/mod177.stderr | 5 + testsuite/tests/module/mod178.hs | 8 + testsuite/tests/module/mod178.stderr | 5 + testsuite/tests/module/mod179.hs | 5 + testsuite/tests/module/mod179.stdout | 1 + testsuite/tests/module/mod18.hs | 3 + testsuite/tests/module/mod18.stderr | 5 + testsuite/tests/module/mod18.stderr-hugs | 1 + testsuite/tests/module/mod180.hs | 13 + testsuite/tests/module/mod180.stderr | 8 + testsuite/tests/module/mod19.hs | 3 + testsuite/tests/module/mod19.stderr | 10 + testsuite/tests/module/mod19.stderr-hugs | 1 + testsuite/tests/module/mod2.hs | 3 + testsuite/tests/module/mod2.stderr | 4 + testsuite/tests/module/mod2.stderr-hugs | 1 + testsuite/tests/module/mod20.hs | 3 + testsuite/tests/module/mod20.stderr | 5 + testsuite/tests/module/mod20.stderr-hugs | 1 + testsuite/tests/module/mod21.hs | 3 + testsuite/tests/module/mod21.stderr | 5 + testsuite/tests/module/mod21.stderr-hugs | 1 + testsuite/tests/module/mod22.hs | 3 + testsuite/tests/module/mod22.stderr | 5 + testsuite/tests/module/mod22.stderr-hugs | 1 + testsuite/tests/module/mod23.hs | 3 + testsuite/tests/module/mod23.stderr | 5 + testsuite/tests/module/mod23.stderr-hugs | 1 + testsuite/tests/module/mod24.hs | 3 + testsuite/tests/module/mod24.stderr | 5 + testsuite/tests/module/mod24.stderr-hugs | 1 + testsuite/tests/module/mod25.hs | 3 + testsuite/tests/module/mod25.stderr | 2 + testsuite/tests/module/mod25.stderr-hugs | 1 + testsuite/tests/module/mod26.hs | 3 + testsuite/tests/module/mod26.stderr | 2 + testsuite/tests/module/mod26.stderr-hugs | 1 + testsuite/tests/module/mod27.hs | 4 + testsuite/tests/module/mod27.stderr | 5 + testsuite/tests/module/mod27.stderr-hugs | 1 + testsuite/tests/module/mod29.hs | 6 + testsuite/tests/module/mod29.stderr | 2 + testsuite/tests/module/mod29.stderr-hugs | 1 + testsuite/tests/module/mod3.hs | 4 + testsuite/tests/module/mod3.stderr | 4 + testsuite/tests/module/mod3.stderr-hugs | 1 + testsuite/tests/module/mod30.hs | 4 + testsuite/tests/module/mod31.hs | 5 + testsuite/tests/module/mod32.hs | 5 + testsuite/tests/module/mod33.hs | 5 + testsuite/tests/module/mod34.hs | 5 + testsuite/tests/module/mod35.hs | 5 + testsuite/tests/module/mod36.hs | 5 + testsuite/tests/module/mod36.stderr | 2 + testsuite/tests/module/mod36.stderr-hugs | 1 + testsuite/tests/module/mod37.hs | 5 + testsuite/tests/module/mod38.hs | 4 + testsuite/tests/module/mod38.stderr | 5 + testsuite/tests/module/mod38.stderr-hugs | 1 + testsuite/tests/module/mod39.hs | 3 + testsuite/tests/module/mod4.hs | 3 + testsuite/tests/module/mod4.stderr | 4 + testsuite/tests/module/mod4.stderr-hugs | 1 + testsuite/tests/module/mod40.hs | 4 + testsuite/tests/module/mod40.stderr | 8 + testsuite/tests/module/mod40.stderr-hugs | 1 + testsuite/tests/module/mod41.hs | 3 + testsuite/tests/module/mod41.stderr | 8 + testsuite/tests/module/mod41.stderr-hugs | 1 + testsuite/tests/module/mod42.hs | 3 + testsuite/tests/module/mod42.stderr | 8 + testsuite/tests/module/mod42.stderr-hugs | 1 + testsuite/tests/module/mod43.hs | 3 + testsuite/tests/module/mod43.stderr | 7 + testsuite/tests/module/mod43.stderr-hugs | 1 + testsuite/tests/module/mod44.hs | 5 + testsuite/tests/module/mod44.stderr | 5 + testsuite/tests/module/mod44.stderr-hugs | 4 + testsuite/tests/module/mod45.hs | 7 + testsuite/tests/module/mod45.stderr | 6 + testsuite/tests/module/mod45.stderr-hugs | 1 + testsuite/tests/module/mod46.hs | 4 + testsuite/tests/module/mod46.stderr | 5 + testsuite/tests/module/mod46.stderr-hugs | 4 + testsuite/tests/module/mod47.hs | 7 + testsuite/tests/module/mod47.stderr | 9 + testsuite/tests/module/mod47.stderr-hugs | 4 + testsuite/tests/module/mod48.hs | 5 + testsuite/tests/module/mod48.stderr | 4 + testsuite/tests/module/mod48.stderr-hugs | 1 + testsuite/tests/module/mod49.hs | 5 + testsuite/tests/module/mod49.stderr | 2 + testsuite/tests/module/mod49.stderr-hugs | 1 + testsuite/tests/module/mod5.hs | 3 + testsuite/tests/module/mod5.stderr-ghc | 3 + testsuite/tests/module/mod50.hs | 3 + testsuite/tests/module/mod50.stderr | 2 + testsuite/tests/module/mod50.stderr-hugs | 1 + testsuite/tests/module/mod51.hs | 3 + testsuite/tests/module/mod51.stderr | 5 + testsuite/tests/module/mod51.stderr-hugs | 4 + testsuite/tests/module/mod52.hs | 4 + testsuite/tests/module/mod52.stderr | 5 + testsuite/tests/module/mod52.stderr-hugs | 4 + testsuite/tests/module/mod53.hs | 4 + testsuite/tests/module/mod53.stderr | 5 + testsuite/tests/module/mod53.stderr-hugs | 1 + testsuite/tests/module/mod54.hs | 3 + testsuite/tests/module/mod54.stderr | 8 + testsuite/tests/module/mod54.stderr-hugs | 4 + testsuite/tests/module/mod55.hs | 3 + testsuite/tests/module/mod55.stderr | 6 + testsuite/tests/module/mod55.stderr-hugs | 1 + testsuite/tests/module/mod56.hs | 4 + testsuite/tests/module/mod56.stderr | 8 + testsuite/tests/module/mod56.stderr-hugs | 1 + testsuite/tests/module/mod58.hs | 4 + testsuite/tests/module/mod58.stderr | 4 + testsuite/tests/module/mod58.stderr-hugs | 1 + testsuite/tests/module/mod59.hs | 3 + testsuite/tests/module/mod59.stderr | 2 + testsuite/tests/module/mod59.stderr-hugs | 1 + testsuite/tests/module/mod6.hs | 3 + testsuite/tests/module/mod60.hs | 3 + testsuite/tests/module/mod60.stderr | 5 + testsuite/tests/module/mod60.stderr-hugs | 1 + testsuite/tests/module/mod61.hs | 3 + testsuite/tests/module/mod61.stderr | 4 + testsuite/tests/module/mod61.stderr-hugs | 1 + testsuite/tests/module/mod62.hs | 3 + testsuite/tests/module/mod62.stderr | 6 + testsuite/tests/module/mod62.stderr-hugs | 1 + testsuite/tests/module/mod63.hs | 4 + testsuite/tests/module/mod63.stderr | 5 + testsuite/tests/module/mod63.stderr-hugs | 1 + testsuite/tests/module/mod64.hs | 3 + testsuite/tests/module/mod65.hs | 3 + testsuite/tests/module/mod66.hs | 5 + testsuite/tests/module/mod66.stderr | 5 + testsuite/tests/module/mod66.stderr-hugs | 1 + testsuite/tests/module/mod67.hs | 3 + testsuite/tests/module/mod67.stderr | 3 + testsuite/tests/module/mod67.stderr-hugs | 1 + testsuite/tests/module/mod68.hs | 5 + testsuite/tests/module/mod68.stderr | 5 + testsuite/tests/module/mod68.stderr-hugs | 1 + testsuite/tests/module/mod69.hs | 3 + testsuite/tests/module/mod69.stderr | 2 + testsuite/tests/module/mod69.stderr-hugs | 1 + testsuite/tests/module/mod7.hs | 3 + testsuite/tests/module/mod7.stderr | 2 + testsuite/tests/module/mod7.stderr-hugs | 1 + testsuite/tests/module/mod70.hs | 3 + testsuite/tests/module/mod70.stderr | 2 + testsuite/tests/module/mod70.stderr-hugs | 1 + testsuite/tests/module/mod71.hs | 3 + testsuite/tests/module/mod71.stderr | 2 + testsuite/tests/module/mod71.stderr-hugs | 1 + testsuite/tests/module/mod72.hs | 3 + testsuite/tests/module/mod72.stderr | 2 + testsuite/tests/module/mod72.stderr-hugs | 1 + testsuite/tests/module/mod73.hs | 3 + testsuite/tests/module/mod73.stderr | 7 + testsuite/tests/module/mod73.stderr-hugs | 1 + testsuite/tests/module/mod74.hs | 3 + testsuite/tests/module/mod74.stderr | 2 + testsuite/tests/module/mod74.stderr-hugs | 1 + testsuite/tests/module/mod75.hs | 3 + testsuite/tests/module/mod76.hs | 7 + testsuite/tests/module/mod76.stderr | 2 + testsuite/tests/module/mod76.stderr-hugs | 1 + testsuite/tests/module/mod77.hs | 4 + testsuite/tests/module/mod77.stderr | 3 + testsuite/tests/module/mod77.stderr-hugs | 1 + testsuite/tests/module/mod79.hs | 4 + testsuite/tests/module/mod79.stderr | 2 + testsuite/tests/module/mod79.stderr-hugs | 1 + testsuite/tests/module/mod8.hs | 3 + testsuite/tests/module/mod8.stderr | 2 + testsuite/tests/module/mod8.stderr-hugs | 1 + testsuite/tests/module/mod80.hs | 4 + testsuite/tests/module/mod80.stderr | 2 + testsuite/tests/module/mod80.stderr-hugs | 1 + testsuite/tests/module/mod81.hs | 4 + testsuite/tests/module/mod81.stderr | 3 + testsuite/tests/module/mod81.stderr-hugs | 1 + testsuite/tests/module/mod82.hs | 4 + testsuite/tests/module/mod83.hs | 4 + testsuite/tests/module/mod84.hs | 4 + testsuite/tests/module/mod85.hs | 5 + testsuite/tests/module/mod86.hs | 4 + testsuite/tests/module/mod87.hs | 4 + testsuite/tests/module/mod87.stderr | 2 + testsuite/tests/module/mod87.stderr-hugs | 1 + testsuite/tests/module/mod88.hs | 5 + testsuite/tests/module/mod88.stderr | 2 + testsuite/tests/module/mod88.stderr-hugs | 1 + testsuite/tests/module/mod89.hs | 4 + testsuite/tests/module/mod89.stderr | 2 + testsuite/tests/module/mod89.stderr-hugs | 1 + testsuite/tests/module/mod9.hs | 3 + testsuite/tests/module/mod9.stderr | 2 + testsuite/tests/module/mod9.stderr-hugs | 1 + testsuite/tests/module/mod90.hs | 4 + testsuite/tests/module/mod90.stderr | 8 + testsuite/tests/module/mod90.stderr-hugs | 1 + testsuite/tests/module/mod91.hs | 4 + testsuite/tests/module/mod91.stderr | 3 + testsuite/tests/module/mod91.stderr-hugs | 1 + testsuite/tests/module/mod92.hs | 4 + testsuite/tests/module/mod93.hs | 4 + testsuite/tests/module/mod94.hs | 5 + testsuite/tests/module/mod95.hs | 5 + testsuite/tests/module/mod96.hs | 4 + testsuite/tests/module/mod97.hs | 4 + testsuite/tests/module/mod97.stderr | 2 + testsuite/tests/module/mod97.stderr-hugs | 1 + testsuite/tests/module/mod98.hs | 4 + testsuite/tests/module/mod98.stderr | 4 + testsuite/tests/module/mod98.stderr-hugs | 1 + testsuite/tests/module/mod99.hs | 4 + testsuite/tests/numeric/Makefile | 3 + testsuite/tests/numeric/should_compile/Makefile | 7 + testsuite/tests/numeric/should_compile/T7116.hs | 19 + .../tests/numeric/should_compile/T7116.stdout | 66 + testsuite/tests/numeric/should_compile/T7881.hs | 34 + .../tests/numeric/should_compile/T7881.stderr | 6 + testsuite/tests/numeric/should_compile/T7895.hs | 26 + .../tests/numeric/should_compile/T7895.stderr | 6 + testsuite/tests/numeric/should_compile/T8542.hs | 9 + .../tests/numeric/should_compile/T8542.stderr | 8 + testsuite/tests/numeric/should_compile/all.T | 4 + testsuite/tests/numeric/should_run/Makefile | 10 + testsuite/tests/numeric/should_run/NumDecimals.hs | 4 + .../tests/numeric/should_run/NumDecimals.stdout | 1 + testsuite/tests/numeric/should_run/T1603.hs | 7 + testsuite/tests/numeric/should_run/T1603.stdout | 1 + testsuite/tests/numeric/should_run/T3676.hs | 32 + testsuite/tests/numeric/should_run/T3676.stdout | 48 + testsuite/tests/numeric/should_run/T4381.hs | 5 + testsuite/tests/numeric/should_run/T4381.stdout | 2 + testsuite/tests/numeric/should_run/T4383.hs | 1 + testsuite/tests/numeric/should_run/T4383.stdout | 1 + testsuite/tests/numeric/should_run/T5863.hs | 6 + testsuite/tests/numeric/should_run/T5863.stdout | 2 + testsuite/tests/numeric/should_run/T7014.hs | 91 + testsuite/tests/numeric/should_run/T7014.primops | 12 + testsuite/tests/numeric/should_run/T7014.stdout | 21 + testsuite/tests/numeric/should_run/T7233.hs | 14 + testsuite/tests/numeric/should_run/T7233.stdout | 10 + testsuite/tests/numeric/should_run/add2.hs | 26 + testsuite/tests/numeric/should_run/add2.stdout | 15 + .../tests/numeric/should_run/add2.stdout-ws-32 | 15 + testsuite/tests/numeric/should_run/all.T | 63 + testsuite/tests/numeric/should_run/arith001.hs | 28 + testsuite/tests/numeric/should_run/arith001.stdout | 5 + .../tests/numeric/should_run/arith001.stdout-ghc | 5 + testsuite/tests/numeric/should_run/arith002.hs | 52 + testsuite/tests/numeric/should_run/arith002.stdout | 4 + .../tests/numeric/should_run/arith002.stdout-ghc | 4 + testsuite/tests/numeric/should_run/arith003.hs | 84 + testsuite/tests/numeric/should_run/arith003.stdout | 1109 ++ .../should_run/arith003.stdout-alpha-dec-osf3 | 1053 ++ .../should_run/arith003.stdout-mips-sgi-irix | 1053 ++ .../tests/numeric/should_run/arith003.stdout-ws-64 | 1109 ++ testsuite/tests/numeric/should_run/arith004.hs | 86 + testsuite/tests/numeric/should_run/arith004.stdout | 12 + testsuite/tests/numeric/should_run/arith005.hs | 60 + testsuite/tests/numeric/should_run/arith005.stdout | 22 + .../tests/numeric/should_run/arith005.stdout-ws-64 | 22 + testsuite/tests/numeric/should_run/arith006.hs | 4 + testsuite/tests/numeric/should_run/arith006.stdout | 1 + testsuite/tests/numeric/should_run/arith007.hs | 23 + testsuite/tests/numeric/should_run/arith007.stdout | 1 + testsuite/tests/numeric/should_run/arith008.hs | 24 + testsuite/tests/numeric/should_run/arith008.stdout | 1000 ++ testsuite/tests/numeric/should_run/arith009.hs | 6 + testsuite/tests/numeric/should_run/arith009.stdout | 1 + testsuite/tests/numeric/should_run/arith010.hs | 11 + testsuite/tests/numeric/should_run/arith010.stdout | 8 + testsuite/tests/numeric/should_run/arith011.hs | 174 + testsuite/tests/numeric/should_run/arith011.stdout |15418 ++++++++++++++++++++ .../should_run/arith011.stdout-alpha-dec-osf3 |14508 ++++++++++++++++++ .../should_run/arith011.stdout-mips-sgi-irix |15138 +++++++++++++++++++ .../tests/numeric/should_run/arith011.stdout-ws-64 |15418 ++++++++++++++++++++ testsuite/tests/numeric/should_run/arith012.hs | 90 + testsuite/tests/numeric/should_run/arith012.stdout | 32 + testsuite/tests/numeric/should_run/arith013.hs | 10 + testsuite/tests/numeric/should_run/arith013.stdout | 32 + testsuite/tests/numeric/should_run/arith014.hs | 11 + testsuite/tests/numeric/should_run/arith014.stdout | 1 + testsuite/tests/numeric/should_run/arith015.hs | 5 + testsuite/tests/numeric/should_run/arith015.stdout | 2 + testsuite/tests/numeric/should_run/arith016.hs | 34 + testsuite/tests/numeric/should_run/arith016.stdout | 55 + testsuite/tests/numeric/should_run/arith017.hs | 10 + testsuite/tests/numeric/should_run/arith017.stdout | 2 + testsuite/tests/numeric/should_run/arith018.hs | 12 + testsuite/tests/numeric/should_run/arith018.stdout | 2 + testsuite/tests/numeric/should_run/arith019.hs | 10 + testsuite/tests/numeric/should_run/arith019.stdout | 1 + testsuite/tests/numeric/should_run/expfloat.hs | 7 + testsuite/tests/numeric/should_run/expfloat.stdout | 1 + testsuite/tests/numeric/should_run/mul2.hs | 26 + testsuite/tests/numeric/should_run/mul2.stdout | 15 + .../tests/numeric/should_run/mul2.stdout-ws-32 | 15 + testsuite/tests/numeric/should_run/numrun009.hs | 17 + .../tests/numeric/should_run/numrun009.stdout | 12 + .../should_run/numrun009.stdout-alpha-dec-osf3 | 12 + .../should_run/numrun009.stdout-mips-sgi-irix | 12 + .../numeric/should_run/numrun009.stdout-ws-64 | 12 + .../numrun009.stdout-x86_64-unknown-openbsd | 12 + testsuite/tests/numeric/should_run/numrun010.hs | 13 + .../tests/numeric/should_run/numrun010.stdout | 1 + testsuite/tests/numeric/should_run/numrun011.hs | 2 + .../tests/numeric/should_run/numrun011.stdout | 1 + testsuite/tests/numeric/should_run/numrun012.hs | 35 + .../tests/numeric/should_run/numrun012.stdout | 5 + .../numeric/should_run/numrun012.stdout-ws-64 | 9 + testsuite/tests/numeric/should_run/numrun013.hs | 16 + .../tests/numeric/should_run/numrun013.stdout | 5 + testsuite/tests/numeric/should_run/numrun014.hs | 211 + .../tests/numeric/should_run/numrun014.stdout | 172 + testsuite/tests/numeric/should_run/quotRem2.hs | 34 + testsuite/tests/numeric/should_run/quotRem2.stdout | 3 + testsuite/tests/overloadedlists/Makefile | 3 + .../tests/overloadedlists/should_fail/Makefile | 3 + testsuite/tests/overloadedlists/should_fail/all.T | 6 + .../should_fail/overloadedlistsfail01.hs | 5 + .../should_fail/overloadedlistsfail01.stderr | 36 + .../should_fail/overloadedlistsfail02.hs | 8 + .../should_fail/overloadedlistsfail02.stderr | 13 + .../should_fail/overloadedlistsfail03.hs | 3 + .../should_fail/overloadedlistsfail03.stderr | 6 + .../should_fail/overloadedlistsfail04.hs | 3 + .../should_fail/overloadedlistsfail04.stderr | 8 + .../should_fail/overloadedlistsfail05.hs | 3 + .../should_fail/overloadedlistsfail05.stderr | 7 + .../should_fail/overloadedlistsfail06.hs | 4 + .../should_fail/overloadedlistsfail06.stderr | 4 + .../tests/overloadedlists/should_run/Makefile | 3 + testsuite/tests/overloadedlists/should_run/all.T | 5 + .../should_run/overloadedlistsrun01.hs | 6 + .../should_run/overloadedlistsrun01.stdout | 4 + .../should_run/overloadedlistsrun02.hs | 13 + .../should_run/overloadedlistsrun02.stdout | 3 + .../should_run/overloadedlistsrun03.hs | 18 + .../should_run/overloadedlistsrun03.stdout | 5 + .../should_run/overloadedlistsrun04.hs | 28 + .../should_run/overloadedlistsrun04.stdout | 7 + .../should_run/overloadedlistsrun05.hs | 16 + .../should_run/overloadedlistsrun05.stdout | 6 + testsuite/tests/parser/Makefile | 3 + testsuite/tests/parser/prog001/Makefile | 3 + testsuite/tests/parser/prog001/Read006.hs | 5 + testsuite/tests/parser/prog001/Read007.hs | 8 + testsuite/tests/parser/prog001/test.T | 4 + .../tests/parser/should_compile/DoAndIfThenElse.hs | 9 + .../tests/parser/should_compile/EmptyDecls.hs | 9 + testsuite/tests/parser/should_compile/Makefile | 3 + .../should_compile/NondecreasingIndentation.hs | 10 + .../parser/should_compile/ParserLambdaCase.hs | 12 + testsuite/tests/parser/should_compile/T2245.hs | 7 + testsuite/tests/parser/should_compile/T2245.stderr | 22 + testsuite/tests/parser/should_compile/T3303.hs | 8 + testsuite/tests/parser/should_compile/T3303.stderr | 6 + testsuite/tests/parser/should_compile/T3303A.hs | 10 + testsuite/tests/parser/should_compile/T3741.hs | 4 + testsuite/tests/parser/should_compile/T5243.hs | 1 + testsuite/tests/parser/should_compile/T5243.stderr | 3 + testsuite/tests/parser/should_compile/T5243A.hs | 2 + testsuite/tests/parser/should_compile/T7118.hs | 2 + .../tests/parser/should_compile/T7476/Makefile | 10 + .../tests/parser/should_compile/T7476/T7476.hs | 2 + .../tests/parser/should_compile/T7476/T7476.stdout | 1 + testsuite/tests/parser/should_compile/T7476/all.T | 6 + testsuite/tests/parser/should_compile/T7776.hs | 6 + testsuite/tests/parser/should_compile/all.T | 98 + testsuite/tests/parser/should_compile/mc15.hs | 13 + testsuite/tests/parser/should_compile/mc16.hs | 16 + testsuite/tests/parser/should_compile/read001.hs | 8 + testsuite/tests/parser/should_compile/read002.hs | 14 + testsuite/tests/parser/should_compile/read003.hs | 20 + testsuite/tests/parser/should_compile/read004.hs | 16 + testsuite/tests/parser/should_compile/read005.hs | 4 + testsuite/tests/parser/should_compile/read008.hs | 4 + testsuite/tests/parser/should_compile/read009.hs | 7 + testsuite/tests/parser/should_compile/read010.hs | 4 + testsuite/tests/parser/should_compile/read011.hs | 24 + testsuite/tests/parser/should_compile/read014.hs | 8 + .../tests/parser/should_compile/read014.stderr-ghc | 13 + testsuite/tests/parser/should_compile/read015.hs | 2 + testsuite/tests/parser/should_compile/read016.hs | 10 + testsuite/tests/parser/should_compile/read017.hs | 15 + testsuite/tests/parser/should_compile/read018.hs | 17 + .../tests/parser/should_compile/read018.stderr | 3 + testsuite/tests/parser/should_compile/read019.hs | 10 + testsuite/tests/parser/should_compile/read021.hs | 6 + testsuite/tests/parser/should_compile/read022.hs | 4 + testsuite/tests/parser/should_compile/read023.hs | 23 + testsuite/tests/parser/should_compile/read024.hs | 33 + testsuite/tests/parser/should_compile/read025.hs | 9 + testsuite/tests/parser/should_compile/read026.hs | 6 + testsuite/tests/parser/should_compile/read027.hs | 14 + testsuite/tests/parser/should_compile/read028.hs | 3 + testsuite/tests/parser/should_compile/read029.hs | 14 + testsuite/tests/parser/should_compile/read030.hs | 10 + testsuite/tests/parser/should_compile/read031.hs | 10 + testsuite/tests/parser/should_compile/read032.hs | 4 + testsuite/tests/parser/should_compile/read033.hs | 3 + testsuite/tests/parser/should_compile/read034.hs | 12 + testsuite/tests/parser/should_compile/read036.hs | 4 + testsuite/tests/parser/should_compile/read037.hs | 6 + testsuite/tests/parser/should_compile/read038.hs | 5 + testsuite/tests/parser/should_compile/read039.hs | 7 + testsuite/tests/parser/should_compile/read040.hs | 8 + testsuite/tests/parser/should_compile/read041.lhs | 10 + testsuite/tests/parser/should_compile/read042.hs | 29 + testsuite/tests/parser/should_compile/read043.hs | 11 + .../tests/parser/should_compile/read043.stderr | 4 + testsuite/tests/parser/should_compile/read044.hs | 5 + testsuite/tests/parser/should_compile/read045.hs | 4 + testsuite/tests/parser/should_compile/read046.hs | 7 + testsuite/tests/parser/should_compile/read047.hs | 7 + testsuite/tests/parser/should_compile/read048.hs | 7 + testsuite/tests/parser/should_compile/read049.hs | 7 + testsuite/tests/parser/should_compile/read050.hs | 7 + testsuite/tests/parser/should_compile/read051.hs | 7 + testsuite/tests/parser/should_compile/read052.hs | 7 + testsuite/tests/parser/should_compile/read053.hs | 7 + testsuite/tests/parser/should_compile/read054.hs | 10 + testsuite/tests/parser/should_compile/read055.hs | 10 + testsuite/tests/parser/should_compile/read056.hs | 11 + testsuite/tests/parser/should_compile/read057.hs | 11 + testsuite/tests/parser/should_compile/read058.hs | 11 + testsuite/tests/parser/should_compile/read059.hs | 11 + testsuite/tests/parser/should_compile/read060.hs | 8 + testsuite/tests/parser/should_compile/read061.hs | 8 + testsuite/tests/parser/should_compile/read062.hs | 16 + testsuite/tests/parser/should_compile/read063.hs | 51 + testsuite/tests/parser/should_compile/read064.hs | 7 + .../tests/parser/should_compile/read064.stderr | 2 + testsuite/tests/parser/should_compile/read066.hs | 8 + .../tests/parser/should_compile/read066.stderr | 2 + testsuite/tests/parser/should_compile/read067.hs | 8 + testsuite/tests/parser/should_compile/read068.hs | 27 + testsuite/tests/parser/should_compile/read069.hs | 8 + testsuite/tests/parser/should_compile/read_1821.hs | 10 + .../tests/parser/should_fail/ExportCommaComma.hs | 3 + .../parser/should_fail/ExportCommaComma.stderr | 2 + testsuite/tests/parser/should_fail/Makefile | 3 + .../tests/parser/should_fail/NoDoAndIfThenElse.hs | 9 + .../parser/should_fail/NoDoAndIfThenElse.stderr | 5 + .../should_fail/NondecreasingIndentationFail.hs | 10 + .../NondecreasingIndentationFail.stderr | 4 + .../parser/should_fail/ParserNoForallUnicode.hs | 6 + .../should_fail/ParserNoForallUnicode.stderr | 5 + .../tests/parser/should_fail/ParserNoLambdaCase.hs | 4 + .../parser/should_fail/ParserNoLambdaCase.stderr | 2 + .../tests/parser/should_fail/ParserNoMultiWayIf.hs | 7 + .../parser/should_fail/ParserNoMultiWayIf.stderr | 3 + testsuite/tests/parser/should_fail/T1344a.hs | 7 + testsuite/tests/parser/should_fail/T1344a.stderr | 3 + testsuite/tests/parser/should_fail/T1344b.hs | 4 + testsuite/tests/parser/should_fail/T1344b.stderr | 3 + testsuite/tests/parser/should_fail/T1344c.hs | 4 + testsuite/tests/parser/should_fail/T1344c.stderr | 3 + testsuite/tests/parser/should_fail/T3095.hs | 5 + testsuite/tests/parser/should_fail/T3095.stderr | 5 + testsuite/tests/parser/should_fail/T3153.hs | 2 + testsuite/tests/parser/should_fail/T3153.stderr | 6 + testsuite/tests/parser/should_fail/T3751.hs | 3 + testsuite/tests/parser/should_fail/T3751.stderr | 3 + testsuite/tests/parser/should_fail/T3811.hs | 5 + testsuite/tests/parser/should_fail/T3811.stderr | 4 + testsuite/tests/parser/should_fail/T3811b.hs | 4 + testsuite/tests/parser/should_fail/T3811b.stderr | 3 + testsuite/tests/parser/should_fail/T3811c.hs | 7 + testsuite/tests/parser/should_fail/T3811c.stderr | 2 + testsuite/tests/parser/should_fail/T3811d.hs | 7 + testsuite/tests/parser/should_fail/T3811d.stderr | 6 + testsuite/tests/parser/should_fail/T3811e.hs | 6 + testsuite/tests/parser/should_fail/T3811e.stderr | 4 + testsuite/tests/parser/should_fail/T3811f.hs | 4 + testsuite/tests/parser/should_fail/T3811f.stderr | 2 + testsuite/tests/parser/should_fail/T3811g.hs | 7 + testsuite/tests/parser/should_fail/T3811g.stderr | 4 + testsuite/tests/parser/should_fail/T5425.hs | 6 + testsuite/tests/parser/should_fail/T5425.stderr | 3 + testsuite/tests/parser/should_fail/T7848.hs | 11 + testsuite/tests/parser/should_fail/T7848.stderr | 19 + testsuite/tests/parser/should_fail/T8430.lhs | 6 + testsuite/tests/parser/should_fail/T8430.stderr | 2 + testsuite/tests/parser/should_fail/T8431.hs | 1 + testsuite/tests/parser/should_fail/T8431.stderr | 2 + testsuite/tests/parser/should_fail/T8506.hs | 4 + testsuite/tests/parser/should_fail/T8506.stderr | 6 + testsuite/tests/parser/should_fail/T984.hs | 9 + testsuite/tests/parser/should_fail/T984.stderr | 4 + testsuite/tests/parser/should_fail/all.T | 85 + testsuite/tests/parser/should_fail/position001.hs | 7 + .../tests/parser/should_fail/position001.stderr | 2 + testsuite/tests/parser/should_fail/position002.hs | 7 + .../tests/parser/should_fail/position002.stderr | 2 + testsuite/tests/parser/should_fail/readFail001.hs | 113 + .../tests/parser/should_fail/readFail001.stderr | 26 + .../parser/should_fail/readFail001.stderr-hugs | 1 + .../tests/parser/should_fail/readFail001.stdout | 87 + testsuite/tests/parser/should_fail/readFail002.hs | 6 + .../tests/parser/should_fail/readFail002.stderr | 3 + .../parser/should_fail/readFail002.stderr-hugs | 1 + testsuite/tests/parser/should_fail/readFail003.hs | 8 + .../tests/parser/should_fail/readFail003.stderr | 16 + .../parser/should_fail/readFail003.stderr-hugs | 5 + .../tests/parser/should_fail/readFail003.stdout | 11 + testsuite/tests/parser/should_fail/readFail004.hs | 41 + .../tests/parser/should_fail/readFail004.stderr | 3 + .../parser/should_fail/readFail004.stderr-hugs | 1 + testsuite/tests/parser/should_fail/readFail005.hs | 4 + .../tests/parser/should_fail/readFail005.stderr | 3 + .../parser/should_fail/readFail005.stderr-hugs | 1 + testsuite/tests/parser/should_fail/readFail006.hs | 9 + .../tests/parser/should_fail/readFail006.stderr | 2 + .../parser/should_fail/readFail006.stderr-hugs | 1 + testsuite/tests/parser/should_fail/readFail007.hs | 8 + .../tests/parser/should_fail/readFail007.stderr | 4 + .../tests/parser/should_fail/readFail007.stdout | 9 + testsuite/tests/parser/should_fail/readFail008.hs | 5 + .../tests/parser/should_fail/readFail008.stderr | 6 + .../parser/should_fail/readFail008.stderr-hugs | 1 + testsuite/tests/parser/should_fail/readFail009.hs | 15 + .../tests/parser/should_fail/readFail009.stderr | 3 + .../parser/should_fail/readFail009.stderr-hugs | 1 + testsuite/tests/parser/should_fail/readFail011.hs | 7 + .../tests/parser/should_fail/readFail011.stderr | 2 + .../parser/should_fail/readFail011.stderr-hugs | 1 + testsuite/tests/parser/should_fail/readFail012.hs | 9 + .../tests/parser/should_fail/readFail012.stderr | 2 + .../parser/should_fail/readFail012.stderr-hugs | 1 + testsuite/tests/parser/should_fail/readFail013.hs | 4 + .../tests/parser/should_fail/readFail013.stderr | 2 + .../parser/should_fail/readFail013.stderr-hugs | 1 + testsuite/tests/parser/should_fail/readFail014.hs | 3 + .../tests/parser/should_fail/readFail014.stderr | 2 + .../parser/should_fail/readFail014.stderr-hugs | 1 + testsuite/tests/parser/should_fail/readFail015.hs | 5 + .../tests/parser/should_fail/readFail015.stderr | 2 + .../parser/should_fail/readFail015.stderr-hugs | 1 + testsuite/tests/parser/should_fail/readFail016.hs | 7 + .../tests/parser/should_fail/readFail016.stderr | 4 + .../tests/parser/should_fail/readFail016.stdout | 7 + testsuite/tests/parser/should_fail/readFail017.hs | 6 + .../tests/parser/should_fail/readFail017.stderr | 2 + .../parser/should_fail/readFail017.stderr-hugs | 1 + testsuite/tests/parser/should_fail/readFail018.hs | 8 + .../tests/parser/should_fail/readFail018.stderr | 2 + .../parser/should_fail/readFail018.stderr-hugs | 1 + testsuite/tests/parser/should_fail/readFail019.hs | 3 + .../tests/parser/should_fail/readFail019.stderr | 2 + .../parser/should_fail/readFail019.stderr-hugs | 1 + testsuite/tests/parser/should_fail/readFail020.hs | 3 + .../tests/parser/should_fail/readFail020.stderr | 2 + .../parser/should_fail/readFail020.stderr-hugs | 1 + .../tests/parser/should_fail/readFail021.stderr | 3 + testsuite/tests/parser/should_fail/readFail022.hs | 4 + .../tests/parser/should_fail/readFail022.stderr | 2 + .../parser/should_fail/readFail022.stderr-hugs | 1 + testsuite/tests/parser/should_fail/readFail023.hs | 12 + .../tests/parser/should_fail/readFail023.stderr | 6 + testsuite/tests/parser/should_fail/readFail024.hs | 5 + .../tests/parser/should_fail/readFail024.stderr | 2 + .../parser/should_fail/readFail024.stderr-hugs | 1 + testsuite/tests/parser/should_fail/readFail025.hs | 5 + .../tests/parser/should_fail/readFail025.stderr | 6 + .../parser/should_fail/readFail025.stderr-hugs | 1 + testsuite/tests/parser/should_fail/readFail026.hs | 3 + .../tests/parser/should_fail/readFail026.stderr | 2 + .../parser/should_fail/readFail026.stderr-hugs | 1 + testsuite/tests/parser/should_fail/readFail027.hs | 15 + .../tests/parser/should_fail/readFail027.stderr | 2 + testsuite/tests/parser/should_fail/readFail028.hs | 4 + .../tests/parser/should_fail/readFail028.stderr | 4 + testsuite/tests/parser/should_fail/readFail029.hs | 1 + .../tests/parser/should_fail/readFail029.stderr | 6 + testsuite/tests/parser/should_fail/readFail030.hs | 1 + .../tests/parser/should_fail/readFail030.stderr | 2 + testsuite/tests/parser/should_fail/readFail031.hs | 4 + .../tests/parser/should_fail/readFail031.stderr | 4 + testsuite/tests/parser/should_fail/readFail032.hs | 22 + .../tests/parser/should_fail/readFail032.stderr | 8 + testsuite/tests/parser/should_fail/readFail033.hs | 2 + .../tests/parser/should_fail/readFail033.stderr | 3 + testsuite/tests/parser/should_fail/readFail034.hs | 5 + .../tests/parser/should_fail/readFail034.stderr | 2 + testsuite/tests/parser/should_fail/readFail035.hs | 7 + .../tests/parser/should_fail/readFail035.stderr | 4 + testsuite/tests/parser/should_fail/readFail036.hs | 5 + .../tests/parser/should_fail/readFail036.stderr | 5 + testsuite/tests/parser/should_fail/readFail037.hs | 5 + .../tests/parser/should_fail/readFail037.stderr | 5 + testsuite/tests/parser/should_fail/readFail038.hs | 8 + .../tests/parser/should_fail/readFail038.stderr | 4 + testsuite/tests/parser/should_fail/readFail039.hs | 9 + .../tests/parser/should_fail/readFail039.stderr | 6 + testsuite/tests/parser/should_fail/readFail040.hs | 9 + .../tests/parser/should_fail/readFail040.stderr | 2 + testsuite/tests/parser/should_fail/readFail041.hs | 7 + .../tests/parser/should_fail/readFail041.stderr | 5 + testsuite/tests/parser/should_fail/readFail042.hs | 12 + .../tests/parser/should_fail/readFail042.stderr | 12 + testsuite/tests/parser/should_fail/readFail043.hs | 14 + .../tests/parser/should_fail/readFail043.stderr | 26 + testsuite/tests/parser/should_fail/readFail044.hs | 9 + .../tests/parser/should_fail/readFail044.stderr | 6 + .../parser/should_fail/readFail045.stderr-ghc-7.0 | 2 + testsuite/tests/parser/should_fail/readFail046.hs | 4 + .../tests/parser/should_fail/readFail046.stderr | 4 + testsuite/tests/parser/should_fail/readFail047.hs | 9 + .../tests/parser/should_fail/readFail047.stderr | 2 + .../should_fail/readFailTraditionalRecords1.hs | 6 + .../should_fail/readFailTraditionalRecords1.stderr | 3 + .../should_fail/readFailTraditionalRecords2.hs | 7 + .../should_fail/readFailTraditionalRecords2.stderr | 3 + .../should_fail/readFailTraditionalRecords3.hs | 6 + .../should_fail/readFailTraditionalRecords3.stderr | 3 + testsuite/tests/parser/should_run/Makefile | 3 + .../tests/parser/should_run/ParserMultiWayIf.hs | 20 + .../parser/should_run/ParserMultiWayIf.stdout | 1 + testsuite/tests/parser/should_run/T1344.hs | 10 + testsuite/tests/parser/should_run/T1344.stdout | 3 + testsuite/tests/parser/should_run/all.T | 8 + testsuite/tests/parser/should_run/operator.hs | 23 + testsuite/tests/parser/should_run/operator.stdout | 8 + testsuite/tests/parser/should_run/operator2.hs | 7 + testsuite/tests/parser/should_run/operator2.stdout | 1 + testsuite/tests/parser/should_run/readRun001.hs | 57 + .../tests/parser/should_run/readRun001.stdout | 11 + testsuite/tests/parser/should_run/readRun002.hs | 35 + .../tests/parser/should_run/readRun002.stdout | 7 + testsuite/tests/parser/should_run/readRun003.hs | 13 + .../tests/parser/should_run/readRun003.stdout | 4 + testsuite/tests/parser/should_run/readRun004.hs | 28 + .../tests/parser/should_run/readRun004.stdout | 2 + testsuite/tests/parser/unicode/Makefile | 3 + testsuite/tests/parser/unicode/T1103.hs | 13 + testsuite/tests/parser/unicode/T1744.hs | 3 + testsuite/tests/parser/unicode/T1744.stdout | 1 + testsuite/tests/parser/unicode/T2302.hs | 1 + testsuite/tests/parser/unicode/T2302.stderr | 2 + testsuite/tests/parser/unicode/T4373.hs | 3 + testsuite/tests/parser/unicode/T7671.hs | 8 + testsuite/tests/parser/unicode/all.T | 23 + testsuite/tests/parser/unicode/utf8_001.hs | 2 + testsuite/tests/parser/unicode/utf8_002.hs | 2 + testsuite/tests/parser/unicode/utf8_002.stderr | 2 + testsuite/tests/parser/unicode/utf8_003.hs | 2 + testsuite/tests/parser/unicode/utf8_003.stderr | 2 + testsuite/tests/parser/unicode/utf8_004.hs | 2 + testsuite/tests/parser/unicode/utf8_004.stderr | 2 + testsuite/tests/parser/unicode/utf8_005.hs | 2 + testsuite/tests/parser/unicode/utf8_005.stderr | 2 + testsuite/tests/parser/unicode/utf8_010.hs | 2 + testsuite/tests/parser/unicode/utf8_010.stderr | 3 + testsuite/tests/parser/unicode/utf8_011.hs | 2 + testsuite/tests/parser/unicode/utf8_011.stderr | 3 + testsuite/tests/parser/unicode/utf8_020.hs | 2 + testsuite/tests/parser/unicode/utf8_020.stderr | 3 + testsuite/tests/parser/unicode/utf8_021.hs | 2 + testsuite/tests/parser/unicode/utf8_021.stderr | 3 + testsuite/tests/parser/unicode/utf8_022.hs | 2 + testsuite/tests/parser/unicode/utf8_022.stderr | 3 + testsuite/tests/parser/unicode/utf8_023.hs | 2 + testsuite/tests/parser/unicode/utf8_024.hs | 194 + testsuite/tests/parser/unicode/utf8_024.stdout | 1 + testsuite/tests/perf/Makefile | 3 + testsuite/tests/perf/compiler/Makefile | 9 + testsuite/tests/perf/compiler/T1969.hs | 1210 ++ testsuite/tests/perf/compiler/T3064.hs | 90 + testsuite/tests/perf/compiler/T3294.hs | 206 + testsuite/tests/perf/compiler/T4007.hs | 5 + testsuite/tests/perf/compiler/T4007.stdout | 7 + testsuite/tests/perf/compiler/T4801.hs | 13 + testsuite/tests/perf/compiler/T5030.hs | 194 + testsuite/tests/perf/compiler/T5321FD.hs | 102 + testsuite/tests/perf/compiler/T5321Fun.hs | 109 + testsuite/tests/perf/compiler/T5631.hs | 1120 ++ testsuite/tests/perf/compiler/T5642.hs | 985 ++ testsuite/tests/perf/compiler/T5837.hs | 9 + testsuite/tests/perf/compiler/T5837.stderr | 161 + testsuite/tests/perf/compiler/T6048.hs | 42 + testsuite/tests/perf/compiler/T783.hs | 503 + testsuite/tests/perf/compiler/all.T | 374 + testsuite/tests/perf/compiler/parsing001.hs | 8413 +++++++++++ testsuite/tests/perf/compiler/parsing001.stderr | 4 + testsuite/tests/perf/haddock/Makefile | 3 + testsuite/tests/perf/haddock/all.T | 141 + testsuite/tests/perf/should_run/Conversions.hs | 21 + testsuite/tests/perf/should_run/Conversions.stdout | 2 + testsuite/tests/perf/should_run/Makefile | 36 + testsuite/tests/perf/should_run/MethSharing.hs | 97 + testsuite/tests/perf/should_run/MethSharing.stdout | 1 + testsuite/tests/perf/should_run/T149_A.hs | 25 + testsuite/tests/perf/should_run/T149_B.hs | 26 + testsuite/tests/perf/should_run/T2902_A.hs | 18 + .../tests/perf/should_run/T2902_A_PairingSum.hs | 49 + testsuite/tests/perf/should_run/T2902_B.hs | 18 + .../tests/perf/should_run/T2902_B_PairingSum.hs | 37 + testsuite/tests/perf/should_run/T2902_Sum.hs | 14 + testsuite/tests/perf/should_run/T3245.hs | 47 + testsuite/tests/perf/should_run/T3245.stdout | 15 + testsuite/tests/perf/should_run/T3586.hs | 20 + testsuite/tests/perf/should_run/T3586.stdout | 1 + testsuite/tests/perf/should_run/T3736.hs | 212 + testsuite/tests/perf/should_run/T3736.stdout | 1 + testsuite/tests/perf/should_run/T3738.hs | 10 + testsuite/tests/perf/should_run/T3738.stdout | 1 + testsuite/tests/perf/should_run/T3738a.hs | 6 + testsuite/tests/perf/should_run/T4321.hs | 15 + testsuite/tests/perf/should_run/T4321.stdout | 1 + testsuite/tests/perf/should_run/T4474a.hs | 40 + testsuite/tests/perf/should_run/T4474a.stdout | 1 + testsuite/tests/perf/should_run/T4474b.hs | 40 + testsuite/tests/perf/should_run/T4474b.stdout | 1 + testsuite/tests/perf/should_run/T4474c.hs | 40 + testsuite/tests/perf/should_run/T4474c.stdout | 1 + testsuite/tests/perf/should_run/T4830.hs | 15 + testsuite/tests/perf/should_run/T4830.stdout | 1 + testsuite/tests/perf/should_run/T4978.hs | 126 + testsuite/tests/perf/should_run/T4978.stdout | 1 + testsuite/tests/perf/should_run/T5113.hs | 31 + testsuite/tests/perf/should_run/T5113.stdout | 1 + testsuite/tests/perf/should_run/T5205.hs | 13 + testsuite/tests/perf/should_run/T5205.stdout | 1 + testsuite/tests/perf/should_run/T5237.hs | 15 + testsuite/tests/perf/should_run/T5237.stdout | 1 + testsuite/tests/perf/should_run/T5536.hs | 5 + testsuite/tests/perf/should_run/T5549.hs | 27 + testsuite/tests/perf/should_run/T5549.stdout | 2 + testsuite/tests/perf/should_run/T7257.hs | 30 + testsuite/tests/perf/should_run/T7257.stdout | 1 + testsuite/tests/perf/should_run/T7436.hs | 22 + testsuite/tests/perf/should_run/T7436.stdout | 1 + testsuite/tests/perf/should_run/T7507.hs | 14 + testsuite/tests/perf/should_run/T7507.stdout | 1 + testsuite/tests/perf/should_run/T7797.hs | 15 + testsuite/tests/perf/should_run/T7797.stdout | 1 + testsuite/tests/perf/should_run/T7797a.hs | 12 + testsuite/tests/perf/should_run/T7850.hs | 11 + testsuite/tests/perf/should_run/T7850.stdout | 1 + testsuite/tests/perf/should_run/T7954.hs | 7 + testsuite/tests/perf/should_run/T7954.stdout | 1 + testsuite/tests/perf/should_run/T876.hs | 11 + testsuite/tests/perf/should_run/T876.stdout | 1 + testsuite/tests/perf/should_run/all.T | 293 + testsuite/tests/perf/should_run/lazy-bs-alloc.hs | 9 + testsuite/tests/perf/space_leaks/Makefile | 3 + testsuite/tests/perf/space_leaks/T2762.hs | 18 + testsuite/tests/perf/space_leaks/T2762A.hs | 15 + testsuite/tests/perf/space_leaks/T4018.hs | 27 + testsuite/tests/perf/space_leaks/T4334.hs | 18 + testsuite/tests/perf/space_leaks/T4334.stdout | 3 + testsuite/tests/perf/space_leaks/all.T | 46 + testsuite/tests/perf/space_leaks/space_leak_001.hs | 5 + .../tests/perf/space_leaks/space_leak_001.stdout | 1 + testsuite/tests/plugins/HomePackagePlugin.hs | 34 + testsuite/tests/plugins/LinkerTicklingPlugin.hs | 17 + testsuite/tests/plugins/Makefile | 10 + testsuite/tests/plugins/all.T | 40 + testsuite/tests/plugins/plugins01.hs | 15 + testsuite/tests/plugins/plugins01.stderr | 4 + testsuite/tests/plugins/plugins01.stdout | 3 + testsuite/tests/plugins/plugins02.hs | 5 + testsuite/tests/plugins/plugins02.stderr | 1 + testsuite/tests/plugins/plugins03.hs | 5 + testsuite/tests/plugins/plugins03.stderr | 2 + testsuite/tests/plugins/plugins04.hs | 5 + testsuite/tests/plugins/plugins04.stderr | 2 + testsuite/tests/plugins/plugins05.hs | 7 + testsuite/tests/plugins/plugins05.stdout | 1 + testsuite/tests/plugins/plugins06.hs | 6 + testsuite/tests/plugins/simple-plugin/LICENSE | 10 + testsuite/tests/plugins/simple-plugin/Makefile | 20 + testsuite/tests/plugins/simple-plugin/Setup.hs | 3 + .../simple-plugin/Simple/BadlyTypedPlugin.hs | 4 + .../plugins/simple-plugin/Simple/DataStructures.hs | 9 + .../tests/plugins/simple-plugin/Simple/Plugin.hs | 83 + .../plugins/simple-plugin/simple-plugin.cabal | 20 + testsuite/tests/polykinds/Freeman.hs | 265 + testsuite/tests/polykinds/Freeman.stdout | 1 + testsuite/tests/polykinds/Makefile | 40 + testsuite/tests/polykinds/MonoidsFD.hs | 106 + testsuite/tests/polykinds/MonoidsFD.stdout | 8 + testsuite/tests/polykinds/MonoidsTF.hs | 116 + testsuite/tests/polykinds/MonoidsTF.stdout | 8 + testsuite/tests/polykinds/PolyKinds01.hs | 14 + testsuite/tests/polykinds/PolyKinds02.hs | 14 + testsuite/tests/polykinds/PolyKinds02.stderr | 5 + testsuite/tests/polykinds/PolyKinds03.hs | 13 + testsuite/tests/polykinds/PolyKinds04.hs | 8 + testsuite/tests/polykinds/PolyKinds04.stderr | 8 + testsuite/tests/polykinds/PolyKinds05.hs | 9 + testsuite/tests/polykinds/PolyKinds06.hs | 10 + testsuite/tests/polykinds/PolyKinds06.stderr | 5 + testsuite/tests/polykinds/PolyKinds07.hs | 12 + testsuite/tests/polykinds/PolyKinds07.stderr | 7 + testsuite/tests/polykinds/PolyKinds08.hs | 12 + testsuite/tests/polykinds/PolyKinds09.hs | 65 + testsuite/tests/polykinds/PolyKinds09.stdout | 1 + testsuite/tests/polykinds/PolyKinds10.hs | 159 + testsuite/tests/polykinds/PolyKinds10.stdout | 1 + testsuite/tests/polykinds/PolyKinds11.hs | 12 + testsuite/tests/polykinds/PolyKinds12.hs | 34 + testsuite/tests/polykinds/PolyKinds13.hs | 29 + testsuite/tests/polykinds/RedBlack.hs | 142 + testsuite/tests/polykinds/T5716.hs | 13 + testsuite/tests/polykinds/T5716.stderr | 4 + testsuite/tests/polykinds/T5716a.hs | 11 + testsuite/tests/polykinds/T5716a.stderr | 7 + testsuite/tests/polykinds/T5717.hs | 20 + testsuite/tests/polykinds/T5770.hs | 21 + testsuite/tests/polykinds/T5771.hs | 29 + testsuite/tests/polykinds/T5798.hs | 8 + testsuite/tests/polykinds/T5862.hs | 27 + testsuite/tests/polykinds/T5881.hs | 5 + testsuite/tests/polykinds/T5881a.hs | 4 + testsuite/tests/polykinds/T5912.hs | 12 + testsuite/tests/polykinds/T5935.hs | 13 + testsuite/tests/polykinds/T5937.hs | 6 + testsuite/tests/polykinds/T5938.hs | 7 + testsuite/tests/polykinds/T5948.hs | 7 + testsuite/tests/polykinds/T6002.hs | 101 + testsuite/tests/polykinds/T6015.hs | 15 + testsuite/tests/polykinds/T6015a.hs | 14 + testsuite/tests/polykinds/T6020.hs | 21 + testsuite/tests/polykinds/T6020a.hs | 16 + testsuite/tests/polykinds/T6021.hs | 5 + testsuite/tests/polykinds/T6021.stderr | 4 + testsuite/tests/polykinds/T6025.hs | 5 + testsuite/tests/polykinds/T6025a.hs | 6 + testsuite/tests/polykinds/T6035.hs | 28 + testsuite/tests/polykinds/T6036.hs | 17 + testsuite/tests/polykinds/T6039.hs | 6 + testsuite/tests/polykinds/T6039.stderr | 4 + testsuite/tests/polykinds/T6044.hs | 6 + testsuite/tests/polykinds/T6049.hs | 8 + testsuite/tests/polykinds/T6054.hs | 7 + testsuite/tests/polykinds/T6054.stderr | 9 + testsuite/tests/polykinds/T6054a.hs | 6 + testsuite/tests/polykinds/T6068.hs | 29 + testsuite/tests/polykinds/T6068.script | 2 + testsuite/tests/polykinds/T6068.stdout | 1 + testsuite/tests/polykinds/T6081.hs | 10 + testsuite/tests/polykinds/T6093.hs | 13 + testsuite/tests/polykinds/T6118.hs | 23 + testsuite/tests/polykinds/T6129.hs | 12 + testsuite/tests/polykinds/T6129.stderr | 7 + testsuite/tests/polykinds/T6137.hs | 25 + testsuite/tests/polykinds/T7020.hs | 17 + testsuite/tests/polykinds/T7022.hs | 9 + testsuite/tests/polykinds/T7022a.hs | 13 + testsuite/tests/polykinds/T7022b.hs | 9 + testsuite/tests/polykinds/T7053.hs | 7 + testsuite/tests/polykinds/T7053.stderr | 8 + testsuite/tests/polykinds/T7053a.hs | 8 + testsuite/tests/polykinds/T7073.hs | 8 + testsuite/tests/polykinds/T7090.hs | 28 + testsuite/tests/polykinds/T7095.hs | 25 + testsuite/tests/polykinds/T7128.hs | 8 + testsuite/tests/polykinds/T7151.hs | 3 + testsuite/tests/polykinds/T7151.stderr | 4 + testsuite/tests/polykinds/T7176.hs | 15 + testsuite/tests/polykinds/T7224.hs | 7 + testsuite/tests/polykinds/T7224.stderr | 5 + testsuite/tests/polykinds/T7230.hs | 49 + testsuite/tests/polykinds/T7230.stderr | 27 + testsuite/tests/polykinds/T7238.hs | 14 + testsuite/tests/polykinds/T7272.hs | 7 + testsuite/tests/polykinds/T7272.hs-boot | 5 + testsuite/tests/polykinds/T7272a.hs | 5 + testsuite/tests/polykinds/T7278.hs | 9 + testsuite/tests/polykinds/T7278.stderr | 5 + testsuite/tests/polykinds/T7328.hs | 8 + testsuite/tests/polykinds/T7328.stderr | 7 + testsuite/tests/polykinds/T7332.hs | 41 + testsuite/tests/polykinds/T7341.hs | 12 + testsuite/tests/polykinds/T7341.stderr | 6 + testsuite/tests/polykinds/T7347.hs | 11 + testsuite/tests/polykinds/T7404.hs | 4 + testsuite/tests/polykinds/T7404.stderr | 4 + testsuite/tests/polykinds/T7422.hs | 17 + testsuite/tests/polykinds/T7433.hs | 2 + testsuite/tests/polykinds/T7433.stderr | 6 + testsuite/tests/polykinds/T7438.hs | 6 + testsuite/tests/polykinds/T7438.stderr | 18 + testsuite/tests/polykinds/T7438a.hs | 8 + testsuite/tests/polykinds/T7488.hs | 8 + testsuite/tests/polykinds/T7502.hs | 4 + testsuite/tests/polykinds/T7524.hs | 6 + testsuite/tests/polykinds/T7524.stderr | 5 + testsuite/tests/polykinds/T7594.hs | 27 + testsuite/tests/polykinds/T7594.stderr | 15 + testsuite/tests/polykinds/T7601.hs | 12 + testsuite/tests/polykinds/T7805.hs | 7 + testsuite/tests/polykinds/T7805.stderr | 4 + testsuite/tests/polykinds/T7916.hs | 15 + testsuite/tests/polykinds/T7939a.hs | 7 + testsuite/tests/polykinds/T7939a.stderr | 7 + testsuite/tests/polykinds/T7973.hs | 25 + testsuite/tests/polykinds/T8132.hs | 6 + testsuite/tests/polykinds/T8132.stderr | 4 + testsuite/tests/polykinds/T8359.hs | 17 + testsuite/tests/polykinds/T8391.hs | 11 + testsuite/tests/polykinds/T8449.hs | 9 + testsuite/tests/polykinds/T8449a.hs | 9 + testsuite/tests/polykinds/T8534.hs | 3 + testsuite/tests/polykinds/all.T | 96 + testsuite/tests/primops/Makefile | 3 + .../primops/should_compile/T6135_should_compile.hs | 22 + testsuite/tests/primops/should_compile/all.T | 1 + testsuite/tests/primops/should_run/T6135.hs | 441 + testsuite/tests/primops/should_run/T6135.stdout | 356 + testsuite/tests/primops/should_run/T7689.hs | 78 + testsuite/tests/primops/should_run/T7689.stdout | 37 + testsuite/tests/primops/should_run/all.T | 3 + testsuite/tests/profiling/Makefile | 3 + testsuite/tests/profiling/should_compile/Makefile | 3 + testsuite/tests/profiling/should_compile/T2410.hs | 10 + testsuite/tests/profiling/should_compile/all.T | 8 + .../tests/profiling/should_compile/prof001.hs | 5 + .../tests/profiling/should_compile/prof002.hs | 17 + .../tests/profiling/should_compile/prof002.stdout | 1 + testsuite/tests/profiling/should_fail/Makefile | 3 + testsuite/tests/profiling/should_fail/all.T | 3 + .../tests/profiling/should_fail/proffail001.hs | 6 + .../tests/profiling/should_fail/proffail001.stderr | 2 + testsuite/tests/profiling/should_run/Makefile | 25 + testsuite/tests/profiling/should_run/T2552.hs | 20 + .../tests/profiling/should_run/T2552.prof.sample | 40 + testsuite/tests/profiling/should_run/T2552.stdout | 3 + testsuite/tests/profiling/should_run/T2592.hs | 1 + testsuite/tests/profiling/should_run/T2592.stderr | 3 + testsuite/tests/profiling/should_run/T3001-2.hs | 280 + .../tests/profiling/should_run/T3001-2.stdout | 1 + testsuite/tests/profiling/should_run/T3001.hs | 8 + testsuite/tests/profiling/should_run/T3001.stdout | 1 + testsuite/tests/profiling/should_run/T5314.hs | 10 + testsuite/tests/profiling/should_run/T5314.stdout | 1 + testsuite/tests/profiling/should_run/T5363.hs | 12 + testsuite/tests/profiling/should_run/T5363.stdout | 1 + .../tests/profiling/should_run/T5363.stdout-ws-32 | 1 + testsuite/tests/profiling/should_run/T5559.hs | 8 + .../tests/profiling/should_run/T5559.prof.sample | 23 + testsuite/tests/profiling/should_run/T5559.stdout | 1 + testsuite/tests/profiling/should_run/T680.hs | 20 + .../tests/profiling/should_run/T680.prof.sample | 35 + testsuite/tests/profiling/should_run/T680.stdout | 1 + testsuite/tests/profiling/should_run/T949.hs | 5 + testsuite/tests/profiling/should_run/all.T | 118 + testsuite/tests/profiling/should_run/bio001.stdout | 1 + .../tests/profiling/should_run/callstack001.hs | 18 + .../tests/profiling/should_run/callstack001.stdout | 2 + .../tests/profiling/should_run/callstack002.hs | 21 + .../tests/profiling/should_run/callstack002.stderr | 16 + .../tests/profiling/should_run/callstack002.stdout | 9 + .../tests/profiling/should_run/heapprof001.hs | 182 + .../tests/profiling/should_run/heapprof001.stdout | 7 + testsuite/tests/profiling/should_run/ioprof.hs | 25 + .../tests/profiling/should_run/ioprof.prof.sample | 39 + testsuite/tests/profiling/should_run/ioprof.stderr | 1 + .../tests/profiling/should_run/prof-doc-fib.hs | 9 + .../profiling/should_run/prof-doc-fib.prof.sample | 25 + .../tests/profiling/should_run/prof-doc-fib.stdout | 1 + .../tests/profiling/should_run/prof-doc-last.hs | 7 + .../profiling/should_run/prof-doc-last.prof.sample | 31 + .../profiling/should_run/prof-doc-last.stdout | 4 + .../tests/profiling/should_run/profinline001.hs | 14 + .../profiling/should_run/profinline001.prof.sample | 28 + .../profiling/should_run/profinline001.stdout | 1 + testsuite/tests/profiling/should_run/scc001.hs | 16 + .../tests/profiling/should_run/scc001.prof.sample | 28 + testsuite/tests/profiling/should_run/scc001.stdout | 3 + testsuite/tests/profiling/should_run/scc002.hs | 26 + .../tests/profiling/should_run/scc002.prof.sample | 29 + testsuite/tests/profiling/should_run/scc002.stdout | 1 + testsuite/tests/profiling/should_run/scc003.hs | 8 + .../tests/profiling/should_run/scc003.prof.sample | 25 + testsuite/tests/profiling/should_run/scc003.stdout | 1 + testsuite/tests/profiling/should_run/scc004.hs | 10 + .../tests/profiling/should_run/scc004.prof.sample | 28 + testsuite/tests/programs/10queens/10queens.stdout | 1 + testsuite/tests/programs/10queens/Main.hs | 30 + testsuite/tests/programs/10queens/Makefile | 3 + testsuite/tests/programs/10queens/test.T | 6 + testsuite/tests/programs/Makefile | 3 + testsuite/tests/programs/Makefile-OLD | 43 + testsuite/tests/programs/Queens/Makefile | 3 + testsuite/tests/programs/Queens/queens.hs | 50 + testsuite/tests/programs/Queens/queens.stdout | 24 + testsuite/tests/programs/Queens/test.T | 6 + testsuite/tests/programs/andre_monad/Main.hs | 89 + testsuite/tests/programs/andre_monad/Makefile | 3 + .../tests/programs/andre_monad/andre_monad.stdout | 1 + testsuite/tests/programs/andre_monad/test.T | 8 + testsuite/tests/programs/andy_cherry/DataTypes.hs | 622 + testsuite/tests/programs/andy_cherry/GenUtils.hs | 244 + testsuite/tests/programs/andy_cherry/Interp.hs | 262 + .../tests/programs/andy_cherry/InterpUtils.hs | 371 + testsuite/tests/programs/andy_cherry/Main.hs | 204 + testsuite/tests/programs/andy_cherry/Makefile | 3 + testsuite/tests/programs/andy_cherry/Parser.hs | 98 + testsuite/tests/programs/andy_cherry/PrintTEX.hs | 182 + .../tests/programs/andy_cherry/andy_cherry.stdout | 7258 +++++++++ testsuite/tests/programs/andy_cherry/mygames.pgn | 1323 ++ testsuite/tests/programs/andy_cherry/test.T | 14 + .../tests/programs/barton-mangler-bug/Basic.hs | 287 + testsuite/tests/programs/barton-mangler-bug/Bug.hs | 6 + .../tests/programs/barton-mangler-bug/Expected.hs | 5009 +++++++ .../tests/programs/barton-mangler-bug/Main.hs | 28 + .../tests/programs/barton-mangler-bug/Makefile | 3 + .../tests/programs/barton-mangler-bug/Physical.hs | 302 + .../tests/programs/barton-mangler-bug/Plot.lhs | 79 + .../programs/barton-mangler-bug/PlotExample.lhs | 21 + .../barton-mangler-bug/TypesettingTricks.hs | 21 + .../barton-mangler-bug/barton-mangler-bug.stdout | 5009 +++++++ .../tests/programs/barton-mangler-bug/piece.gnp | 4 + .../tests/programs/barton-mangler-bug/piece.plt | 2500 ++++ .../tests/programs/barton-mangler-bug/sine.gnp | 4 + .../tests/programs/barton-mangler-bug/sine.plt | 2500 ++++ testsuite/tests/programs/barton-mangler-bug/test.T | 14 + testsuite/tests/programs/cholewo-eval/Arr.lhs | 395 + testsuite/tests/programs/cholewo-eval/Main.lhs | 109 + testsuite/tests/programs/cholewo-eval/Makefile | 3 + .../programs/cholewo-eval/cholewo-eval.stdout | 1 + testsuite/tests/programs/cholewo-eval/test.T | 5 + testsuite/tests/programs/cvh_unboxing/Append.lhs | 142 + testsuite/tests/programs/cvh_unboxing/Main.lhs | 10 + testsuite/tests/programs/cvh_unboxing/Makefile | 3 + testsuite/tests/programs/cvh_unboxing/README | 4 + testsuite/tests/programs/cvh_unboxing/Types.lhs | 63 + .../programs/cvh_unboxing/cvh_unboxing.stdout | 1 + testsuite/tests/programs/cvh_unboxing/test.T | 10 + .../tests/programs/fast2haskell/Fast2haskell.hs | 50 + testsuite/tests/programs/fast2haskell/Main.hs | 296 + testsuite/tests/programs/fast2haskell/Makefile | 3 + .../programs/fast2haskell/fast2haskell.stdout | 2 + testsuite/tests/programs/fast2haskell/test.T | 8 + testsuite/tests/programs/fun_insts/Main.hs | 26 + testsuite/tests/programs/fun_insts/Makefile | 3 + .../tests/programs/fun_insts/fun_insts.stdout | 1 + testsuite/tests/programs/fun_insts/test.T | 6 + testsuite/tests/programs/galois_raytrace/CSG.hs | 16 + .../tests/programs/galois_raytrace/Construct.hs | 265 + testsuite/tests/programs/galois_raytrace/Data.hs | 408 + testsuite/tests/programs/galois_raytrace/Eval.hs | 355 + .../tests/programs/galois_raytrace/Geometry.hs | 312 + .../tests/programs/galois_raytrace/Illumination.hs | 224 + .../programs/galois_raytrace/Intersections.hs | 404 + .../tests/programs/galois_raytrace/Interval.hs | 121 + testsuite/tests/programs/galois_raytrace/Main.hs | 15 + testsuite/tests/programs/galois_raytrace/Makefile | 3 + testsuite/tests/programs/galois_raytrace/Misc.hs | 11 + testsuite/tests/programs/galois_raytrace/Parse.hs | 137 + testsuite/tests/programs/galois_raytrace/Pixmap.hs | 64 + .../tests/programs/galois_raytrace/Primitives.hs | 24 + .../tests/programs/galois_raytrace/RayTrace.hs | 9 + .../tests/programs/galois_raytrace/Surface.hs | 115 + .../tests/programs/galois_raytrace/galois.gml | 147 + .../galois_raytrace/galois_raytrace.stdout | 205 + testsuite/tests/programs/galois_raytrace/test.T | 26 + testsuite/tests/programs/hs-boot/A.hs | 6 + testsuite/tests/programs/hs-boot/A.hs-boot | 4 + testsuite/tests/programs/hs-boot/B.hs | 5 + testsuite/tests/programs/hs-boot/C.hs | 2 + testsuite/tests/programs/hs-boot/Main.hs | 8 + testsuite/tests/programs/hs-boot/Makefile | 3 + testsuite/tests/programs/hs-boot/all.T | 9 + testsuite/tests/programs/hs-boot/hs-boot.stderr | 2 + testsuite/tests/programs/jl_defaults/Main.hs | 24 + testsuite/tests/programs/jl_defaults/Makefile | 3 + .../tests/programs/jl_defaults/jl_defaults.stdin | 97 + .../tests/programs/jl_defaults/jl_defaults.stdout | 81 + testsuite/tests/programs/jl_defaults/test.T | 6 + .../tests/programs/joao-circular/Data_Lazy.hs | 273 + .../tests/programs/joao-circular/Funcs_Lexer.hs | 111 + .../programs/joao-circular/Funcs_Parser_Lazy.hs | 1549 ++ .../tests/programs/joao-circular/LrcPrelude.hs | 72 + testsuite/tests/programs/joao-circular/Main.hs | 77 + testsuite/tests/programs/joao-circular/Makefile | 3 + testsuite/tests/programs/joao-circular/README | 6 + .../tests/programs/joao-circular/Visfun_Lazy.hs | 1160 ++ testsuite/tests/programs/joao-circular/inp | 22 + .../programs/joao-circular/joao-circular.stdout | 86 + testsuite/tests/programs/joao-circular/test.T | 11 + testsuite/tests/programs/jq_readsPrec/Main.hs | 20 + testsuite/tests/programs/jq_readsPrec/Makefile | 3 + .../tests/programs/jq_readsPrec/jq_readsPrec.stdin | 1 + .../programs/jq_readsPrec/jq_readsPrec.stdout | 1 + testsuite/tests/programs/jq_readsPrec/test.T | 6 + testsuite/tests/programs/jtod_circint/Bit.hs | 183 + testsuite/tests/programs/jtod_circint/LogFun.hs | 34 + testsuite/tests/programs/jtod_circint/Main.hs | 12 + testsuite/tests/programs/jtod_circint/Makefile | 3 + testsuite/tests/programs/jtod_circint/Signal.hs | 146 + .../programs/jtod_circint/jtod_circint.stdout | 1 + testsuite/tests/programs/jtod_circint/test.T | 10 + testsuite/tests/programs/jules_xref/Main.hs | 174 + testsuite/tests/programs/jules_xref/Makefile | 3 + .../tests/programs/jules_xref/jules_xref.stdin | 1105 ++ .../tests/programs/jules_xref/jules_xref.stdout | 500 + testsuite/tests/programs/jules_xref/test.T | 8 + testsuite/tests/programs/jules_xref2/Main.hs | 76 + testsuite/tests/programs/jules_xref2/Makefile | 3 + .../tests/programs/jules_xref2/jules_xref2.stdin | 1105 ++ .../tests/programs/jules_xref2/jules_xref2.stdout | 499 + testsuite/tests/programs/jules_xref2/test.T | 6 + testsuite/tests/programs/launchbury/Main.hs | 18 + testsuite/tests/programs/launchbury/Makefile | 3 + .../tests/programs/launchbury/launchbury.stdin | 18 + .../tests/programs/launchbury/launchbury.stdout | 18 + testsuite/tests/programs/launchbury/test.T | 6 + testsuite/tests/programs/lennart_range/Main.hs | 24 + testsuite/tests/programs/lennart_range/Makefile | 3 + .../programs/lennart_range/lennart_range.stdout | 1 + testsuite/tests/programs/lennart_range/test.T | 6 + testsuite/tests/programs/lex/Main.hs | 9 + testsuite/tests/programs/lex/Makefile | 3 + testsuite/tests/programs/lex/lex.stdin | 170 + testsuite/tests/programs/lex/lex.stdout | 1 + testsuite/tests/programs/lex/test.T | 6 + testsuite/tests/programs/life_space_leak/Main.hs | 360 + testsuite/tests/programs/life_space_leak/Makefile | 3 + testsuite/tests/programs/life_space_leak/life.test | 17 + .../life_space_leak/life_space_leak.stdout | 3201 ++++ testsuite/tests/programs/life_space_leak/test.T | 8 + .../tests/programs/maessen-hashtab/Data/HashTab.hs | 339 + .../tests/programs/maessen-hashtab/HashTest.hs | 278 + testsuite/tests/programs/maessen-hashtab/Makefile | 3 + .../maessen-hashtab/maessen_hashtab.stdout | 15 + testsuite/tests/programs/maessen-hashtab/test.T | 11 + testsuite/tests/programs/north_array/Main.hs | 10 + testsuite/tests/programs/north_array/Makefile | 3 + .../tests/programs/north_array/north_array.stdout | 1 + testsuite/tests/programs/north_array/test.T | 6 + testsuite/tests/programs/okeefe_neural/Main.hs | 1533 ++ testsuite/tests/programs/okeefe_neural/Makefile | 3 + testsuite/tests/programs/okeefe_neural/test.T | 12 + testsuite/tests/programs/record_upd/Main.hs | 25 + testsuite/tests/programs/record_upd/Makefile | 3 + .../tests/programs/record_upd/record_upd.stdout | 1 + testsuite/tests/programs/record_upd/test.T | 6 + testsuite/tests/programs/rittri/Main.hs | 39 + testsuite/tests/programs/rittri/Makefile | 3 + testsuite/tests/programs/rittri/rittri.stdin | 39 + testsuite/tests/programs/rittri/rittri.stdout | 39 + testsuite/tests/programs/rittri/test.T | 6 + testsuite/tests/programs/sanders_array/Main.hs | 52 + testsuite/tests/programs/sanders_array/Makefile | 3 + .../programs/sanders_array/sanders_array.stdout | 1 + testsuite/tests/programs/sanders_array/test.T | 6 + .../tests/programs/seward-space-leak/Main.lhs | 650 + .../tests/programs/seward-space-leak/Makefile | 3 + testsuite/tests/programs/seward-space-leak/README | 13 + .../tests/programs/seward-space-leak/cg023.stdout | 1 + .../seward-space-leak/seward-space-leak.stdout | 1 + testsuite/tests/programs/seward-space-leak/test.T | 7 + testsuite/tests/programs/strict_anns/Main.hs | 13 + testsuite/tests/programs/strict_anns/Makefile | 3 + .../tests/programs/strict_anns/strict_anns.stdout | 2 + testsuite/tests/programs/strict_anns/test.T | 6 + .../tests/programs/thurston-modular-arith/Main.hs | 62 + .../tests/programs/thurston-modular-arith/Makefile | 3 + .../programs/thurston-modular-arith/TypeVal.hs | 89 + .../tests/programs/thurston-modular-arith/test.T | 8 + .../thurston-modular-arith.stdout | 1 + testsuite/tests/quasiquotation/Makefile | 11 + testsuite/tests/quasiquotation/T3953.hs | 6 + testsuite/tests/quasiquotation/T3953.stderr | 2 + testsuite/tests/quasiquotation/T4150.hs | 16 + testsuite/tests/quasiquotation/T4150.stderr | 3 + testsuite/tests/quasiquotation/T4150A.hs | 13 + testsuite/tests/quasiquotation/T4150template.txt | 3 + testsuite/tests/quasiquotation/T4491/A.hs | 9 + testsuite/tests/quasiquotation/T4491/Makefile | 3 + testsuite/tests/quasiquotation/T4491/T4491.hs | 30 + testsuite/tests/quasiquotation/T4491/T4491.stdout | 5 + testsuite/tests/quasiquotation/T4491/test.T | 11 + testsuite/tests/quasiquotation/T5204.hs | 39 + testsuite/tests/quasiquotation/T5204.stderr | 2 + testsuite/tests/quasiquotation/T7918.hs | 78 + testsuite/tests/quasiquotation/T7918.stdout | 27 + testsuite/tests/quasiquotation/T7918A.hs | 26 + testsuite/tests/quasiquotation/T7918B.hs | 19 + testsuite/tests/quasiquotation/all.T | 19 + testsuite/tests/quasiquotation/qq001/Makefile | 3 + testsuite/tests/quasiquotation/qq001/qq001.hs | 7 + testsuite/tests/quasiquotation/qq001/qq001.stderr | 4 + testsuite/tests/quasiquotation/qq001/test.T | 2 + testsuite/tests/quasiquotation/qq002/Makefile | 3 + testsuite/tests/quasiquotation/qq002/qq002.hs | 9 + testsuite/tests/quasiquotation/qq002/qq002.stderr | 4 + testsuite/tests/quasiquotation/qq002/test.T | 2 + testsuite/tests/quasiquotation/qq003/Makefile | 3 + testsuite/tests/quasiquotation/qq003/qq003.hs | 5 + testsuite/tests/quasiquotation/qq003/qq003.stderr | 4 + testsuite/tests/quasiquotation/qq003/test.T | 2 + testsuite/tests/quasiquotation/qq004/Makefile | 3 + testsuite/tests/quasiquotation/qq004/qq004.hs | 9 + testsuite/tests/quasiquotation/qq004/qq004.stderr | 4 + testsuite/tests/quasiquotation/qq004/test.T | 2 + testsuite/tests/quasiquotation/qq005/Expr.hs | 99 + testsuite/tests/quasiquotation/qq005/Main.hs | 13 + testsuite/tests/quasiquotation/qq005/Makefile | 3 + testsuite/tests/quasiquotation/qq005/qq005.stdout | 3 + testsuite/tests/quasiquotation/qq005/test.T | 11 + testsuite/tests/quasiquotation/qq006/Expr.hs | 99 + testsuite/tests/quasiquotation/qq006/Main.hs | 9 + testsuite/tests/quasiquotation/qq006/Makefile | 3 + testsuite/tests/quasiquotation/qq006/qq006.stderr | 4 + testsuite/tests/quasiquotation/qq006/test.T | 7 + testsuite/tests/quasiquotation/qq007/Makefile | 12 + testsuite/tests/quasiquotation/qq007/QQ.hs | 11 + testsuite/tests/quasiquotation/qq007/Test.hs | 13 + testsuite/tests/quasiquotation/qq007/test.T | 7 + testsuite/tests/quasiquotation/qq008/Makefile | 12 + testsuite/tests/quasiquotation/qq008/QQ.hs | 11 + testsuite/tests/quasiquotation/qq008/Test.hs | 13 + testsuite/tests/quasiquotation/qq008/qq008.stderr | 4 + testsuite/tests/quasiquotation/qq008/test.T | 7 + testsuite/tests/rebindable/DoParamM.hs | 303 + testsuite/tests/rebindable/DoParamM.stderr | 34 + testsuite/tests/rebindable/DoRestrictedM.hs | 99 + testsuite/tests/rebindable/Makefile | 3 + testsuite/tests/rebindable/T303.hs | 30 + testsuite/tests/rebindable/T4851.hs | 12 + testsuite/tests/rebindable/T5038.hs | 10 + testsuite/tests/rebindable/T5038.stdout | 1 + testsuite/tests/rebindable/T5821.hs | 71 + testsuite/tests/rebindable/all.T | 33 + testsuite/tests/rebindable/rebindable1.hs | 55 + testsuite/tests/rebindable/rebindable10.hs | 13 + testsuite/tests/rebindable/rebindable10.stdout | 2 + testsuite/tests/rebindable/rebindable2.hs | 122 + testsuite/tests/rebindable/rebindable2.stdout | 43 + testsuite/tests/rebindable/rebindable3.hs | 119 + testsuite/tests/rebindable/rebindable3.stdout | 43 + testsuite/tests/rebindable/rebindable4.hs | 127 + testsuite/tests/rebindable/rebindable4.stdout | 43 + testsuite/tests/rebindable/rebindable5.hs | 196 + testsuite/tests/rebindable/rebindable5.stdout | 43 + testsuite/tests/rebindable/rebindable6.hs | 184 + testsuite/tests/rebindable/rebindable6.stderr | 67 + testsuite/tests/rebindable/rebindable6.stdout | 43 + testsuite/tests/rebindable/rebindable7.hs | 38 + testsuite/tests/rebindable/rebindable7.stdout | 1 + testsuite/tests/rebindable/rebindable8.hs | 26 + testsuite/tests/rebindable/rebindable9.hs | 53 + testsuite/tests/rename/Makefile | 3 + testsuite/tests/rename/prog001/Makefile | 3 + testsuite/tests/rename/prog001/Rn037Help.hs | 3 + testsuite/tests/rename/prog001/rn037.hs | 9 + testsuite/tests/rename/prog001/test.T | 4 + testsuite/tests/rename/prog002/Makefile | 3 + testsuite/tests/rename/prog002/Rn037Help.hs | 3 + .../tests/rename/prog002/rename.prog002.stderr | 2 + .../rename/prog002/rename.prog002.stderr-hugs | 1 + testsuite/tests/rename/prog002/rnfail037.hs | 8 + testsuite/tests/rename/prog002/test.T | 4 + testsuite/tests/rename/prog003/A.hs | 2 + testsuite/tests/rename/prog003/B.hs | 5 + testsuite/tests/rename/prog003/Makefile | 3 + .../tests/rename/prog003/rename.prog003.stderr | 2 + .../rename/prog003/rename.prog003.stderr-hugs | 1 + testsuite/tests/rename/prog003/test.T | 4 + testsuite/tests/rename/prog004/A.hs | 6 + testsuite/tests/rename/prog004/B.hs | 4 + testsuite/tests/rename/prog004/C.hs | 7 + testsuite/tests/rename/prog004/Makefile | 3 + testsuite/tests/rename/prog004/test.T | 4 + testsuite/tests/rename/prog005/Makefile | 3 + .../tests/rename/prog005/VersionGraphClient.hs | 8 + .../rename/prog005/VersionGraphClient.hs-boot | 3 + testsuite/tests/rename/prog005/View.hs | 42 + testsuite/tests/rename/prog005/ViewType.hs | 12 + testsuite/tests/rename/prog005/test.T | 7 + testsuite/tests/rename/prog006/A.hs | 9 + testsuite/tests/rename/prog006/B/C.hs | 5 + testsuite/tests/rename/prog006/Main.hs | 7 + testsuite/tests/rename/prog006/Makefile | 45 + testsuite/tests/rename/prog006/Setup.lhs | 5 + testsuite/tests/rename/prog006/all.T | 7 + testsuite/tests/rename/prog006/pwd.hs | 12 + testsuite/tests/rename/prog006/test.cabal | 4 + testsuite/tests/rename/should_compile/DodgyA.hs | 9 + testsuite/tests/rename/should_compile/Imp100Aux.hs | 14 + .../tests/rename/should_compile/Imp100Aux.hs-boot | 23 + testsuite/tests/rename/should_compile/Imp10Aux.hs | 13 + .../tests/rename/should_compile/Imp10Aux.hs-boot | 24 + testsuite/tests/rename/should_compile/Imp500Aux.hs | 14 + .../tests/rename/should_compile/Imp500Aux.hs-boot | 23 + testsuite/tests/rename/should_compile/Makefile | 53 + testsuite/tests/rename/should_compile/Rn042_A.hs | 3 + testsuite/tests/rename/should_compile/Rn043_A.hs | 3 + testsuite/tests/rename/should_compile/Rn043_B.hs | 3 + testsuite/tests/rename/should_compile/Rn044_A.hs | 3 + testsuite/tests/rename/should_compile/Rn044_B.hs | 3 + testsuite/tests/rename/should_compile/Rn050_A.hs | 10 + testsuite/tests/rename/should_compile/Rn052Aux.hs | 6 + testsuite/tests/rename/should_compile/Rn053_A.hs | 5 + testsuite/tests/rename/should_compile/Rn053_B.hs | 5 + testsuite/tests/rename/should_compile/Rn059_A.hs | 5 + testsuite/tests/rename/should_compile/Rn059_B.hs | 5 + testsuite/tests/rename/should_compile/Rn065A.hs | 4 + testsuite/tests/rename/should_compile/Rn066_A.hs | 10 + testsuite/tests/rename/should_compile/Rn067_A.hs | 4 + testsuite/tests/rename/should_compile/RnAux017.hs | 14 + .../tests/rename/should_compile/RnAux017.hs-boot | 8 + testsuite/tests/rename/should_compile/T1074b.hs | 4 + testsuite/tests/rename/should_compile/T1789.hs | 11 + testsuite/tests/rename/should_compile/T1789.stderr | 12 + testsuite/tests/rename/should_compile/T1789_2.hs | 8 + .../tests/rename/should_compile/T1792_imports.hs | 6 + .../rename/should_compile/T1792_imports.stdout | 1 + testsuite/tests/rename/should_compile/T1954.hs | 8 + testsuite/tests/rename/should_compile/T1972.hs | 20 + testsuite/tests/rename/should_compile/T1972.stderr | 11 + testsuite/tests/rename/should_compile/T2205.hs | 17 + testsuite/tests/rename/should_compile/T2334.hs | 7 + testsuite/tests/rename/should_compile/T2435.hs | 4 + testsuite/tests/rename/should_compile/T2435Foo.hs | 3 + testsuite/tests/rename/should_compile/T2436.hs | 14 + testsuite/tests/rename/should_compile/T2436a.hs | 4 + testsuite/tests/rename/should_compile/T2506.hs | 6 + testsuite/tests/rename/should_compile/T2914.hs | 14 + .../rename/should_compile/T3103/Foreign/Ptr.hs | 10 + .../tests/rename/should_compile/T3103/GHC/Base.lhs | 17 + .../tests/rename/should_compile/T3103/GHC/Show.lhs | 10 + .../rename/should_compile/T3103/GHC/Unicode.hs | 5 + .../should_compile/T3103/GHC/Unicode.hs-boot | 4 + .../tests/rename/should_compile/T3103/GHC/Word.hs | 15 + .../tests/rename/should_compile/T3103/Makefile | 4 + .../tests/rename/should_compile/T3103/T3103.stderr | 3 + testsuite/tests/rename/should_compile/T3103/test.T | 15 + testsuite/tests/rename/should_compile/T3221.hs | 8 + testsuite/tests/rename/should_compile/T3262.hs | 21 + .../tests/rename/should_compile/T3262.stderr-ghc | 8 + testsuite/tests/rename/should_compile/T3371.hs | 10 + testsuite/tests/rename/should_compile/T3371.stderr | 2 + testsuite/tests/rename/should_compile/T3449.hs | 13 + .../tests/rename/should_compile/T3449.hs-boot | 9 + testsuite/tests/rename/should_compile/T3449.stderr | 2 + testsuite/tests/rename/should_compile/T3449A.hs | 10 + testsuite/tests/rename/should_compile/T3640.hs | 11 + testsuite/tests/rename/should_compile/T3823.stderr | 5 + testsuite/tests/rename/should_compile/T3823A.hs | 8 + .../tests/rename/should_compile/T3823A.hs-boot | 5 + testsuite/tests/rename/should_compile/T3823B.hs | 8 + testsuite/tests/rename/should_compile/T3901.hs | 16 + testsuite/tests/rename/should_compile/T3943.hs | 10 + testsuite/tests/rename/should_compile/T4003A.hs | 15 + .../tests/rename/should_compile/T4003A.hs-boot | 8 + testsuite/tests/rename/should_compile/T4003B.hs | 19 + testsuite/tests/rename/should_compile/T4239.hs | 14 + testsuite/tests/rename/should_compile/T4239.stdout | 1 + testsuite/tests/rename/should_compile/T4239A.hs | 10 + testsuite/tests/rename/should_compile/T4240.hs | 8 + testsuite/tests/rename/should_compile/T4240.stdout | 1 + testsuite/tests/rename/should_compile/T4240A.hs | 9 + testsuite/tests/rename/should_compile/T4240B.hs | 5 + testsuite/tests/rename/should_compile/T4478.hs | 7 + testsuite/tests/rename/should_compile/T4489.hs | 6 + testsuite/tests/rename/should_compile/T4489.stderr | 6 + testsuite/tests/rename/should_compile/T4534.hs | 9 + testsuite/tests/rename/should_compile/T5306.hs | 5 + testsuite/tests/rename/should_compile/T5306a.hs | 5 + testsuite/tests/rename/should_compile/T5306b.hs | 5 + testsuite/tests/rename/should_compile/T5331.hs | 16 + testsuite/tests/rename/should_compile/T5331.stderr | 13 + testsuite/tests/rename/should_compile/T5334.hs | 14 + testsuite/tests/rename/should_compile/T5334.stderr | 13 + testsuite/tests/rename/should_compile/T5592.hs | 9 + testsuite/tests/rename/should_compile/T5592.stdout | 1 + testsuite/tests/rename/should_compile/T5592a.hs | 4 + testsuite/tests/rename/should_compile/T5867.hs | 5 + testsuite/tests/rename/should_compile/T5867.stderr | 8 + testsuite/tests/rename/should_compile/T5867a.hs | 4 + testsuite/tests/rename/should_compile/T6027.hs | 10 + testsuite/tests/rename/should_compile/T6038.hs | 7 + testsuite/tests/rename/should_compile/T6120.hs | 10 + testsuite/tests/rename/should_compile/T7007.hs | 10 + testsuite/tests/rename/should_compile/T7085.hs | 8 + testsuite/tests/rename/should_compile/T7085.stderr | 3 + testsuite/tests/rename/should_compile/T7145a.hs | 3 + testsuite/tests/rename/should_compile/T7145b.hs | 10 + .../tests/rename/should_compile/T7145b.stderr | 2 + testsuite/tests/rename/should_compile/T7167.hs | 5 + testsuite/tests/rename/should_compile/T7167.stderr | 2 + testsuite/tests/rename/should_compile/T7336.hs | 8 + testsuite/tests/rename/should_compile/T7336.stderr | 3 + testsuite/tests/rename/should_compile/T7963.hs | 7 + testsuite/tests/rename/should_compile/T7963.stdout | 2 + testsuite/tests/rename/should_compile/T7963a.hs | 4 + testsuite/tests/rename/should_compile/T7969.hs | 5 + testsuite/tests/rename/should_compile/T7969.stdout | 1 + testsuite/tests/rename/should_compile/T7969a.hs | 3 + testsuite/tests/rename/should_compile/all.T | 216 + testsuite/tests/rename/should_compile/dodgy.hs | 4 + testsuite/tests/rename/should_compile/mc09.hs | 10 + testsuite/tests/rename/should_compile/mc10.hs | 15 + .../tests/rename/should_compile/mc10.stderr-ghc | 2 + testsuite/tests/rename/should_compile/mc11.hs | 16 + testsuite/tests/rename/should_compile/mc12.hs | 11 + testsuite/tests/rename/should_compile/rn003.hs | 9 + testsuite/tests/rename/should_compile/rn005.hs | 8 + testsuite/tests/rename/should_compile/rn006.hs | 14 + testsuite/tests/rename/should_compile/rn009.hs | 2 + testsuite/tests/rename/should_compile/rn010.hs | 12 + testsuite/tests/rename/should_compile/rn011.hs | 101 + testsuite/tests/rename/should_compile/rn012.hs | 503 + testsuite/tests/rename/should_compile/rn013.hs | 21 + testsuite/tests/rename/should_compile/rn017.hs | 14 + testsuite/tests/rename/should_compile/rn019.hs | 4 + testsuite/tests/rename/should_compile/rn020.hs | 11 + testsuite/tests/rename/should_compile/rn022.hs | 11 + testsuite/tests/rename/should_compile/rn023.hs | 3 + testsuite/tests/rename/should_compile/rn024.hs | 9 + testsuite/tests/rename/should_compile/rn025.hs | 5 + testsuite/tests/rename/should_compile/rn026.hs | 12 + testsuite/tests/rename/should_compile/rn027.hs | 12 + testsuite/tests/rename/should_compile/rn028.hs | 18 + testsuite/tests/rename/should_compile/rn029.hs | 17 + testsuite/tests/rename/should_compile/rn031.hs | 12 + testsuite/tests/rename/should_compile/rn032.hs | 18 + testsuite/tests/rename/should_compile/rn033.hs | 14 + testsuite/tests/rename/should_compile/rn034.hs | 12 + testsuite/tests/rename/should_compile/rn035.hs | 10 + testsuite/tests/rename/should_compile/rn036.hs | 14 + testsuite/tests/rename/should_compile/rn037.hs | 4 + .../tests/rename/should_compile/rn037.stderr-ghc | 5 + testsuite/tests/rename/should_compile/rn039.hs | 6 + .../tests/rename/should_compile/rn039.stderr-ghc | 5 + testsuite/tests/rename/should_compile/rn040.hs | 8 + .../tests/rename/should_compile/rn040.stderr-ghc | 4 + testsuite/tests/rename/should_compile/rn041.hs | 13 + .../tests/rename/should_compile/rn041.stderr-ghc | 6 + testsuite/tests/rename/should_compile/rn042.hs | 5 + testsuite/tests/rename/should_compile/rn043.hs | 6 + testsuite/tests/rename/should_compile/rn044.hs | 8 + testsuite/tests/rename/should_compile/rn045.hs | 9 + testsuite/tests/rename/should_compile/rn046.hs | 6 + .../tests/rename/should_compile/rn046.stderr-ghc | 8 + testsuite/tests/rename/should_compile/rn047.hs | 13 + .../tests/rename/should_compile/rn047.stderr-ghc | 2 + testsuite/tests/rename/should_compile/rn048.hs | 15 + testsuite/tests/rename/should_compile/rn049.hs | 13 + testsuite/tests/rename/should_compile/rn049.stderr | 4 + testsuite/tests/rename/should_compile/rn050.hs | 13 + testsuite/tests/rename/should_compile/rn050.stderr | 8 + testsuite/tests/rename/should_compile/rn051.hs | 13 + testsuite/tests/rename/should_compile/rn052.hs | 10 + testsuite/tests/rename/should_compile/rn053.hs | 7 + testsuite/tests/rename/should_compile/rn054.hs | 5 + testsuite/tests/rename/should_compile/rn055.hs | 6 + .../tests/rename/should_compile/rn055.stderr-ghc | 2 + testsuite/tests/rename/should_compile/rn056.hs | 9 + testsuite/tests/rename/should_compile/rn057.hs | 6 + testsuite/tests/rename/should_compile/rn058.hs | 14 + testsuite/tests/rename/should_compile/rn059.hs | 13 + testsuite/tests/rename/should_compile/rn060.hs | 6 + testsuite/tests/rename/should_compile/rn061.hs | 3 + testsuite/tests/rename/should_compile/rn062.hs | 8 + testsuite/tests/rename/should_compile/rn063.hs | 14 + testsuite/tests/rename/should_compile/rn063.stderr | 4 + testsuite/tests/rename/should_compile/rn064.hs | 17 + testsuite/tests/rename/should_compile/rn064.stderr | 4 + testsuite/tests/rename/should_compile/rn065.hs | 10 + testsuite/tests/rename/should_compile/rn066.hs | 13 + testsuite/tests/rename/should_compile/rn066.stderr | 8 + testsuite/tests/rename/should_compile/rn067.hs | 14 + testsuite/tests/rename/should_compile/timing001.hs | 507 + testsuite/tests/rename/should_compile/timing002.hs | 504 + testsuite/tests/rename/should_compile/timing003.hs | 508 + testsuite/tests/rename/should_fail/Makefile | 3 + testsuite/tests/rename/should_fail/Misplaced.hs | 10 + .../tests/rename/should_fail/Misplaced.stderr | 4 + testsuite/tests/rename/should_fail/RnFail047_A.hs | 8 + .../tests/rename/should_fail/RnFail047_A.hs-boot | 6 + testsuite/tests/rename/should_fail/RnFail055.hs | 48 + .../tests/rename/should_fail/RnFail055.hs-boot | 29 + .../tests/rename/should_fail/RnFail055_aux.hs | 3 + testsuite/tests/rename/should_fail/Rnfail040_A.hs | 2 + testsuite/tests/rename/should_fail/T1595a.hs | 5 + testsuite/tests/rename/should_fail/T1595a.stderr | 2 + testsuite/tests/rename/should_fail/T2310.hs | 5 + testsuite/tests/rename/should_fail/T2310.stderr | 10 + testsuite/tests/rename/should_fail/T2490.hs | 10 + testsuite/tests/rename/should_fail/T2490.stderr | 15 + testsuite/tests/rename/should_fail/T2723.hs | 16 + testsuite/tests/rename/should_fail/T2723.stderr | 4 + testsuite/tests/rename/should_fail/T2901.hs | 6 + testsuite/tests/rename/should_fail/T2901.stderr | 4 + testsuite/tests/rename/should_fail/T2993.hs | 8 + testsuite/tests/rename/should_fail/T2993.stderr | 2 + testsuite/tests/rename/should_fail/T3265.hs | 9 + testsuite/tests/rename/should_fail/T3265.stderr | 8 + testsuite/tests/rename/should_fail/T3792.hs | 4 + testsuite/tests/rename/should_fail/T3792.stderr | 2 + testsuite/tests/rename/should_fail/T4042.hs | 12 + testsuite/tests/rename/should_fail/T4042.stderr | 4 + testsuite/tests/rename/should_fail/T5211.hs | 16 + testsuite/tests/rename/should_fail/T5211.stderr | 5 + testsuite/tests/rename/should_fail/T5281.hs | 8 + testsuite/tests/rename/should_fail/T5281.stderr | 4 + testsuite/tests/rename/should_fail/T5281A.hs | 7 + testsuite/tests/rename/should_fail/T5372.hs | 4 + testsuite/tests/rename/should_fail/T5372.stderr | 6 + testsuite/tests/rename/should_fail/T5372a.hs | 2 + testsuite/tests/rename/should_fail/T5385.hs | 3 + testsuite/tests/rename/should_fail/T5385.stderr | 8 + testsuite/tests/rename/should_fail/T5385a.hs | 3 + testsuite/tests/rename/should_fail/T5513.hs | 4 + testsuite/tests/rename/should_fail/T5513.stderr | 2 + testsuite/tests/rename/should_fail/T5533.hs | 6 + testsuite/tests/rename/should_fail/T5533.stderr | 4 + testsuite/tests/rename/should_fail/T5589.hs | 6 + testsuite/tests/rename/should_fail/T5589.stderr | 5 + testsuite/tests/rename/should_fail/T5657.hs | 3 + testsuite/tests/rename/should_fail/T5657.stderr | 5 + testsuite/tests/rename/should_fail/T5745.hs | 6 + testsuite/tests/rename/should_fail/T5745.stderr | 2 + testsuite/tests/rename/should_fail/T5745a.hs | 3 + testsuite/tests/rename/should_fail/T5745b.hs | 4 + testsuite/tests/rename/should_fail/T5892a.hs | 12 + testsuite/tests/rename/should_fail/T5892a.stderr | 10 + testsuite/tests/rename/should_fail/T5892b.hs | 11 + testsuite/tests/rename/should_fail/T5892b.stderr | 4 + testsuite/tests/rename/should_fail/T5951.hs | 11 + testsuite/tests/rename/should_fail/T5951.stderr | 2 + testsuite/tests/rename/should_fail/T6060.hs | 5 + testsuite/tests/rename/should_fail/T6060.stderr | 4 + testsuite/tests/rename/should_fail/T6148.hs | 15 + testsuite/tests/rename/should_fail/T6148.stderr | 15 + testsuite/tests/rename/should_fail/T7164.hs | 8 + testsuite/tests/rename/should_fail/T7164.stderr | 5 + testsuite/tests/rename/should_fail/T7338.hs | 5 + testsuite/tests/rename/should_fail/T7338.stderr | 6 + testsuite/tests/rename/should_fail/T7338a.hs | 11 + testsuite/tests/rename/should_fail/T7338a.stderr | 10 + testsuite/tests/rename/should_fail/T7454.hs | 7 + testsuite/tests/rename/should_fail/T7454.stderr | 3 + testsuite/tests/rename/should_fail/T7906.hs | 5 + testsuite/tests/rename/should_fail/T7906.stderr | 4 + testsuite/tests/rename/should_fail/T7937.hs | 10 + testsuite/tests/rename/should_fail/T7937.stderr | 4 + testsuite/tests/rename/should_fail/T7943.hs | 4 + testsuite/tests/rename/should_fail/T7943.stderr | 2 + testsuite/tests/rename/should_fail/T8448.hs | 7 + testsuite/tests/rename/should_fail/T8448.stderr | 2 + testsuite/tests/rename/should_fail/all.T | 113 + testsuite/tests/rename/should_fail/mc13.hs | 14 + testsuite/tests/rename/should_fail/mc13.stderr | 2 + testsuite/tests/rename/should_fail/mc14.hs | 16 + testsuite/tests/rename/should_fail/mc14.stderr | 2 + testsuite/tests/rename/should_fail/rn_dup.hs | 19 + testsuite/tests/rename/should_fail/rn_dup.stderr | 22 + testsuite/tests/rename/should_fail/rnfail001.hs | 3 + .../tests/rename/should_fail/rnfail001.stderr | 6 + .../tests/rename/should_fail/rnfail001.stderr-hugs | 1 + testsuite/tests/rename/should_fail/rnfail002.hs | 10 + .../tests/rename/should_fail/rnfail002.stderr | 5 + .../tests/rename/should_fail/rnfail002.stderr-hugs | 1 + testsuite/tests/rename/should_fail/rnfail003.hs | 4 + .../tests/rename/should_fail/rnfail003.stderr | 5 + .../tests/rename/should_fail/rnfail003.stderr-hugs | 1 + testsuite/tests/rename/should_fail/rnfail004.hs | 8 + .../tests/rename/should_fail/rnfail004.stderr | 10 + .../tests/rename/should_fail/rnfail004.stderr-hugs | 1 + .../tests/rename/should_fail/rnfail005.stderr | 8 + testsuite/tests/rename/should_fail/rnfail007.hs | 5 + .../tests/rename/should_fail/rnfail007.stderr | 3 + testsuite/tests/rename/should_fail/rnfail008.hs | 19 + .../tests/rename/should_fail/rnfail008.stderr | 2 + .../tests/rename/should_fail/rnfail008.stderr-hugs | 1 + testsuite/tests/rename/should_fail/rnfail009.hs | 5 + .../tests/rename/should_fail/rnfail009.stderr | 5 + .../tests/rename/should_fail/rnfail009.stderr-hugs | 1 + testsuite/tests/rename/should_fail/rnfail010.hs | 6 + .../tests/rename/should_fail/rnfail010.stderr | 5 + .../tests/rename/should_fail/rnfail010.stderr-hugs | 1 + testsuite/tests/rename/should_fail/rnfail011.hs | 6 + .../tests/rename/should_fail/rnfail011.stderr | 5 + .../tests/rename/should_fail/rnfail011.stderr-hugs | 1 + testsuite/tests/rename/should_fail/rnfail012.hs | 9 + .../tests/rename/should_fail/rnfail012.stderr | 5 + .../tests/rename/should_fail/rnfail012.stderr-hugs | 1 + testsuite/tests/rename/should_fail/rnfail013.hs | 9 + .../tests/rename/should_fail/rnfail013.stderr | 5 + .../tests/rename/should_fail/rnfail013.stderr-hugs | 1 + testsuite/tests/rename/should_fail/rnfail015.hs | 20 + .../tests/rename/should_fail/rnfail015.stderr | 5 + .../tests/rename/should_fail/rnfail015.stderr-hugs | 1 + testsuite/tests/rename/should_fail/rnfail016.hs | 8 + .../tests/rename/should_fail/rnfail016.stderr | 6 + .../tests/rename/should_fail/rnfail016.stderr-hugs | 1 + testsuite/tests/rename/should_fail/rnfail017.hs | 17 + .../tests/rename/should_fail/rnfail017.stderr | 8 + testsuite/tests/rename/should_fail/rnfail018.hs | 15 + .../tests/rename/should_fail/rnfail018.stderr | 8 + testsuite/tests/rename/should_fail/rnfail019.hs | 7 + .../tests/rename/should_fail/rnfail019.stderr | 6 + .../tests/rename/should_fail/rnfail019.stderr-hugs | 1 + testsuite/tests/rename/should_fail/rnfail020.hs | 21 + testsuite/tests/rename/should_fail/rnfail021.hs | 6 + .../tests/rename/should_fail/rnfail021.stderr | 2 + .../tests/rename/should_fail/rnfail021.stderr-hugs | 1 + testsuite/tests/rename/should_fail/rnfail022.hs | 9 + .../tests/rename/should_fail/rnfail022.stderr | 4 + .../tests/rename/should_fail/rnfail022.stderr-hugs | 1 + testsuite/tests/rename/should_fail/rnfail023.hs | 15 + .../tests/rename/should_fail/rnfail023.stderr | 9 + .../tests/rename/should_fail/rnfail023.stderr-hugs | 1 + testsuite/tests/rename/should_fail/rnfail024.hs | 6 + .../tests/rename/should_fail/rnfail024.stderr | 6 + .../tests/rename/should_fail/rnfail024.stderr-hugs | 1 + testsuite/tests/rename/should_fail/rnfail025.hs | 6 + .../tests/rename/should_fail/rnfail025.stderr | 4 + .../tests/rename/should_fail/rnfail025.stderr-hugs | 1 + testsuite/tests/rename/should_fail/rnfail026.hs | 19 + .../tests/rename/should_fail/rnfail026.stderr | 9 + .../tests/rename/should_fail/rnfail026.stderr-hugs | 1 + testsuite/tests/rename/should_fail/rnfail027.hs | 5 + .../tests/rename/should_fail/rnfail027.stderr | 3 + .../tests/rename/should_fail/rnfail027.stderr-hugs | 1 + testsuite/tests/rename/should_fail/rnfail028.hs | 2 + .../tests/rename/should_fail/rnfail028.stderr | 2 + .../tests/rename/should_fail/rnfail028.stderr-hugs | 1 + testsuite/tests/rename/should_fail/rnfail029.hs | 4 + .../tests/rename/should_fail/rnfail029.stderr | 8 + .../tests/rename/should_fail/rnfail029.stderr-hugs | 2 + testsuite/tests/rename/should_fail/rnfail030.hs | 3 + .../tests/rename/should_fail/rnfail030.stderr | 2 + .../tests/rename/should_fail/rnfail030.stderr-hugs | 1 + testsuite/tests/rename/should_fail/rnfail031.hs | 3 + .../tests/rename/should_fail/rnfail031.stderr | 2 + .../tests/rename/should_fail/rnfail031.stderr-hugs | 1 + testsuite/tests/rename/should_fail/rnfail032.hs | 3 + .../tests/rename/should_fail/rnfail032.stderr | 7 + .../tests/rename/should_fail/rnfail032.stderr-hugs | 1 + testsuite/tests/rename/should_fail/rnfail033.hs | 3 + .../tests/rename/should_fail/rnfail033.stderr | 7 + .../tests/rename/should_fail/rnfail033.stderr-hugs | 1 + testsuite/tests/rename/should_fail/rnfail034.hs | 4 + .../tests/rename/should_fail/rnfail034.stderr | 6 + .../tests/rename/should_fail/rnfail034.stderr-hugs | 1 + testsuite/tests/rename/should_fail/rnfail035.hs | 3 + .../tests/rename/should_fail/rnfail035.stderr | 2 + .../tests/rename/should_fail/rnfail035.stderr-hugs | 1 + testsuite/tests/rename/should_fail/rnfail039.hs | 12 + .../tests/rename/should_fail/rnfail039.stderr | 2 + .../tests/rename/should_fail/rnfail039.stderr-hugs | 1 + testsuite/tests/rename/should_fail/rnfail040.hs | 11 + .../tests/rename/should_fail/rnfail040.stderr | 8 + .../tests/rename/should_fail/rnfail040.stderr-hugs | 2 + testsuite/tests/rename/should_fail/rnfail041.hs | 7 + .../tests/rename/should_fail/rnfail041.stderr | 6 + .../tests/rename/should_fail/rnfail041.stderr-hugs | 1 + testsuite/tests/rename/should_fail/rnfail042.hs | 9 + .../tests/rename/should_fail/rnfail042.stderr | 8 + .../tests/rename/should_fail/rnfail042.stderr-hugs | 1 + testsuite/tests/rename/should_fail/rnfail043.hs | 10 + .../tests/rename/should_fail/rnfail043.stderr | 5 + testsuite/tests/rename/should_fail/rnfail044.hs | 8 + .../tests/rename/should_fail/rnfail044.stderr | 7 + testsuite/tests/rename/should_fail/rnfail045.hs | 9 + .../tests/rename/should_fail/rnfail045.stderr | 10 + testsuite/tests/rename/should_fail/rnfail046.hs | 4 + .../tests/rename/should_fail/rnfail046.stderr | 2 + testsuite/tests/rename/should_fail/rnfail047.hs | 9 + .../tests/rename/should_fail/rnfail047.stderr | 3 + testsuite/tests/rename/should_fail/rnfail048.hs | 13 + .../tests/rename/should_fail/rnfail048.stderr | 9 + testsuite/tests/rename/should_fail/rnfail049.hs | 14 + .../tests/rename/should_fail/rnfail049.stderr | 2 + testsuite/tests/rename/should_fail/rnfail050.hs | 12 + .../tests/rename/should_fail/rnfail050.stderr | 2 + testsuite/tests/rename/should_fail/rnfail051.hs | 11 + .../tests/rename/should_fail/rnfail051.stderr | 3 + testsuite/tests/rename/should_fail/rnfail052.hs | 15 + .../tests/rename/should_fail/rnfail052.stderr | 5 + testsuite/tests/rename/should_fail/rnfail053.hs | 6 + .../tests/rename/should_fail/rnfail053.stderr | 4 + testsuite/tests/rename/should_fail/rnfail054.hs | 6 + .../tests/rename/should_fail/rnfail054.stderr | 5 + .../tests/rename/should_fail/rnfail055.stderr | 81 + testsuite/tests/rename/should_fail/rnfail056.hs | 8 + .../tests/rename/should_fail/rnfail056.stderr | 4 + testsuite/tests/rename/should_fail/rnfail057.hs | 5 + .../tests/rename/should_fail/rnfail057.stderr | 3 + testsuite/tests/roles/Makefile | 3 + testsuite/tests/roles/should_compile/Makefile | 3 + testsuite/tests/roles/should_compile/Roles1.hs | 18 + testsuite/tests/roles/should_compile/Roles1.stderr | 57 + testsuite/tests/roles/should_compile/Roles13.hs | 12 + .../tests/roles/should_compile/Roles13.stderr | 20 + testsuite/tests/roles/should_compile/Roles2.hs | 9 + testsuite/tests/roles/should_compile/Roles2.stderr | 22 + testsuite/tests/roles/should_compile/Roles3.hs | 21 + testsuite/tests/roles/should_compile/Roles3.stderr | 39 + testsuite/tests/roles/should_compile/Roles4.hs | 17 + testsuite/tests/roles/should_compile/Roles4.stderr | 28 + .../tests/roles/should_compile/RolesIArray.hs | 10 + testsuite/tests/roles/should_compile/all.T | 6 + testsuite/tests/roles/should_fail/Makefile | 9 + testsuite/tests/roles/should_fail/Roles10.hs | 16 + testsuite/tests/roles/should_fail/Roles10.stderr | 10 + testsuite/tests/roles/should_fail/Roles11.hs | 8 + testsuite/tests/roles/should_fail/Roles11.stderr | 5 + testsuite/tests/roles/should_fail/Roles12.hs | 5 + testsuite/tests/roles/should_fail/Roles12.hs-boot | 3 + testsuite/tests/roles/should_fail/Roles12.stderr | 7 + testsuite/tests/roles/should_fail/Roles5.hs | 9 + testsuite/tests/roles/should_fail/Roles5.stderr | 14 + testsuite/tests/roles/should_fail/Roles6.hs | 8 + testsuite/tests/roles/should_fail/Roles6.stderr | 6 + testsuite/tests/roles/should_fail/Roles7.hs | 7 + testsuite/tests/roles/should_fail/Roles7.stderr | 4 + testsuite/tests/roles/should_fail/Roles8.hs | 13 + testsuite/tests/roles/should_fail/Roles8.stderr | 10 + testsuite/tests/roles/should_fail/Roles9.stderr | 7 + testsuite/tests/roles/should_fail/all.T | 9 + testsuite/tests/rts/Makefile | 121 + testsuite/tests/rts/T2047.hs | 102 + testsuite/tests/rts/T2615.hs | 9 + testsuite/tests/rts/T2615.stdout | 1 + testsuite/tests/rts/T2783.hs | 1 + testsuite/tests/rts/T2783.stderr | 1 + testsuite/tests/rts/T3236.c | 7 + testsuite/tests/rts/T3236.stderr | 1 + testsuite/tests/rts/T3424.hs | 611 + testsuite/tests/rts/T3424.stdout | 1 + testsuite/tests/rts/T4059.hs | 22 + testsuite/tests/rts/T4059.stdout | 2 + testsuite/tests/rts/T4059_c.c | 4 + testsuite/tests/rts/T4850.hs | 32 + testsuite/tests/rts/T4850.stdout | 1 + testsuite/tests/rts/T5250.hs | 60 + testsuite/tests/rts/T5423.hs | 14 + testsuite/tests/rts/T5423.stdout | 2 + testsuite/tests/rts/T5423_cmm.cmm | 16 + testsuite/tests/rts/T5435.hs | 60 + testsuite/tests/rts/T5435_asm.c | 49 + testsuite/tests/rts/T5435_dyn_asm.stderr-mingw32 | 1 + testsuite/tests/rts/T5435_dyn_asm.stdout | 5 + testsuite/tests/rts/T5435_dyn_asm.stdout-darwin | 3 + testsuite/tests/rts/T5435_dyn_asm.stdout-mingw32 | 3 + testsuite/tests/rts/T5435_dyn_gcc.stderr-mingw32 | 1 + testsuite/tests/rts/T5435_dyn_gcc.stdout | 2 + testsuite/tests/rts/T5435_gcc.c | 8 + testsuite/tests/rts/T5435_v_asm.stdout | 5 + testsuite/tests/rts/T5435_v_asm.stdout-darwin | 3 + testsuite/tests/rts/T5435_v_asm.stdout-mingw32 | 3 + testsuite/tests/rts/T5435_v_gcc.stdout | 2 + testsuite/tests/rts/T5644/Conf.hs | 7 + testsuite/tests/rts/T5644/Makefile | 3 + testsuite/tests/rts/T5644/ManyQueue.hs | 82 + testsuite/tests/rts/T5644/T5644.stderr | 3 + testsuite/tests/rts/T5644/Util.hs | 29 + testsuite/tests/rts/T5644/all.T | 7 + testsuite/tests/rts/T5644/heap-overflow.hs | 8 + testsuite/tests/rts/T5993.hs | 6 + testsuite/tests/rts/T5993.stdout | 1 + testsuite/tests/rts/T6006.hs | 7 + testsuite/tests/rts/T6006.stdout | 2 + testsuite/tests/rts/T6006.stdout-mingw32 | 2 + testsuite/tests/rts/T6006_c.c | 9 + testsuite/tests/rts/T7037.hs | 1 + testsuite/tests/rts/T7037.stdout | 1 + testsuite/tests/rts/T7037_main.c | 7 + testsuite/tests/rts/T7040.hs | 9 + testsuite/tests/rts/T7040.stdout | 2 + testsuite/tests/rts/T7040_c.c | 11 + testsuite/tests/rts/T7040_c.h | 2 + testsuite/tests/rts/T7040_ghci.hs | 9 + testsuite/tests/rts/T7040_ghci.stdout | 2 + testsuite/tests/rts/T7040_ghci_c.c | 11 + testsuite/tests/rts/T7087.hs | 8 + testsuite/tests/rts/T7087.stderr | 1 + testsuite/tests/rts/T7160.hs | 28 + testsuite/tests/rts/T7160.stderr | 6 + testsuite/tests/rts/T7227.hs | 1 + testsuite/tests/rts/T7636.hs | 13 + testsuite/tests/rts/T7636.stderr | 1 + testsuite/tests/rts/T7815.hs | 29 + testsuite/tests/rts/T7919.hs | 8 + testsuite/tests/rts/T7919.stdout | 1 + testsuite/tests/rts/T7919.stdout-ws-32 | 1 + testsuite/tests/rts/T7919A.hs | 65 + testsuite/tests/rts/T8035.hs | 10 + testsuite/tests/rts/T8035.stdout | 1 + testsuite/tests/rts/T8209.hs | 13 + testsuite/tests/rts/T8242.hs | 42 + testsuite/tests/rts/Test.hs | 11 + testsuite/tests/rts/all.T | 201 + testsuite/tests/rts/atomicinc.c | 19 + testsuite/tests/rts/bug1010.hs | 16 + testsuite/tests/rts/bug1010.stdout | 1 + testsuite/tests/rts/derefnull.hs | 14 + .../rts/derefnull.stderr-x86_64-unknown-openbsd | 1 + .../rts/derefnull.stdout-i386-unknown-mingw32 | 1 + testsuite/tests/rts/divbyzero.hs | 13 + .../rts/divbyzero.stderr-x86_64-unknown-openbsd | 1 + .../rts/divbyzero.stdout-i386-unknown-mingw32 | 1 + testsuite/tests/rts/exec_signals.hs | 20 + testsuite/tests/rts/exec_signals_child.c | 47 + testsuite/tests/rts/exec_signals_prepare.c | 29 + testsuite/tests/rts/ffishutdown.hs | 13 + testsuite/tests/rts/ffishutdown.stderr | 1 + testsuite/tests/rts/libfoo_T2615.c | 2 + testsuite/tests/rts/libfoo_script_T2615.so | 5 + testsuite/tests/rts/linker_unload.c | 84 + testsuite/tests/rts/linker_unload.stdout | 1 + testsuite/tests/rts/outofmem.hs | 7 + testsuite/tests/rts/outofmem.stderr | 1 + .../tests/rts/outofmem.stderr-i386-apple-darwin | 1 + .../tests/rts/outofmem.stderr-i386-unknown-mingw32 | 1 + .../tests/rts/outofmem.stderr-powerpc-apple-darwin | 1 + testsuite/tests/rts/outofmem.stderr-ws-32 | 1 + testsuite/tests/rts/outofmem.stderr-ws-64 | 1 + .../rts/outofmem.stderr-x86_64-unknown-mingw32 | 1 + testsuite/tests/rts/outofmem.stdout | 1 + testsuite/tests/rts/outofmem2.hs | 10 + testsuite/tests/rts/outofmem2.stderr | 3 + testsuite/tests/rts/outofmem2.stdout | 1 + testsuite/tests/rts/return_mem_to_os.hs | 21 + testsuite/tests/rts/return_mem_to_os.stdout | 21 + testsuite/tests/rts/rtsflags001.hs | 1 + testsuite/tests/rts/rtsflags001.stderr-ws-32 | 1 + testsuite/tests/rts/rtsflags001.stderr-ws-64 | 1 + testsuite/tests/rts/rtsflags002.hs | 1 + testsuite/tests/rts/rtsflags002.stderr | 1 + testsuite/tests/rts/spalign.c | 30 + testsuite/tests/rts/stablename001.hs | 13 + testsuite/tests/rts/stablename001.stdout | 1 + testsuite/tests/rts/stack001.hs | 9 + testsuite/tests/rts/stack002.hs | 2 + testsuite/tests/rts/stack003.hs | 17 + testsuite/tests/rts/stack003.stdout | 1 + testsuite/tests/rts/testblockalloc.c | 83 + testsuite/tests/rts/testheapalloced.c | 100 + testsuite/tests/rts/testwsdeque.c | 167 + testsuite/tests/rts/traceEvent.hs | 5 + testsuite/tests/runghc/Makefile | 7 + testsuite/tests/runghc/T7859.stderr | 1 + testsuite/tests/runghc/T7859.stderr-mingw32 | 1 + testsuite/tests/runghc/all.T | 6 + testsuite/tests/safeHaskell/Makefile | 3 + testsuite/tests/safeHaskell/check/Check01.hs | 10 + testsuite/tests/safeHaskell/check/Check01.stderr | 4 + testsuite/tests/safeHaskell/check/Check01_A.hs | 15 + testsuite/tests/safeHaskell/check/Check01_B.hs | 10 + testsuite/tests/safeHaskell/check/Check02.hs | 9 + testsuite/tests/safeHaskell/check/Check02.stderr | 1 + testsuite/tests/safeHaskell/check/Check02_A.hs | 16 + testsuite/tests/safeHaskell/check/Check02_B.hs | 10 + testsuite/tests/safeHaskell/check/Check03.hs | 9 + testsuite/tests/safeHaskell/check/Check03.stderr | 1 + testsuite/tests/safeHaskell/check/Check03_A.hs | 15 + testsuite/tests/safeHaskell/check/Check03_B.hs | 10 + testsuite/tests/safeHaskell/check/Check04.hs | 7 + testsuite/tests/safeHaskell/check/Check04.stderr | 2 + testsuite/tests/safeHaskell/check/Check04_1.hs | 9 + testsuite/tests/safeHaskell/check/Check04_A.hs | 15 + testsuite/tests/safeHaskell/check/Check04_B.hs | 10 + testsuite/tests/safeHaskell/check/Check05.hs | 7 + testsuite/tests/safeHaskell/check/Check05.stderr | 3 + testsuite/tests/safeHaskell/check/Check06.hs | 13 + testsuite/tests/safeHaskell/check/Check06.stderr | 5 + testsuite/tests/safeHaskell/check/Check06_A.hs | 6 + testsuite/tests/safeHaskell/check/Check07.hs | 14 + testsuite/tests/safeHaskell/check/Check07.stderr | 3 + testsuite/tests/safeHaskell/check/Check07_A.hs | 8 + testsuite/tests/safeHaskell/check/Check07_B.hs | 8 + testsuite/tests/safeHaskell/check/Check08.hs | 14 + testsuite/tests/safeHaskell/check/Check08.stderr | 6 + testsuite/tests/safeHaskell/check/Check08_A.hs | 8 + testsuite/tests/safeHaskell/check/Check08_B.hs | 8 + testsuite/tests/safeHaskell/check/Check09.hs | 9 + testsuite/tests/safeHaskell/check/Check09.stderr | 8 + testsuite/tests/safeHaskell/check/Check10.hs | 9 + testsuite/tests/safeHaskell/check/CheckA.hs | 15 + testsuite/tests/safeHaskell/check/CheckB.hs | 10 + testsuite/tests/safeHaskell/check/CheckB.stderr | 2 + testsuite/tests/safeHaskell/check/CheckB_Aux.hs | 15 + testsuite/tests/safeHaskell/check/Makefile | 3 + testsuite/tests/safeHaskell/check/all.T | 72 + .../tests/safeHaskell/check/pkg01/ImpSafe01.hs | 12 + .../tests/safeHaskell/check/pkg01/ImpSafe01.stderr | 4 + .../tests/safeHaskell/check/pkg01/ImpSafe02.hs | 12 + .../tests/safeHaskell/check/pkg01/ImpSafeOnly01.hs | 8 + .../tests/safeHaskell/check/pkg01/ImpSafeOnly02.hs | 8 + .../tests/safeHaskell/check/pkg01/ImpSafeOnly03.hs | 8 + .../safeHaskell/check/pkg01/ImpSafeOnly03.stderr | 4 + .../tests/safeHaskell/check/pkg01/ImpSafeOnly04.hs | 8 + .../tests/safeHaskell/check/pkg01/ImpSafeOnly05.hs | 8 + .../safeHaskell/check/pkg01/ImpSafeOnly05.stderr | 4 + .../tests/safeHaskell/check/pkg01/ImpSafeOnly06.hs | 8 + .../tests/safeHaskell/check/pkg01/ImpSafeOnly07.hs | 8 + .../safeHaskell/check/pkg01/ImpSafeOnly07.stderr | 6 + .../tests/safeHaskell/check/pkg01/ImpSafeOnly08.hs | 8 + .../safeHaskell/check/pkg01/ImpSafeOnly08.stderr | 6 + .../tests/safeHaskell/check/pkg01/ImpSafeOnly09.hs | 8 + .../safeHaskell/check/pkg01/ImpSafeOnly09.stderr | 3 + .../tests/safeHaskell/check/pkg01/ImpSafeOnly10.hs | 8 + .../tests/safeHaskell/check/pkg01/M_SafePkg.hs | 6 + .../tests/safeHaskell/check/pkg01/M_SafePkg2.hs | 6 + .../tests/safeHaskell/check/pkg01/M_SafePkg3.hs | 8 + .../tests/safeHaskell/check/pkg01/M_SafePkg4.hs | 11 + .../tests/safeHaskell/check/pkg01/M_SafePkg5.hs | 14 + .../tests/safeHaskell/check/pkg01/M_SafePkg6.hs | 8 + .../tests/safeHaskell/check/pkg01/M_SafePkg7.hs | 8 + .../tests/safeHaskell/check/pkg01/M_SafePkg8.hs | 8 + testsuite/tests/safeHaskell/check/pkg01/Makefile | 76 + testsuite/tests/safeHaskell/check/pkg01/Setup.hs | 4 + testsuite/tests/safeHaskell/check/pkg01/all.T | 113 + testsuite/tests/safeHaskell/check/pkg01/p.cabal | 19 + .../tests/safeHaskell/check/pkg01/safePkg01.stdout | 49 + testsuite/tests/safeHaskell/flags/Flags01.hs | 11 + testsuite/tests/safeHaskell/flags/Flags01_A.cpp | 3 + testsuite/tests/safeHaskell/flags/Flags02.hs | 8 + testsuite/tests/safeHaskell/flags/Makefile | 3 + testsuite/tests/safeHaskell/flags/SafeFlags01.hs | 8 + testsuite/tests/safeHaskell/flags/SafeFlags02.hs | 8 + testsuite/tests/safeHaskell/flags/SafeFlags03.hs | 8 + .../tests/safeHaskell/flags/SafeFlags03.stderr | 2 + testsuite/tests/safeHaskell/flags/SafeFlags04.hs | 8 + .../tests/safeHaskell/flags/SafeFlags04.stderr | 2 + testsuite/tests/safeHaskell/flags/SafeFlags05.hs | 8 + .../tests/safeHaskell/flags/SafeFlags05.stderr | 2 + testsuite/tests/safeHaskell/flags/SafeFlags06.hs | 8 + .../tests/safeHaskell/flags/SafeFlags06.stderr | 2 + testsuite/tests/safeHaskell/flags/SafeFlags07.hs | 8 + .../tests/safeHaskell/flags/SafeFlags07.stderr | 2 + testsuite/tests/safeHaskell/flags/SafeFlags08.hs | 8 + .../tests/safeHaskell/flags/SafeFlags08.stderr | 2 + testsuite/tests/safeHaskell/flags/SafeFlags09.hs | 8 + .../tests/safeHaskell/flags/SafeFlags09.stderr | 2 + testsuite/tests/safeHaskell/flags/SafeFlags10.hs | 8 + .../tests/safeHaskell/flags/SafeFlags10.stderr | 2 + testsuite/tests/safeHaskell/flags/SafeFlags11.hs | 9 + testsuite/tests/safeHaskell/flags/SafeFlags12.hs | 7 + testsuite/tests/safeHaskell/flags/SafeFlags13.hs | 8 + .../tests/safeHaskell/flags/SafeFlags13.stderr | 2 + testsuite/tests/safeHaskell/flags/SafeFlags14.hs | 8 + .../tests/safeHaskell/flags/SafeFlags14.stderr | 2 + testsuite/tests/safeHaskell/flags/SafeFlags15.hs | 8 + testsuite/tests/safeHaskell/flags/SafeFlags16.hs | 8 + testsuite/tests/safeHaskell/flags/SafeFlags17.hs | 8 + .../tests/safeHaskell/flags/SafeFlags17.stderr | 4 + testsuite/tests/safeHaskell/flags/SafeFlags18.hs | 7 + .../tests/safeHaskell/flags/SafeFlags18.stderr | 6 + testsuite/tests/safeHaskell/flags/SafeFlags19.hs | 9 + .../tests/safeHaskell/flags/SafeFlags19.stderr | 3 + testsuite/tests/safeHaskell/flags/SafeFlags20.hs | 8 + testsuite/tests/safeHaskell/flags/SafeFlags21.hs | 9 + testsuite/tests/safeHaskell/flags/SafeFlags22.hs | 11 + .../tests/safeHaskell/flags/SafeFlags22.stderr | 7 + testsuite/tests/safeHaskell/flags/SafeFlags23.hs | 11 + .../tests/safeHaskell/flags/SafeFlags23.stderr | 10 + testsuite/tests/safeHaskell/flags/SafeFlags24.hs | 11 + testsuite/tests/safeHaskell/flags/SafeFlags25.hs | 9 + .../tests/safeHaskell/flags/SafeFlags25.stderr | 3 + testsuite/tests/safeHaskell/flags/SafeFlags26.hs | 9 + .../tests/safeHaskell/flags/SafeFlags26.stderr | 6 + testsuite/tests/safeHaskell/flags/SafeFlags27.hs | 9 + testsuite/tests/safeHaskell/flags/SafeFlags28.hs | 9 + .../tests/safeHaskell/flags/SafeFlags28.stderr | 12 + testsuite/tests/safeHaskell/flags/SafeFlags29.hs | 10 + .../tests/safeHaskell/flags/SafeFlags29.stderr | 12 + testsuite/tests/safeHaskell/flags/all.T | 64 + testsuite/tests/safeHaskell/ghci/A.hs | 10 + testsuite/tests/safeHaskell/ghci/B.hs | 8 + testsuite/tests/safeHaskell/ghci/C.hs | 13 + testsuite/tests/safeHaskell/ghci/D.hs | 8 + testsuite/tests/safeHaskell/ghci/E.hs | 7 + testsuite/tests/safeHaskell/ghci/Makefile | 4 + testsuite/tests/safeHaskell/ghci/P13_A.hs | 9 + testsuite/tests/safeHaskell/ghci/all.T | 29 + testsuite/tests/safeHaskell/ghci/p1.script | 8 + testsuite/tests/safeHaskell/ghci/p1.stderr | 6 + testsuite/tests/safeHaskell/ghci/p10.script | 10 + testsuite/tests/safeHaskell/ghci/p10.stderr | 2 + testsuite/tests/safeHaskell/ghci/p10.stdout | 1 + testsuite/tests/safeHaskell/ghci/p11.script | 6 + testsuite/tests/safeHaskell/ghci/p11.stderr | 4 + testsuite/tests/safeHaskell/ghci/p12.script | 10 + testsuite/tests/safeHaskell/ghci/p12.stderr | 7 + testsuite/tests/safeHaskell/ghci/p13.script | 14 + testsuite/tests/safeHaskell/ghci/p13.stderr | 13 + testsuite/tests/safeHaskell/ghci/p14.script | 10 + testsuite/tests/safeHaskell/ghci/p14.stderr | 2 + testsuite/tests/safeHaskell/ghci/p15.script | 23 + testsuite/tests/safeHaskell/ghci/p15.stderr | 18 + testsuite/tests/safeHaskell/ghci/p15.stdout | 2 + testsuite/tests/safeHaskell/ghci/p16.script | 22 + testsuite/tests/safeHaskell/ghci/p16.stderr | 15 + testsuite/tests/safeHaskell/ghci/p16.stdout | 1 + testsuite/tests/safeHaskell/ghci/p17.script | 10 + testsuite/tests/safeHaskell/ghci/p17.stderr | 5 + testsuite/tests/safeHaskell/ghci/p18.script | 10 + testsuite/tests/safeHaskell/ghci/p18.stdout | 7 + testsuite/tests/safeHaskell/ghci/p2.script | 12 + testsuite/tests/safeHaskell/ghci/p3.script | 12 + testsuite/tests/safeHaskell/ghci/p3.stderr | 10 + testsuite/tests/safeHaskell/ghci/p4.script | 8 + testsuite/tests/safeHaskell/ghci/p4.stderr | 6 + testsuite/tests/safeHaskell/ghci/p5.script | 13 + testsuite/tests/safeHaskell/ghci/p5.stderr | 7 + testsuite/tests/safeHaskell/ghci/p6.script | 13 + testsuite/tests/safeHaskell/ghci/p6.stderr | 10 + testsuite/tests/safeHaskell/ghci/p6.stdout | 1 + testsuite/tests/safeHaskell/ghci/p7.script | 6 + testsuite/tests/safeHaskell/ghci/p7.stderr | 2 + testsuite/tests/safeHaskell/ghci/p8.script | 6 + testsuite/tests/safeHaskell/ghci/p8.stderr | 2 + testsuite/tests/safeHaskell/ghci/p9.script | 10 + testsuite/tests/safeHaskell/ghci/p9.stderr | 2 + testsuite/tests/safeHaskell/ghci/p9.stdout | 1 + testsuite/tests/safeHaskell/safeInfered/Makefile | 3 + testsuite/tests/safeHaskell/safeInfered/Mixed01.hs | 9 + .../tests/safeHaskell/safeInfered/Mixed01.stderr | 4 + testsuite/tests/safeHaskell/safeInfered/Mixed02.hs | 10 + .../tests/safeHaskell/safeInfered/Mixed02.stderr | 3 + testsuite/tests/safeHaskell/safeInfered/Mixed03.hs | 11 + .../tests/safeHaskell/safeInfered/Mixed03.stderr | 3 + .../tests/safeHaskell/safeInfered/SafeInfered01.hs | 8 + .../safeHaskell/safeInfered/SafeInfered01.stderr | 2 + .../safeHaskell/safeInfered/SafeInfered01_A.hs | 6 + .../tests/safeHaskell/safeInfered/SafeInfered02.hs | 8 + .../safeHaskell/safeInfered/SafeInfered02.stderr | 2 + .../safeHaskell/safeInfered/SafeInfered02_A.hs | 11 + .../tests/safeHaskell/safeInfered/SafeInfered03.hs | 8 + .../safeHaskell/safeInfered/SafeInfered03.stderr | 2 + .../safeHaskell/safeInfered/SafeInfered03_A.hs | 8 + .../tests/safeHaskell/safeInfered/SafeInfered04.hs | 8 + .../safeHaskell/safeInfered/SafeInfered04.stderr | 2 + .../safeHaskell/safeInfered/SafeInfered04_A.hs | 8 + .../safeHaskell/safeInfered/UnsafeInfered01.hs | 8 + .../safeHaskell/safeInfered/UnsafeInfered01.stderr | 6 + .../safeHaskell/safeInfered/UnsafeInfered01_A.hs | 8 + .../safeHaskell/safeInfered/UnsafeInfered02.hs | 8 + .../safeHaskell/safeInfered/UnsafeInfered02.stderr | 6 + .../safeHaskell/safeInfered/UnsafeInfered02_A.hs | 7 + .../safeHaskell/safeInfered/UnsafeInfered03.hs | 8 + .../safeHaskell/safeInfered/UnsafeInfered03.stderr | 6 + .../safeHaskell/safeInfered/UnsafeInfered03_A.hs | 7 + .../safeHaskell/safeInfered/UnsafeInfered05.hs | 8 + .../safeHaskell/safeInfered/UnsafeInfered05.stderr | 6 + .../safeHaskell/safeInfered/UnsafeInfered05_A.hs | 11 + .../safeHaskell/safeInfered/UnsafeInfered06.hs | 5 + .../safeHaskell/safeInfered/UnsafeInfered06.stderr | 6 + .../safeHaskell/safeInfered/UnsafeInfered06_A.hs | 8 + .../safeHaskell/safeInfered/UnsafeInfered07.hs | 5 + .../safeHaskell/safeInfered/UnsafeInfered07.stderr | 24 + .../safeHaskell/safeInfered/UnsafeInfered07_A.hs | 10 + .../safeHaskell/safeInfered/UnsafeInfered08.hs | 8 + .../safeHaskell/safeInfered/UnsafeInfered08.stderr | 6 + .../safeHaskell/safeInfered/UnsafeInfered08_A.hs | 9 + .../safeHaskell/safeInfered/UnsafeInfered09.hs | 8 + .../safeHaskell/safeInfered/UnsafeInfered09.stderr | 7 + .../safeHaskell/safeInfered/UnsafeInfered09_A.hs | 8 + .../safeHaskell/safeInfered/UnsafeInfered09_B.hs | 6 + .../safeHaskell/safeInfered/UnsafeInfered10.hs | 9 + .../safeHaskell/safeInfered/UnsafeInfered10.stderr | 6 + .../safeHaskell/safeInfered/UnsafeInfered10_A.hs | 8 + .../safeHaskell/safeInfered/UnsafeInfered11.hs | 9 + .../safeHaskell/safeInfered/UnsafeInfered11.stderr | 13 + .../safeHaskell/safeInfered/UnsafeInfered11_A.hs | 39 + .../safeHaskell/safeInfered/UnsafeInfered12.hs | 7 + .../safeHaskell/safeInfered/UnsafeInfered12.stderr | 9 + testsuite/tests/safeHaskell/safeInfered/all.T | 66 + testsuite/tests/safeHaskell/safeLanguage/Makefile | 82 + .../tests/safeHaskell/safeLanguage/SafeLang01.hs | 8 + .../safeHaskell/safeLanguage/SafeLang01.stderr | 3 + .../tests/safeHaskell/safeLanguage/SafeLang02.hs | 8 + .../safeHaskell/safeLanguage/SafeLang02.stderr | 3 + .../tests/safeHaskell/safeLanguage/SafeLang03.hs | 10 + .../safeHaskell/safeLanguage/SafeLang03.stderr | 4 + .../tests/safeHaskell/safeLanguage/SafeLang04.hs | 32 + .../safeHaskell/safeLanguage/SafeLang04.stdout | 4 + .../tests/safeHaskell/safeLanguage/SafeLang05.hs | 34 + .../safeHaskell/safeLanguage/SafeLang05.stdout | 4 + .../tests/safeHaskell/safeLanguage/SafeLang07.hs | 41 + .../safeHaskell/safeLanguage/SafeLang07.stderr | 7 + .../tests/safeHaskell/safeLanguage/SafeLang07_A.hs | 24 + .../tests/safeHaskell/safeLanguage/SafeLang08.hs | 21 + .../safeHaskell/safeLanguage/SafeLang08.stderr | 7 + .../tests/safeHaskell/safeLanguage/SafeLang08_A.c | 6 + .../tests/safeHaskell/safeLanguage/SafeLang09.hs | 10 + .../safeHaskell/safeLanguage/SafeLang09.stderr | 1 + .../tests/safeHaskell/safeLanguage/SafeLang09_A.hs | 14 + .../tests/safeHaskell/safeLanguage/SafeLang09_B.hs | 18 + .../tests/safeHaskell/safeLanguage/SafeLang10.hs | 11 + .../safeHaskell/safeLanguage/SafeLang10.stderr | 20 + .../safeHaskell/safeLanguage/SafeLang10.stdout | 3 + .../tests/safeHaskell/safeLanguage/SafeLang10_A.hs | 16 + .../tests/safeHaskell/safeLanguage/SafeLang10_B.hs | 20 + .../tests/safeHaskell/safeLanguage/SafeLang11.hs | 12 + .../safeHaskell/safeLanguage/SafeLang11.stdout | 1 + .../tests/safeHaskell/safeLanguage/SafeLang11_A.hs | 9 + .../tests/safeHaskell/safeLanguage/SafeLang11_B.hs | 16 + .../tests/safeHaskell/safeLanguage/SafeLang12.hs | 14 + .../safeHaskell/safeLanguage/SafeLang12.stderr | 12 + .../tests/safeHaskell/safeLanguage/SafeLang12_A.hs | 9 + .../tests/safeHaskell/safeLanguage/SafeLang12_B.hs | 17 + .../tests/safeHaskell/safeLanguage/SafeLang13.hs | 41 + .../safeHaskell/safeLanguage/SafeLang13.stdout | 5 + .../tests/safeHaskell/safeLanguage/SafeLang13_A.hs | 19 + .../tests/safeHaskell/safeLanguage/SafeLang14.hs | 41 + .../safeHaskell/safeLanguage/SafeLang14.stderr | 8 + .../tests/safeHaskell/safeLanguage/SafeLang14_A.hs | 19 + .../tests/safeHaskell/safeLanguage/SafeLang15.hs | 33 + .../safeHaskell/safeLanguage/SafeLang15.stderr | 2 + .../safeHaskell/safeLanguage/SafeLang15.stdout | 3 + .../tests/safeHaskell/safeLanguage/SafeLang15_A.hs | 19 + .../tests/safeHaskell/safeLanguage/SafeLang16.hs | 11 + .../safeHaskell/safeLanguage/SafeLang16.stderr | 3 + .../tests/safeHaskell/safeLanguage/SafeRecomp01.hs | 5 + .../tests/safeHaskell/safeLanguage/SafeRecomp02.hs | 10 + .../safeHaskell/safeLanguage/SafeRecomp02_A.hs | 5 + testsuite/tests/safeHaskell/safeLanguage/all.T | 62 + .../tests/safeHaskell/unsafeLibs/BadImport01.hs | 12 + .../safeHaskell/unsafeLibs/BadImport01.stderr | 4 + .../tests/safeHaskell/unsafeLibs/BadImport02.hs | 27 + .../safeHaskell/unsafeLibs/BadImport02.stdout | 3 + .../tests/safeHaskell/unsafeLibs/BadImport02_A.hs | 16 + .../tests/safeHaskell/unsafeLibs/BadImport03.hs | 29 + .../safeHaskell/unsafeLibs/BadImport03.stderr | 5 + .../tests/safeHaskell/unsafeLibs/BadImport03_A.hs | 16 + .../tests/safeHaskell/unsafeLibs/BadImport05.hs | 12 + .../safeHaskell/unsafeLibs/BadImport05.stderr | 4 + .../tests/safeHaskell/unsafeLibs/BadImport06.hs | 12 + .../safeHaskell/unsafeLibs/BadImport06.stderr | 4 + .../tests/safeHaskell/unsafeLibs/BadImport07.hs | 12 + .../safeHaskell/unsafeLibs/BadImport07.stderr | 4 + .../tests/safeHaskell/unsafeLibs/BadImport08.hs | 12 + .../safeHaskell/unsafeLibs/BadImport08.stderr | 4 + testsuite/tests/safeHaskell/unsafeLibs/Dep05.hs | 14 + .../tests/safeHaskell/unsafeLibs/Dep05.stderr | 3 + testsuite/tests/safeHaskell/unsafeLibs/Dep06.hs | 7 + .../tests/safeHaskell/unsafeLibs/Dep06.stderr | 3 + testsuite/tests/safeHaskell/unsafeLibs/Dep07.hs | 7 + .../tests/safeHaskell/unsafeLibs/Dep07.stderr | 4 + testsuite/tests/safeHaskell/unsafeLibs/Dep08.hs | 10 + .../tests/safeHaskell/unsafeLibs/Dep08.stderr | 4 + testsuite/tests/safeHaskell/unsafeLibs/Dep09.hs | 7 + .../tests/safeHaskell/unsafeLibs/Dep09.stderr | 3 + testsuite/tests/safeHaskell/unsafeLibs/Dep10.hs | 9 + .../tests/safeHaskell/unsafeLibs/Dep10.stderr | 3 + .../tests/safeHaskell/unsafeLibs/GoodImport01.hs | 14 + .../tests/safeHaskell/unsafeLibs/GoodImport02.hs | 15 + .../tests/safeHaskell/unsafeLibs/GoodImport03.hs | 114 + testsuite/tests/safeHaskell/unsafeLibs/Makefile | 3 + testsuite/tests/safeHaskell/unsafeLibs/all.T | 39 + testsuite/tests/simplCore/Makefile | 3 + testsuite/tests/simplCore/prog001/Makefile | 3 + testsuite/tests/simplCore/prog001/Simpl006Help.hs | 3 + testsuite/tests/simplCore/prog001/simpl006.hs | 19 + testsuite/tests/simplCore/prog001/test.T | 5 + testsuite/tests/simplCore/prog002/Makefile | 3 + testsuite/tests/simplCore/prog002/Simpl009Help.hs | 51 + testsuite/tests/simplCore/prog002/simpl009.hs | 23 + testsuite/tests/simplCore/prog002/test.T | 5 + .../tests/simplCore/should_compile/EvalTest.hs | 58 + .../tests/simplCore/should_compile/EvalTest.stdout | 1 + testsuite/tests/simplCore/should_compile/Makefile | 117 + .../tests/simplCore/should_compile/Simpl020_A.hs | 27 + .../tests/simplCore/should_compile/Simpl021A.hs | 8 + .../tests/simplCore/should_compile/Simpl021B.hs | 9 + testsuite/tests/simplCore/should_compile/T1647.hs | 5 + testsuite/tests/simplCore/should_compile/T2520.hs | 28 + testsuite/tests/simplCore/should_compile/T3016.hs | 588 + testsuite/tests/simplCore/should_compile/T3055.hs | 9 + .../tests/simplCore/should_compile/T3055.stdout | 1 + testsuite/tests/simplCore/should_compile/T3118.hs | 40 + testsuite/tests/simplCore/should_compile/T3234.hs | 8 + .../tests/simplCore/should_compile/T3234.stderr | 66 + testsuite/tests/simplCore/should_compile/T3717.hs | 10 + .../tests/simplCore/should_compile/T3717.stderr | 35 + .../simplCore/should_compile/T3717.stderr-ghc-7.0 | 47 + testsuite/tests/simplCore/should_compile/T3772.hs | 21 + .../tests/simplCore/should_compile/T3772.stdout | 29 + .../simplCore/should_compile/T3772.stdout-ghc-7.0 | 25 + .../tests/simplCore/should_compile/T3772_A.hs | 48 + testsuite/tests/simplCore/should_compile/T3831.hs | 120 + testsuite/tests/simplCore/should_compile/T4138.hs | 20 + .../tests/simplCore/should_compile/T4138.stdout | 1 + .../tests/simplCore/should_compile/T4138_A.hs | 11 + testsuite/tests/simplCore/should_compile/T4201.hs | 15 + .../tests/simplCore/should_compile/T4201.stdout | 3 + testsuite/tests/simplCore/should_compile/T4203.hs | 46 + testsuite/tests/simplCore/should_compile/T4306.hs | 12 + .../tests/simplCore/should_compile/T4306.stdout | 1 + testsuite/tests/simplCore/should_compile/T4345.hs | 16 + testsuite/tests/simplCore/should_compile/T4398.hs | 13 + .../tests/simplCore/should_compile/T4398.stderr | 3 + testsuite/tests/simplCore/should_compile/T4903.hs | 10 + testsuite/tests/simplCore/should_compile/T4903a.hs | 56 + testsuite/tests/simplCore/should_compile/T4908.hs | 10 + .../tests/simplCore/should_compile/T4908.stderr | 75 + .../simplCore/should_compile/T4908.stderr-ghc-7.0 | 77 + testsuite/tests/simplCore/should_compile/T4918.hs | 6 + .../tests/simplCore/should_compile/T4918.stdout | 2 + testsuite/tests/simplCore/should_compile/T4918a.hs | 8 + testsuite/tests/simplCore/should_compile/T4930.hs | 5 + .../tests/simplCore/should_compile/T4930.stderr | 37 + testsuite/tests/simplCore/should_compile/T4945.hs | 30 + testsuite/tests/simplCore/should_compile/T4957.hs | 19 + testsuite/tests/simplCore/should_compile/T5168.hs | 32 + testsuite/tests/simplCore/should_compile/T5303.hs | 44 + testsuite/tests/simplCore/should_compile/T5327.hs | 12 + .../tests/simplCore/should_compile/T5327.stdout | 1 + testsuite/tests/simplCore/should_compile/T5329.hs | 129 + testsuite/tests/simplCore/should_compile/T5342.hs | 18 + testsuite/tests/simplCore/should_compile/T5359a.hs | 88 + testsuite/tests/simplCore/should_compile/T5359b.hs | 62 + .../tests/simplCore/should_compile/T5359b.stderr | 3 + testsuite/tests/simplCore/should_compile/T5366.hs | 8 + .../tests/simplCore/should_compile/T5366.stdout | 2 + testsuite/tests/simplCore/should_compile/T5458.hs | 8 + testsuite/tests/simplCore/should_compile/T5550.hs | 11 + .../tests/simplCore/should_compile/T5550.stderr | 3 + testsuite/tests/simplCore/should_compile/T5623.hs | 10 + .../tests/simplCore/should_compile/T5623.stdout | 1 + testsuite/tests/simplCore/should_compile/T5658b.hs | 18 + .../tests/simplCore/should_compile/T5658b.stdout | 1 + testsuite/tests/simplCore/should_compile/T5776.hs | 28 + .../tests/simplCore/should_compile/T5776.stdout | 1 + testsuite/tests/simplCore/should_compile/T5996.hs | 12 + .../tests/simplCore/should_compile/T5996.stdout | 2 + .../tests/simplCore/should_compile/T6082-RULE.hs | 16 + .../simplCore/should_compile/T6082-RULE.stderr | 8 + testsuite/tests/simplCore/should_compile/T7088.hs | 16 + testsuite/tests/simplCore/should_compile/T7162.hs | 9 + testsuite/tests/simplCore/should_compile/T7165.hs | 5 + testsuite/tests/simplCore/should_compile/T7165a.hs | 8 + testsuite/tests/simplCore/should_compile/T7287.hs | 8 + testsuite/tests/simplCore/should_compile/T7360.hs | 19 + .../tests/simplCore/should_compile/T7360.stderr | 69 + testsuite/tests/simplCore/should_compile/T7702.hs | 7 + .../tests/simplCore/should_compile/T7702.stderr | 1 + .../simplCore/should_compile/T7702plugin/Makefile | 20 + .../simplCore/should_compile/T7702plugin/Setup.hs | 3 + .../should_compile/T7702plugin/T7702Plugin.hs | 51 + .../should_compile/T7702plugin/T7702plugin.cabal | 13 + testsuite/tests/simplCore/should_compile/T7785.hs | 28 + .../tests/simplCore/should_compile/T7785.stderr | 9 + testsuite/tests/simplCore/should_compile/T7796.hs | 64 + .../tests/simplCore/should_compile/T7796.stdout | 1 + testsuite/tests/simplCore/should_compile/T7865.hs | 29 + .../tests/simplCore/should_compile/T7865.stdout | 4 + testsuite/tests/simplCore/should_compile/T7995.hs | 6 + .../tests/simplCore/should_compile/T7995.stdout | 1 + testsuite/tests/simplCore/should_compile/T8196.hs | 8 + testsuite/tests/simplCore/should_compile/T8221.hs | 6 + testsuite/tests/simplCore/should_compile/T8221a.hs | 8 + testsuite/tests/simplCore/should_compile/T8221b.hs | 3 + testsuite/tests/simplCore/should_compile/T8329.hs | 4 + .../tests/simplCore/should_compile/T8329_Com.hs | 6 + .../tests/simplCore/should_compile/T8329_Meta.hs | 5 + .../tests/simplCore/should_compile/T8329_Parse.hs | 3 + testsuite/tests/simplCore/should_compile/T8537.hs | 20 + .../tests/simplCore/should_compile/T8537.stderr | 3 + testsuite/tests/simplCore/should_compile/all.T | 200 + .../tests/simplCore/should_compile/dfun-loop.hs | 41 + testsuite/tests/simplCore/should_compile/rule1.hs | 19 + testsuite/tests/simplCore/should_compile/rule2.hs | 18 + .../tests/simplCore/should_compile/rule2.stderr | 30 + .../tests/simplCore/should_compile/simpl-T1370.hs | 7 + .../tests/simplCore/should_compile/simpl001.hs | 13 + .../tests/simplCore/should_compile/simpl002.hs | 10 + .../tests/simplCore/should_compile/simpl003.hs | 42 + .../tests/simplCore/should_compile/simpl004.hs | 18 + .../tests/simplCore/should_compile/simpl005.hs | 25 + .../tests/simplCore/should_compile/simpl007.hs | 235 + .../tests/simplCore/should_compile/simpl009.hs | 12 + .../tests/simplCore/should_compile/simpl010.hs | 19 + .../tests/simplCore/should_compile/simpl011.hs | 57 + .../tests/simplCore/should_compile/simpl012.hs | 23 + .../tests/simplCore/should_compile/simpl013.hs | 19 + .../tests/simplCore/should_compile/simpl014.hs | 30 + .../tests/simplCore/should_compile/simpl015.hs | 1683 +++ .../tests/simplCore/should_compile/simpl016.hs | 12 + .../tests/simplCore/should_compile/simpl016.stderr | 4 + .../tests/simplCore/should_compile/simpl017.hs | 64 + .../tests/simplCore/should_compile/simpl017.stderr | 44 + .../tests/simplCore/should_compile/simpl018.hs | 12 + .../tests/simplCore/should_compile/simpl019.hs | 14 + .../tests/simplCore/should_compile/simpl020.hs | 9 + .../tests/simplCore/should_compile/simpl020.stderr | 5 + .../tests/simplCore/should_compile/spec-inline.hs | 29 + .../simplCore/should_compile/spec-inline.stderr | 157 + .../should_compile/spec-inline.stderr-ghc-7.0 | 154 + .../tests/simplCore/should_compile/spec001.hs | 425 + .../tests/simplCore/should_compile/spec002.hs | 17 + .../tests/simplCore/should_compile/spec003.hs | 11 + .../tests/simplCore/should_compile/strict-float.hs | 13 + testsuite/tests/simplCore/should_run/Makefile | 3 + testsuite/tests/simplCore/should_run/SeqRule.hs | 16 + .../tests/simplCore/should_run/SeqRule.stdout | 1 + testsuite/tests/simplCore/should_run/T2486.hs | 37 + testsuite/tests/simplCore/should_run/T2486.stderr | 24 + testsuite/tests/simplCore/should_run/T2756.hs | 15 + testsuite/tests/simplCore/should_run/T3403.hs | 32 + testsuite/tests/simplCore/should_run/T3403.stdout | 2 + testsuite/tests/simplCore/should_run/T3437.hs | 19 + testsuite/tests/simplCore/should_run/T3437.stdout | 1 + testsuite/tests/simplCore/should_run/T3591.hs | 206 + testsuite/tests/simplCore/should_run/T3591.stderr | 456 + testsuite/tests/simplCore/should_run/T3591.stdout | 1 + testsuite/tests/simplCore/should_run/T3959.hs | 67 + testsuite/tests/simplCore/should_run/T3959.stdout | 1 + testsuite/tests/simplCore/should_run/T3972.hs | 25 + testsuite/tests/simplCore/should_run/T3972A.hs | 86 + testsuite/tests/simplCore/should_run/T3983.hs | 5 + testsuite/tests/simplCore/should_run/T3983.stdout | 1 + testsuite/tests/simplCore/should_run/T3983_Bar.hs | 15 + testsuite/tests/simplCore/should_run/T3983_Foo.hs | 8 + testsuite/tests/simplCore/should_run/T457.hs | 5 + testsuite/tests/simplCore/should_run/T457.stderr | 1 + testsuite/tests/simplCore/should_run/T4814.hs | 39 + testsuite/tests/simplCore/should_run/T4814.stdout | 1 + testsuite/tests/simplCore/should_run/T5315.hs | 89 + testsuite/tests/simplCore/should_run/T5315.stdout | 1 + testsuite/tests/simplCore/should_run/T5441.hs | 5 + testsuite/tests/simplCore/should_run/T5441.stdout | 1 + testsuite/tests/simplCore/should_run/T5441a.hs | 39 + testsuite/tests/simplCore/should_run/T5453.hs | 21 + testsuite/tests/simplCore/should_run/T5453.stdout | 1 + testsuite/tests/simplCore/should_run/T5587.hs | 30 + testsuite/tests/simplCore/should_run/T5587.stderr | 1 + testsuite/tests/simplCore/should_run/T5603.hs | 15 + testsuite/tests/simplCore/should_run/T5625.hs | 4 + testsuite/tests/simplCore/should_run/T5625.stderr | 1 + testsuite/tests/simplCore/should_run/T5915.hs | 5 + testsuite/tests/simplCore/should_run/T5915.stdout | 1 + testsuite/tests/simplCore/should_run/T5920.hs | 10 + testsuite/tests/simplCore/should_run/T5920.stdout | 1 + testsuite/tests/simplCore/should_run/T5997.hs | 29 + testsuite/tests/simplCore/should_run/T5997.stdout | 1 + testsuite/tests/simplCore/should_run/T7101.hs | 14 + testsuite/tests/simplCore/should_run/T7101.stdout | 1 + testsuite/tests/simplCore/should_run/T7924.hs | 20 + testsuite/tests/simplCore/should_run/T7924.stderr | 1 + testsuite/tests/simplCore/should_run/all.T | 63 + .../tests/simplCore/should_run/simplrun001.hs | 14 + .../tests/simplCore/should_run/simplrun001.stdout | 1 + .../tests/simplCore/should_run/simplrun002.hs | 23 + .../tests/simplCore/should_run/simplrun002.stderr | 1 + .../tests/simplCore/should_run/simplrun002.stdout | 1 + .../tests/simplCore/should_run/simplrun003.hs | 23 + .../tests/simplCore/should_run/simplrun003.stdout | 1 + .../tests/simplCore/should_run/simplrun004.hs | 34 + .../tests/simplCore/should_run/simplrun004.stdout | 1 + .../tests/simplCore/should_run/simplrun005.hs | 47 + .../tests/simplCore/should_run/simplrun005.stdout | 1 + .../tests/simplCore/should_run/simplrun007.hs | 27 + .../tests/simplCore/should_run/simplrun007.stdout | 5 + .../simplCore/should_run/simplrun007.stdout-ws-64 | 5 + .../tests/simplCore/should_run/simplrun008.hs | 18 + .../tests/simplCore/should_run/simplrun008.stdout | 2 + .../tests/simplCore/should_run/simplrun009.hs | 149 + .../tests/simplCore/should_run/simplrun009.stdout | 1 + .../tests/simplCore/should_run/simplrun010.hs | 326 + .../tests/simplCore/should_run/simplrun010.stderr | 3 + testsuite/tests/stranal/Makefile | 3 + testsuite/tests/stranal/should_compile/Makefile | 3 + testsuite/tests/stranal/should_compile/T1988.hs | 12 + testsuite/tests/stranal/should_compile/T8037.hs | 17 + testsuite/tests/stranal/should_compile/T8467.hs | 11 + testsuite/tests/stranal/should_compile/all.T | 20 + testsuite/tests/stranal/should_compile/default.hs | 16 + testsuite/tests/stranal/should_compile/fact.hs | 3 + testsuite/tests/stranal/should_compile/fun.hs | 6 + testsuite/tests/stranal/should_compile/goo.hs | 10 + testsuite/tests/stranal/should_compile/ins.hs | 27 + testsuite/tests/stranal/should_compile/map.hs | 32 + testsuite/tests/stranal/should_compile/newtype.hs | 14 + testsuite/tests/stranal/should_compile/sim.hs | 103 + testsuite/tests/stranal/should_compile/str001.hs | 10 + .../tests/stranal/should_compile/str001.stderr | 4 + testsuite/tests/stranal/should_compile/str002.hs | 12 + testsuite/tests/stranal/should_compile/syn.hs | 15 + testsuite/tests/stranal/should_compile/test.hs | 6 + testsuite/tests/stranal/should_compile/tst.hs | 3 + testsuite/tests/stranal/should_compile/unu.hs | 76 + testsuite/tests/stranal/should_run/Makefile | 3 + testsuite/tests/stranal/should_run/T2756b.hs | 15 + testsuite/tests/stranal/should_run/T7649.hs | 32 + testsuite/tests/stranal/should_run/T7649.stdout | 6 + testsuite/tests/stranal/should_run/T8425/Arr.hs | 67 + testsuite/tests/stranal/should_run/T8425/Base.hs | 43 + .../tests/stranal/should_run/T8425/BuggyOpt.hs | 13 + testsuite/tests/stranal/should_run/T8425/Good.hs | 4 + testsuite/tests/stranal/should_run/T8425/M.hs | 9 + testsuite/tests/stranal/should_run/T8425/Main.hs | 14 + testsuite/tests/stranal/should_run/T8425/Makefile | 3 + .../tests/stranal/should_run/T8425/T8425.stdout | 1 + testsuite/tests/stranal/should_run/T8425/all.T | 5 + testsuite/tests/stranal/should_run/all.T | 9 + testsuite/tests/stranal/should_run/strun001.hs | 15 + testsuite/tests/stranal/should_run/strun001.stdout | 1 + testsuite/tests/stranal/should_run/strun002.hs | 12 + testsuite/tests/stranal/should_run/strun002.stderr | 1 + testsuite/tests/stranal/should_run/strun003.hs | 23 + testsuite/tests/stranal/should_run/strun003.stdout | 1 + testsuite/tests/stranal/should_run/strun004.hs | 10 + testsuite/tests/stranal/should_run/strun004.stdout | 1 + testsuite/tests/stranal/sigs/HyperStrUse.hs | 9 + testsuite/tests/stranal/sigs/Makefile | 3 + testsuite/tests/stranal/sigs/StrAnalAnnotation.hs | 59 + testsuite/tests/stranal/sigs/StrAnalExample.hs | 10 + testsuite/tests/stranal/sigs/T8569.hs | 15 + testsuite/tests/stranal/sigs/all.T | 21 + testsuite/tests/th/ClosedFam1TH.hs | 13 + testsuite/tests/th/ClosedFam1TH.stderr | 6 + testsuite/tests/th/ClosedFam2TH.hs | 22 + testsuite/tests/th/Makefile | 39 + testsuite/tests/th/T1541.hs | 11 + testsuite/tests/th/T1835.hs | 39 + testsuite/tests/th/T1835.stdout | 14 + testsuite/tests/th/T1849.script | 10 + testsuite/tests/th/T1849.stdout | 6 + testsuite/tests/th/T2014/A.hs | 1 + testsuite/tests/th/T2014/A.hs-boot | 1 + testsuite/tests/th/T2014/B.hs | 9 + testsuite/tests/th/T2014/C.hs | 8 + testsuite/tests/th/T2014/Makefile | 9 + testsuite/tests/th/T2014/all.T | 8 + testsuite/tests/th/T2222.hs | 42 + testsuite/tests/th/T2222.stderr | 5 + testsuite/tests/th/T2386.hs | 9 + testsuite/tests/th/T2386_Lib.hs | 7 + testsuite/tests/th/T2597a.hs | 8 + testsuite/tests/th/T2597a_Lib.hs | 12 + testsuite/tests/th/T2597b.hs | 9 + testsuite/tests/th/T2597b.stderr | 5 + testsuite/tests/th/T2597b_Lib.hs | 9 + testsuite/tests/th/T2632.hs | 16 + testsuite/tests/th/T2674.hs | 9 + testsuite/tests/th/T2674.stderr | 4 + testsuite/tests/th/T2685.hs | 6 + testsuite/tests/th/T2685a.hs | 9 + testsuite/tests/th/T2700.hs | 10 + testsuite/tests/th/T2700.stderr | 1 + testsuite/tests/th/T2700.stderr-ghc-7.0 | 1 + testsuite/tests/th/T2713.hs | 12 + testsuite/tests/th/T2713.stderr | 8 + testsuite/tests/th/T2817.hs | 11 + testsuite/tests/th/T2931.hs | 8 + testsuite/tests/th/T3100.hs | 20 + testsuite/tests/th/T3177.hs | 14 + testsuite/tests/th/T3177a.hs | 13 + testsuite/tests/th/T3177a.stderr | 8 + testsuite/tests/th/T3319.hs | 11 + testsuite/tests/th/T3319.stderr | 8 + testsuite/tests/th/T3395.hs | 9 + testsuite/tests/th/T3395.stderr | 11 + testsuite/tests/th/T3467.hs | 11 + testsuite/tests/th/T3572.hs | 10 + testsuite/tests/th/T3572.stdout | 1 + testsuite/tests/th/T3600.hs | 5 + testsuite/tests/th/T3600.stderr | 5 + testsuite/tests/th/T3600a.hs | 19 + testsuite/tests/th/T3845.hs | 21 + testsuite/tests/th/T3899.hs | 6 + testsuite/tests/th/T3899.stderr | 2 + testsuite/tests/th/T3899a.hs | 14 + testsuite/tests/th/T3920.hs | 17 + testsuite/tests/th/T3920.stdout | 2 + testsuite/tests/th/T4056.hs | 15 + testsuite/tests/th/T4124.hs | 6 + testsuite/tests/th/T4128.hs | 7 + testsuite/tests/th/T4135.hs | 16 + testsuite/tests/th/T4135.stderr | 2 + testsuite/tests/th/T4135a.hs | 15 + testsuite/tests/th/T4169.hs | 15 + testsuite/tests/th/T4170.hs | 13 + testsuite/tests/th/T4188.hs | 28 + testsuite/tests/th/T4188.stderr | 6 + testsuite/tests/th/T4233.hs | 9 + testsuite/tests/th/T4255.hs | 5 + testsuite/tests/th/T4255.stderr | 2 + testsuite/tests/th/T4364.hs | 7 + testsuite/tests/th/T4436.hs | 9 + testsuite/tests/th/T4436.stderr | 11 + testsuite/tests/th/T4949.hs | 8 + testsuite/tests/th/T5037.hs | 11 + testsuite/tests/th/T5037.stderr | 3 + testsuite/tests/th/T5126.hs | 12 + testsuite/tests/th/T5217.hs | 11 + testsuite/tests/th/T5217.stderr | 14 + testsuite/tests/th/T5290.hs | 8 + testsuite/tests/th/T5290.stderr | 6 + testsuite/tests/th/T5358.hs | 16 + testsuite/tests/th/T5358.stderr | 9 + testsuite/tests/th/T5362.hs | 23 + testsuite/tests/th/T5362.stderr | 4 + testsuite/tests/th/T5379.hs | 11 + testsuite/tests/th/T5379.stdout | 1 + testsuite/tests/th/T5404.hs | 12 + testsuite/tests/th/T5410.hs | 8 + testsuite/tests/th/T5410.stdout | 1 + testsuite/tests/th/T5434.hs | 12 + testsuite/tests/th/T5434a.hs | 18 + testsuite/tests/th/T5452.hs | 17 + testsuite/tests/th/T5508.hs | 9 + testsuite/tests/th/T5508.stderr | 7 + testsuite/tests/th/T5555.hs | 8 + testsuite/tests/th/T5555.stdout | 1 + testsuite/tests/th/T5555_Lib.hs | 10 + testsuite/tests/th/T5597.hs | 5 + testsuite/tests/th/T5597a.hs | 6 + testsuite/tests/th/T5665.hs | 9 + testsuite/tests/th/T5665a.hs | 6 + testsuite/tests/th/T5700.hs | 8 + testsuite/tests/th/T5700.stderr | 7 + testsuite/tests/th/T5700a.hs | 15 + testsuite/tests/th/T5721.hs | 7 + testsuite/tests/th/T5737.hs | 5 + testsuite/tests/th/T5795.hs | 10 + testsuite/tests/th/T5795.stderr | 6 + testsuite/tests/th/T5882.hs | 11 + testsuite/tests/th/T5883.hs | 12 + testsuite/tests/th/T5883.stderr | 12 + testsuite/tests/th/T5886.hs | 8 + testsuite/tests/th/T5886a.hs | 14 + testsuite/tests/th/T5968.hs | 6 + testsuite/tests/th/T5971.hs | 6 + testsuite/tests/th/T5971.stderr | 7 + testsuite/tests/th/T5976.hs | 3 + testsuite/tests/th/T5976.stderr | 5 + testsuite/tests/th/T5984.hs | 8 + testsuite/tests/th/T5984.stderr | 10 + testsuite/tests/th/T5984_Lib.hs | 13 + testsuite/tests/th/T6005.hs | 10 + testsuite/tests/th/T6005a.hs | 15 + testsuite/tests/th/T6062.hs | 3 + testsuite/tests/th/T6114.hs | 11 + testsuite/tests/th/T6114.stderr | 12 + testsuite/tests/th/T7064.hs | 9 + testsuite/tests/th/T7064.stdout | 26 + testsuite/tests/th/T7064a.hs | 29 + testsuite/tests/th/T7092.hs | 10 + testsuite/tests/th/T7092a.hs | 12 + testsuite/tests/th/T7276.hs | 6 + testsuite/tests/th/T7276.stderr | 8 + testsuite/tests/th/T7276a.script | 4 + testsuite/tests/th/T7276a.stdout | 19 + testsuite/tests/th/T7445.hs | 6 + testsuite/tests/th/T7445a.hs | 13 + testsuite/tests/th/T7477.hs | 12 + testsuite/tests/th/T7477.stderr | 3 + testsuite/tests/th/T7532.hs | 11 + testsuite/tests/th/T7532.stderr | 16 + testsuite/tests/th/T7532a.hs | 15 + testsuite/tests/th/T7667.hs | 8 + testsuite/tests/th/T7667a.hs | 8 + testsuite/tests/th/T7667a.stderr | 5 + testsuite/tests/th/T7681.hs | 12 + testsuite/tests/th/T7910.hs | 18 + testsuite/tests/th/T7910.stdout | 1 + testsuite/tests/th/T8028.hs | 7 + testsuite/tests/th/T8028.stderr | 4 + testsuite/tests/th/T8028a.hs | 6 + testsuite/tests/th/T8186.hs | 11 + testsuite/tests/th/T8186.stdout | 3 + testsuite/tests/th/T8333.hs | 5 + testsuite/tests/th/T8412.hs | 5 + testsuite/tests/th/T8412.stderr | 4 + testsuite/tests/th/T8455.hs | 5 + testsuite/tests/th/T8499.hs | 12 + testsuite/tests/th/T8507.hs | 8 + testsuite/tests/th/T8540.hs | 7 + testsuite/tests/th/T8540a.hs | 10 + testsuite/tests/th/T8577.hs | 10 + testsuite/tests/th/T8577.stderr | 7 + testsuite/tests/th/T8577a.hs | 11 + testsuite/tests/th/TH_1tuple.hs | 15 + testsuite/tests/th/TH_1tuple.stderr | 5 + testsuite/tests/th/TH_Depends.hs | 9 + testsuite/tests/th/TH_Depends.stdout | 4 + testsuite/tests/th/TH_Depends_External.hs | 12 + testsuite/tests/th/TH_NestedSplices.hs | 31 + testsuite/tests/th/TH_NestedSplices_Lib.hs | 14 + testsuite/tests/th/TH_Promoted1Tuple.hs | 7 + testsuite/tests/th/TH_Promoted1Tuple.stderr | 4 + testsuite/tests/th/TH_PromotedList.hs | 20 + testsuite/tests/th/TH_PromotedList.stderr | 3 + testsuite/tests/th/TH_PromotedTuple.hs | 18 + testsuite/tests/th/TH_PromotedTuple.stderr | 9 + testsuite/tests/th/TH_RichKinds.hs | 21 + testsuite/tests/th/TH_RichKinds.stderr | 9 + testsuite/tests/th/TH_RichKinds2.hs | 49 + testsuite/tests/th/TH_RichKinds2.stderr | 9 + testsuite/tests/th/TH_Roles1.hs | 9 + testsuite/tests/th/TH_Roles1.stderr | 5 + testsuite/tests/th/TH_Roles2.hs | 9 + testsuite/tests/th/TH_Roles2.stderr | 17 + testsuite/tests/th/TH_Roles3.hs | 11 + testsuite/tests/th/TH_Roles3.stderr | 2 + testsuite/tests/th/TH_Roles4.hs | 12 + testsuite/tests/th/TH_Roles4.stderr | 1 + testsuite/tests/th/TH_StringPrimL.hs | 22 + testsuite/tests/th/TH_StringPrimL.stdout | 4 + testsuite/tests/th/TH_TyInstWhere1.hs | 15 + testsuite/tests/th/TH_TyInstWhere1.stderr | 9 + testsuite/tests/th/TH_TyInstWhere2.hs | 13 + testsuite/tests/th/TH_TyInstWhere2.stderr | 5 + testsuite/tests/th/TH_bracket1.hs | 7 + testsuite/tests/th/TH_bracket2.hs | 7 + testsuite/tests/th/TH_bracket3.hs | 10 + testsuite/tests/th/TH_class1.hs | 7 + testsuite/tests/th/TH_dataD1.hs | 11 + testsuite/tests/th/TH_dupdecl.hs | 10 + testsuite/tests/th/TH_dupdecl.stderr | 5 + testsuite/tests/th/TH_emptycase.hs | 12 + testsuite/tests/th/TH_exn1.hs | 11 + testsuite/tests/th/TH_exn1.stderr | 6 + testsuite/tests/th/TH_exn2.hs | 11 + testsuite/tests/th/TH_exn2.stderr | 6 + testsuite/tests/th/TH_fail.hs | 7 + testsuite/tests/th/TH_fail.stderr | 2 + testsuite/tests/th/TH_foreignInterruptible.hs | 11 + testsuite/tests/th/TH_foreignInterruptible.stderr | 13 + testsuite/tests/th/TH_genEx.hs | 14 + testsuite/tests/th/TH_genEx.stderr | 6 + testsuite/tests/th/TH_genExLib.hs | 20 + testsuite/tests/th/TH_ghci1.script | 6 + testsuite/tests/th/TH_ghci1.stdout | 2 + testsuite/tests/th/TH_import_loop/Main.hs | 7 + testsuite/tests/th/TH_import_loop/Makefile | 3 + testsuite/tests/th/TH_import_loop/ModuleA.hs | 5 + testsuite/tests/th/TH_import_loop/ModuleA.hs-boot | 3 + testsuite/tests/th/TH_import_loop/ModuleB.hs | 9 + testsuite/tests/th/TH_import_loop/ModuleC.hs | 9 + testsuite/tests/th/TH_import_loop/TH_import_loop.T | 10 + testsuite/tests/th/TH_lookupName.hs | 35 + testsuite/tests/th/TH_lookupName.stdout | 14 + testsuite/tests/th/TH_lookupName_Lib.hs | 9 + testsuite/tests/th/TH_mkName.hs | 20 + testsuite/tests/th/TH_ppr1.hs | 37 + testsuite/tests/th/TH_ppr1.stdout | 14 + testsuite/tests/th/TH_pragma.hs | 12 + testsuite/tests/th/TH_pragma.stderr | 18 + testsuite/tests/th/TH_raiseErr1.hs | 4 + testsuite/tests/th/TH_recover.hs | 12 + testsuite/tests/th/TH_recover.stdout | 1 + testsuite/tests/th/TH_reifyDecl1.hs | 88 + testsuite/tests/th/TH_reifyDecl1.stderr | 35 + testsuite/tests/th/TH_reifyDecl2.hs | 12 + testsuite/tests/th/TH_reifyDecl2.stderr | 2 + testsuite/tests/th/TH_reifyInstances.hs | 49 + testsuite/tests/th/TH_reifyInstances.stderr | 13 + testsuite/tests/th/TH_reifyMkName.hs | 14 + testsuite/tests/th/TH_reifyMkName.stderr | 1 + testsuite/tests/th/TH_reifyType1.hs | 13 + testsuite/tests/th/TH_reifyType2.hs | 9 + testsuite/tests/th/TH_repE1.hs | 30 + testsuite/tests/th/TH_repE2.hs | 36 + testsuite/tests/th/TH_repE2.stdout | 8 + testsuite/tests/th/TH_repE3.hs | 19 + testsuite/tests/th/TH_repGuard.hs | 35 + testsuite/tests/th/TH_repGuard.stderr | 7 + testsuite/tests/th/TH_repGuardOutput.hs | 29 + testsuite/tests/th/TH_repGuardOutput.stdout | 4 + testsuite/tests/th/TH_repPatSig.hs | 18 + testsuite/tests/th/TH_repPatSig.stderr | 4 + testsuite/tests/th/TH_repPrim.hs | 33 + testsuite/tests/th/TH_repPrim.stderr | 8 + testsuite/tests/th/TH_repPrim2.hs | 33 + testsuite/tests/th/TH_repPrim2.stderr | 8 + testsuite/tests/th/TH_repPrimOutput.hs | 23 + testsuite/tests/th/TH_repPrimOutput.stdout | 4 + testsuite/tests/th/TH_repPrimOutput2.hs | 23 + testsuite/tests/th/TH_repPrimOutput2.stdout | 4 + testsuite/tests/th/TH_repUnboxedTuples.hs | 27 + testsuite/tests/th/TH_repUnboxedTuples.stderr | 5 + testsuite/tests/th/TH_runIO.hs | 12 + testsuite/tests/th/TH_runIO.stderr | 6 + testsuite/tests/th/TH_scope.hs | 8 + testsuite/tests/th/TH_scopedTvs.hs | 7 + testsuite/tests/th/TH_sections.hs | 11 + testsuite/tests/th/TH_spliceD1.hs | 10 + testsuite/tests/th/TH_spliceD1.stderr | 6 + testsuite/tests/th/TH_spliceD1_Lib.hs | 13 + testsuite/tests/th/TH_spliceD2.hs | 5 + testsuite/tests/th/TH_spliceD2_Lib.hs | 3 + testsuite/tests/th/TH_spliceDecl1.hs | 10 + testsuite/tests/th/TH_spliceDecl2.hs | 11 + testsuite/tests/th/TH_spliceDecl3.hs | 11 + testsuite/tests/th/TH_spliceDecl3_Lib.hs | 12 + testsuite/tests/th/TH_spliceDecl4.hs | 12 + testsuite/tests/th/TH_spliceDecl4_Lib.hs | 21 + testsuite/tests/th/TH_spliceE1.hs | 6 + testsuite/tests/th/TH_spliceE1.stdout | 1 + testsuite/tests/th/TH_spliceE3.hs | 25 + testsuite/tests/th/TH_spliceE4.hs | 13 + testsuite/tests/th/TH_spliceE4.stdout | 1 + testsuite/tests/th/TH_spliceE5.hs | 15 + testsuite/tests/th/TH_spliceE5.stdout | 1 + testsuite/tests/th/TH_spliceE5_Lib.hs | 10 + testsuite/tests/th/TH_spliceE5_prof.hs | 15 + testsuite/tests/th/TH_spliceE5_prof.stdout | 1 + testsuite/tests/th/TH_spliceE5_prof_Lib.hs | 10 + testsuite/tests/th/TH_spliceE6.hs | 11 + testsuite/tests/th/TH_spliceExpr1.hs | 10 + testsuite/tests/th/TH_spliceGuard.hs | 13 + testsuite/tests/th/TH_spliceInst.hs | 15 + testsuite/tests/th/TH_spliceViewPat/A.hs | 11 + testsuite/tests/th/TH_spliceViewPat/Main.hs | 11 + testsuite/tests/th/TH_spliceViewPat/Makefile | 4 + .../th/TH_spliceViewPat/TH_spliceViewPat.stdout | 2 + testsuite/tests/th/TH_spliceViewPat/test.T | 14 + testsuite/tests/th/TH_tf1.hs | 21 + testsuite/tests/th/TH_tf2.hs | 25 + testsuite/tests/th/TH_tf3.hs | 11 + testsuite/tests/th/TH_tuple1.hs | 15 + testsuite/tests/th/TH_unboxedSingleton.hs | 7 + testsuite/tests/th/TH_unresolvedInfix.hs | 109 + testsuite/tests/th/TH_unresolvedInfix.stdout | 46 + testsuite/tests/th/TH_unresolvedInfix2.hs | 16 + testsuite/tests/th/TH_unresolvedInfix2.stderr | 11 + testsuite/tests/th/TH_unresolvedInfix_Lib.hs | 74 + testsuite/tests/th/TH_viewPatPrint.hs | 10 + testsuite/tests/th/TH_viewPatPrint.stdout | 2 + testsuite/tests/th/TH_where.hs | 8 + testsuite/tests/th/TH_where.stdout | 1 + testsuite/tests/th/all.T | 317 + testsuite/tests/typecheck/Makefile | 3 + testsuite/tests/typecheck/bug1465/B1.hs | 6 + testsuite/tests/typecheck/bug1465/B2.hs | 6 + testsuite/tests/typecheck/bug1465/C.hs | 6 + testsuite/tests/typecheck/bug1465/Makefile | 33 + testsuite/tests/typecheck/bug1465/all.T | 4 + testsuite/tests/typecheck/bug1465/bug1465.stderr | 8 + testsuite/tests/typecheck/bug1465/v1/A.hs | 2 + testsuite/tests/typecheck/bug1465/v1/Setup.hs | 6 + testsuite/tests/typecheck/bug1465/v1/bug1465.cabal | 4 + testsuite/tests/typecheck/bug1465/v2/A.hs | 2 + testsuite/tests/typecheck/bug1465/v2/Setup.hs | 6 + testsuite/tests/typecheck/bug1465/v2/bug1465.cabal | 4 + testsuite/tests/typecheck/prog001/A.hs | 5 + testsuite/tests/typecheck/prog001/B.hs | 7 + testsuite/tests/typecheck/prog001/C.hs | 9 + testsuite/tests/typecheck/prog001/Makefile | 3 + testsuite/tests/typecheck/prog001/test.T | 6 + .../typecheck/prog001/typecheck.prog001.stderr-ghc | 5 + testsuite/tests/typecheck/prog002/A.hs | 8 + testsuite/tests/typecheck/prog002/B.hs | 11 + testsuite/tests/typecheck/prog002/Makefile | 3 + testsuite/tests/typecheck/prog002/test.T | 7 + .../tests/typecheck/should_compile/DfltProb1.hs | 16 + .../tests/typecheck/should_compile/DfltProb2.hs | 23 + testsuite/tests/typecheck/should_compile/FD1.hs | 17 + .../tests/typecheck/should_compile/FD1.stderr | 13 + testsuite/tests/typecheck/should_compile/FD2.hs | 26 + .../tests/typecheck/should_compile/FD2.stderr | 30 + testsuite/tests/typecheck/should_compile/FD3.hs | 15 + .../tests/typecheck/should_compile/FD3.stderr | 5 + testsuite/tests/typecheck/should_compile/FD4.hs | 28 + .../typecheck/should_compile/GivenOverlapping.hs | 21 + .../typecheck/should_compile/GivenTypeSynonym.hs | 14 + testsuite/tests/typecheck/should_compile/HasKey.hs | 22 + .../typecheck/should_compile/HasKey.stderr-ghc | 5 + .../typecheck/should_compile/LoopOfTheDay1.hs | 31 + .../typecheck/should_compile/LoopOfTheDay2.hs | 38 + .../typecheck/should_compile/LoopOfTheDay3.hs | 22 + testsuite/tests/typecheck/should_compile/Makefile | 38 + .../tests/typecheck/should_compile/PolyRec.hs | 29 + .../typecheck/should_compile/PolytypeDecomp.hs | 32 + testsuite/tests/typecheck/should_compile/T1123.hs | 42 + testsuite/tests/typecheck/should_compile/T1470.hs | 38 + testsuite/tests/typecheck/should_compile/T1495.hs | 19 + testsuite/tests/typecheck/should_compile/T1634.hs | 6 + testsuite/tests/typecheck/should_compile/T2045.hs | 126 + testsuite/tests/typecheck/should_compile/T2357.hs | 7 + testsuite/tests/typecheck/should_compile/T2412.hs | 7 + .../tests/typecheck/should_compile/T2412.hs-boot | 4 + testsuite/tests/typecheck/should_compile/T2412A.hs | 6 + testsuite/tests/typecheck/should_compile/T2433.hs | 11 + .../tests/typecheck/should_compile/T2433_Help.hs | 3 + testsuite/tests/typecheck/should_compile/T2478.hs | 7 + .../tests/typecheck/should_compile/T2478.stderr | 3 + .../tests/typecheck/should_compile/T2494-2.hs | 17 + testsuite/tests/typecheck/should_compile/T2494.hs | 16 + .../tests/typecheck/should_compile/T2494.stderr | 34 + testsuite/tests/typecheck/should_compile/T2497.hs | 22 + .../tests/typecheck/should_compile/T2497.stderr | 2 + testsuite/tests/typecheck/should_compile/T2572.hs | 10 + testsuite/tests/typecheck/should_compile/T2683.hs | 31 + testsuite/tests/typecheck/should_compile/T2735.hs | 7 + testsuite/tests/typecheck/should_compile/T2799.hs | 16 + testsuite/tests/typecheck/should_compile/T2846.hs | 4 + testsuite/tests/typecheck/should_compile/T3018.hs | 106 + testsuite/tests/typecheck/should_compile/T3108.hs | 37 + testsuite/tests/typecheck/should_compile/T3219.hs | 11 + testsuite/tests/typecheck/should_compile/T3342.hs | 15 + testsuite/tests/typecheck/should_compile/T3346.hs | 21 + testsuite/tests/typecheck/should_compile/T3391.hs | 14 + testsuite/tests/typecheck/should_compile/T3409.hs | 53 + testsuite/tests/typecheck/should_compile/T3692.hs | 10 + testsuite/tests/typecheck/should_compile/T3696.hs | 12 + .../tests/typecheck/should_compile/T3696.stderr | 3 + testsuite/tests/typecheck/should_compile/T3743.hs | 14 + testsuite/tests/typecheck/should_compile/T3955.hs | 34 + testsuite/tests/typecheck/should_compile/T4284.hs | 17 + testsuite/tests/typecheck/should_compile/T4310.hs | 11 + testsuite/tests/typecheck/should_compile/T4355.hs | 60 + .../tests/typecheck/should_compile/T4355.stderr | 3 + testsuite/tests/typecheck/should_compile/T4361.hs | 30 + testsuite/tests/typecheck/should_compile/T4401.hs | 11 + testsuite/tests/typecheck/should_compile/T4404.hs | 19 + testsuite/tests/typecheck/should_compile/T4418.hs | 20 + testsuite/tests/typecheck/should_compile/T4444.hs | 18 + testsuite/tests/typecheck/should_compile/T4498.hs | 7 + testsuite/tests/typecheck/should_compile/T4524.hs | 251 + testsuite/tests/typecheck/should_compile/T4912.hs | 14 + .../tests/typecheck/should_compile/T4912.stderr | 4 + testsuite/tests/typecheck/should_compile/T4912a.hs | 9 + testsuite/tests/typecheck/should_compile/T4917.hs | 21 + testsuite/tests/typecheck/should_compile/T4952.hs | 36 + testsuite/tests/typecheck/should_compile/T4969.hs | 88 + testsuite/tests/typecheck/should_compile/T5032.hs | 20 + testsuite/tests/typecheck/should_compile/T5120.hs | 12 + testsuite/tests/typecheck/should_compile/T5481.hs | 8 + .../tests/typecheck/should_compile/T5481.stderr | 8 + testsuite/tests/typecheck/should_compile/T5490.hs | 300 + testsuite/tests/typecheck/should_compile/T5514.hs | 13 + testsuite/tests/typecheck/should_compile/T5581.hs | 9 + testsuite/tests/typecheck/should_compile/T5595.hs | 14 + testsuite/tests/typecheck/should_compile/T5643.hs | 22 + testsuite/tests/typecheck/should_compile/T5655.hs | 27 + testsuite/tests/typecheck/should_compile/T5676.hs | 19 + testsuite/tests/typecheck/should_compile/T5792.hs | 10 + testsuite/tests/typecheck/should_compile/T6011.hs | 11 + testsuite/tests/typecheck/should_compile/T6055.hs | 45 + testsuite/tests/typecheck/should_compile/T6134.hs | 8 + testsuite/tests/typecheck/should_compile/T700.hs | 10 + testsuite/tests/typecheck/should_compile/T7050.hs | 3 + .../tests/typecheck/should_compile/T7050.stderr | 5 + testsuite/tests/typecheck/should_compile/T7147.hs | 35 + testsuite/tests/typecheck/should_compile/T7171.hs | 14 + testsuite/tests/typecheck/should_compile/T7171a.hs | 18 + testsuite/tests/typecheck/should_compile/T7173.hs | 18 + testsuite/tests/typecheck/should_compile/T7196.hs | 40 + testsuite/tests/typecheck/should_compile/T7268.hs | 11 + testsuite/tests/typecheck/should_compile/T7312.hs | 9 + testsuite/tests/typecheck/should_compile/T7384.hs | 11 + testsuite/tests/typecheck/should_compile/T7408.hs | 6 + testsuite/tests/typecheck/should_compile/T7451.hs | 12 + testsuite/tests/typecheck/should_compile/T7541.hs | 9 + testsuite/tests/typecheck/should_compile/T7562.hs | 3 + .../tests/typecheck/should_compile/T7562.stderr | 5 + testsuite/tests/typecheck/should_compile/T7641.hs | 14 + testsuite/tests/typecheck/should_compile/T7827.hs | 5 + testsuite/tests/typecheck/should_compile/T7875.hs | 32 + testsuite/tests/typecheck/should_compile/T7888.hs | 11 + testsuite/tests/typecheck/should_compile/T7891.hs | 37 + testsuite/tests/typecheck/should_compile/T7903.hs | 6 + .../typecheck/should_compile/T7903.stderr-ghc | 10 + testsuite/tests/typecheck/should_compile/T8392.hs | 17 + testsuite/tests/typecheck/should_compile/T8474.hs | 19 + testsuite/tests/typecheck/should_compile/T8563.hs | 4 + testsuite/tests/typecheck/should_compile/T8565.hs | 6 + .../tests/typecheck/should_compile/Tc170_Aux.hs | 24 + testsuite/tests/typecheck/should_compile/Tc173a.hs | 17 + testsuite/tests/typecheck/should_compile/Tc173b.hs | 6 + .../tests/typecheck/should_compile/Tc239_Help.hs | 23 + .../tests/typecheck/should_compile/Tc245_A.hs | 5 + .../tests/typecheck/should_compile/Tc251_Help.hs | 6 + .../tests/typecheck/should_compile/Tc263_Help.hs | 7 + .../typecheck/should_compile/TcCoercibleCompile.hs | 9 + .../tests/typecheck/should_compile/TcLambdaCase.hs | 17 + .../typecheck/should_compile/TcTypeNatSimple.hs | 94 + .../should_compile/UnboxStrictPrimitiveFields.hs | 28 + testsuite/tests/typecheck/should_compile/all.T | 416 + testsuite/tests/typecheck/should_compile/faxen.hs | 30 + testsuite/tests/typecheck/should_compile/holes.hs | 13 + .../tests/typecheck/should_compile/holes.stderr | 33 + testsuite/tests/typecheck/should_compile/holes2.hs | 5 + .../tests/typecheck/should_compile/holes2.stderr | 20 + testsuite/tests/typecheck/should_compile/holes3.hs | 13 + .../tests/typecheck/should_compile/holes3.stderr | 33 + testsuite/tests/typecheck/should_compile/mc18.hs | 14 + .../tests/typecheck/should_compile/syn-perf.hs | 108 + .../tests/typecheck/should_compile/syn-perf2.hs | 33 + testsuite/tests/typecheck/should_compile/tc001.hs | 3 + testsuite/tests/typecheck/should_compile/tc002.hs | 3 + testsuite/tests/typecheck/should_compile/tc003.hs | 12 + testsuite/tests/typecheck/should_compile/tc004.hs | 5 + testsuite/tests/typecheck/should_compile/tc005.hs | 4 + testsuite/tests/typecheck/should_compile/tc006.hs | 3 + testsuite/tests/typecheck/should_compile/tc007.hs | 9 + testsuite/tests/typecheck/should_compile/tc008.hs | 4 + testsuite/tests/typecheck/should_compile/tc009.hs | 4 + testsuite/tests/typecheck/should_compile/tc010.hs | 3 + testsuite/tests/typecheck/should_compile/tc011.hs | 3 + testsuite/tests/typecheck/should_compile/tc012.hs | 3 + testsuite/tests/typecheck/should_compile/tc013.hs | 3 + testsuite/tests/typecheck/should_compile/tc014.hs | 3 + testsuite/tests/typecheck/should_compile/tc015.hs | 3 + testsuite/tests/typecheck/should_compile/tc016.hs | 3 + testsuite/tests/typecheck/should_compile/tc017.hs | 4 + testsuite/tests/typecheck/should_compile/tc018.hs | 4 + testsuite/tests/typecheck/should_compile/tc019.hs | 3 + testsuite/tests/typecheck/should_compile/tc020.hs | 3 + testsuite/tests/typecheck/should_compile/tc021.hs | 7 + testsuite/tests/typecheck/should_compile/tc022.hs | 5 + testsuite/tests/typecheck/should_compile/tc023.hs | 7 + testsuite/tests/typecheck/should_compile/tc024.hs | 7 + testsuite/tests/typecheck/should_compile/tc025.hs | 3 + testsuite/tests/typecheck/should_compile/tc026.hs | 4 + testsuite/tests/typecheck/should_compile/tc027.hs | 5 + testsuite/tests/typecheck/should_compile/tc028.hs | 3 + testsuite/tests/typecheck/should_compile/tc029.hs | 6 + testsuite/tests/typecheck/should_compile/tc030.hs | 5 + testsuite/tests/typecheck/should_compile/tc031.hs | 3 + testsuite/tests/typecheck/should_compile/tc032.hs | 3 + testsuite/tests/typecheck/should_compile/tc033.hs | 7 + testsuite/tests/typecheck/should_compile/tc034.hs | 11 + testsuite/tests/typecheck/should_compile/tc035.hs | 9 + testsuite/tests/typecheck/should_compile/tc036.hs | 4 + testsuite/tests/typecheck/should_compile/tc037.hs | 9 + testsuite/tests/typecheck/should_compile/tc038.hs | 3 + testsuite/tests/typecheck/should_compile/tc039.hs | 4 + testsuite/tests/typecheck/should_compile/tc040.hs | 9 + testsuite/tests/typecheck/should_compile/tc041.hs | 12 + testsuite/tests/typecheck/should_compile/tc042.hs | 73 + testsuite/tests/typecheck/should_compile/tc043.hs | 18 + testsuite/tests/typecheck/should_compile/tc044.hs | 6 + testsuite/tests/typecheck/should_compile/tc045.hs | 19 + testsuite/tests/typecheck/should_compile/tc046.hs | 9 + testsuite/tests/typecheck/should_compile/tc047.hs | 23 + testsuite/tests/typecheck/should_compile/tc048.hs | 21 + testsuite/tests/typecheck/should_compile/tc049.hs | 39 + testsuite/tests/typecheck/should_compile/tc050.hs | 23 + testsuite/tests/typecheck/should_compile/tc051.hs | 30 + testsuite/tests/typecheck/should_compile/tc052.hs | 8 + testsuite/tests/typecheck/should_compile/tc053.hs | 12 + testsuite/tests/typecheck/should_compile/tc054.hs | 16 + testsuite/tests/typecheck/should_compile/tc055.hs | 3 + testsuite/tests/typecheck/should_compile/tc056.hs | 19 + .../tests/typecheck/should_compile/tc056.stderr | 6 + testsuite/tests/typecheck/should_compile/tc057.hs | 18 + testsuite/tests/typecheck/should_compile/tc058.hs | 18 + testsuite/tests/typecheck/should_compile/tc059.hs | 15 + testsuite/tests/typecheck/should_compile/tc060.hs | 12 + testsuite/tests/typecheck/should_compile/tc061.hs | 11 + testsuite/tests/typecheck/should_compile/tc062.hs | 12 + testsuite/tests/typecheck/should_compile/tc063.hs | 18 + testsuite/tests/typecheck/should_compile/tc064.hs | 7 + testsuite/tests/typecheck/should_compile/tc065.hs | 108 + testsuite/tests/typecheck/should_compile/tc066.hs | 4 + testsuite/tests/typecheck/should_compile/tc067.hs | 4 + testsuite/tests/typecheck/should_compile/tc068.hs | 18 + testsuite/tests/typecheck/should_compile/tc069.hs | 4 + testsuite/tests/typecheck/should_compile/tc070.hs | 9 + testsuite/tests/typecheck/should_compile/tc073.hs | 5 + testsuite/tests/typecheck/should_compile/tc074.hs | 18 + testsuite/tests/typecheck/should_compile/tc076.hs | 8 + testsuite/tests/typecheck/should_compile/tc077.hs | 9 + testsuite/tests/typecheck/should_compile/tc078.hs | 8 + .../typecheck/should_compile/tc078.stderr-ghc | 10 + testsuite/tests/typecheck/should_compile/tc079.hs | 16 + testsuite/tests/typecheck/should_compile/tc080.hs | 58 + testsuite/tests/typecheck/should_compile/tc081.hs | 29 + testsuite/tests/typecheck/should_compile/tc082.hs | 12 + testsuite/tests/typecheck/should_compile/tc084.hs | 23 + testsuite/tests/typecheck/should_compile/tc085.hs | 9 + testsuite/tests/typecheck/should_compile/tc086.hs | 60 + testsuite/tests/typecheck/should_compile/tc087.hs | 32 + testsuite/tests/typecheck/should_compile/tc088.hs | 20 + testsuite/tests/typecheck/should_compile/tc089.hs | 77 + testsuite/tests/typecheck/should_compile/tc090.hs | 22 + testsuite/tests/typecheck/should_compile/tc091.hs | 67 + testsuite/tests/typecheck/should_compile/tc092.hs | 11 + testsuite/tests/typecheck/should_compile/tc093.hs | 35 + testsuite/tests/typecheck/should_compile/tc094.hs | 7 + testsuite/tests/typecheck/should_compile/tc095.hs | 237 + testsuite/tests/typecheck/should_compile/tc096.hs | 36 + testsuite/tests/typecheck/should_compile/tc097.hs | 9 + testsuite/tests/typecheck/should_compile/tc098.hs | 31 + testsuite/tests/typecheck/should_compile/tc099.hs | 8 + testsuite/tests/typecheck/should_compile/tc100.hs | 7 + testsuite/tests/typecheck/should_compile/tc101.hs | 15 + testsuite/tests/typecheck/should_compile/tc102.hs | 13 + testsuite/tests/typecheck/should_compile/tc104.hs | 4 + testsuite/tests/typecheck/should_compile/tc105.hs | 15 + testsuite/tests/typecheck/should_compile/tc106.hs | 20 + testsuite/tests/typecheck/should_compile/tc107.hs | 8 + testsuite/tests/typecheck/should_compile/tc108.hs | 19 + testsuite/tests/typecheck/should_compile/tc109.hs | 19 + testsuite/tests/typecheck/should_compile/tc111.hs | 20 + testsuite/tests/typecheck/should_compile/tc112.hs | 12 + testsuite/tests/typecheck/should_compile/tc113.hs | 13 + testsuite/tests/typecheck/should_compile/tc114.hs | 16 + testsuite/tests/typecheck/should_compile/tc115.hs | 18 + .../typecheck/should_compile/tc115.stderr-ghc | 5 + testsuite/tests/typecheck/should_compile/tc116.hs | 18 + .../typecheck/should_compile/tc116.stderr-ghc | 5 + testsuite/tests/typecheck/should_compile/tc117.hs | 19 + testsuite/tests/typecheck/should_compile/tc118.hs | 18 + testsuite/tests/typecheck/should_compile/tc119.hs | 15 + testsuite/tests/typecheck/should_compile/tc120.hs | 8 + testsuite/tests/typecheck/should_compile/tc121.hs | 18 + testsuite/tests/typecheck/should_compile/tc122.hs | 18 + testsuite/tests/typecheck/should_compile/tc123.hs | 17 + testsuite/tests/typecheck/should_compile/tc124.hs | 18 + testsuite/tests/typecheck/should_compile/tc125.hs | 38 + .../typecheck/should_compile/tc125.stderr-ghc | 25 + testsuite/tests/typecheck/should_compile/tc126.hs | 36 + .../typecheck/should_compile/tc126.stderr-ghc | 10 + testsuite/tests/typecheck/should_compile/tc127.hs | 27 + testsuite/tests/typecheck/should_compile/tc128.hs | 10 + testsuite/tests/typecheck/should_compile/tc129.hs | 18 + testsuite/tests/typecheck/should_compile/tc130.hs | 16 + testsuite/tests/typecheck/should_compile/tc131.hs | 30 + testsuite/tests/typecheck/should_compile/tc132.hs | 13 + testsuite/tests/typecheck/should_compile/tc133.hs | 16 + testsuite/tests/typecheck/should_compile/tc134.hs | 11 + .../tests/typecheck/should_compile/tc134.stderr | 5 + testsuite/tests/typecheck/should_compile/tc135.hs | 12 + testsuite/tests/typecheck/should_compile/tc136.hs | 11 + testsuite/tests/typecheck/should_compile/tc137.hs | 34 + testsuite/tests/typecheck/should_compile/tc140.hs | 14 + testsuite/tests/typecheck/should_compile/tc141.hs | 17 + .../tests/typecheck/should_compile/tc141.stderr | 46 + testsuite/tests/typecheck/should_compile/tc142.hs | 11 + testsuite/tests/typecheck/should_compile/tc143.hs | 7 + testsuite/tests/typecheck/should_compile/tc144.hs | 15 + testsuite/tests/typecheck/should_compile/tc145.hs | 18 + testsuite/tests/typecheck/should_compile/tc146.hs | 15 + testsuite/tests/typecheck/should_compile/tc147.hs | 8 + testsuite/tests/typecheck/should_compile/tc148.hs | 12 + testsuite/tests/typecheck/should_compile/tc149.hs | 18 + testsuite/tests/typecheck/should_compile/tc150.hs | 5 + testsuite/tests/typecheck/should_compile/tc151.hs | 30 + testsuite/tests/typecheck/should_compile/tc152.hs | 28 + testsuite/tests/typecheck/should_compile/tc153.hs | 12 + testsuite/tests/typecheck/should_compile/tc154.hs | 9 + testsuite/tests/typecheck/should_compile/tc155.hs | 17 + testsuite/tests/typecheck/should_compile/tc156.hs | 18 + testsuite/tests/typecheck/should_compile/tc157.hs | 19 + testsuite/tests/typecheck/should_compile/tc158.hs | 12 + testsuite/tests/typecheck/should_compile/tc159.hs | 21 + .../tests/typecheck/should_compile/tc159.stdout | 1 + testsuite/tests/typecheck/should_compile/tc160.hs | 14 + testsuite/tests/typecheck/should_compile/tc161.hs | 17 + .../typecheck/should_compile/tc161.stderr-ghc | 5 + testsuite/tests/typecheck/should_compile/tc162.hs | 27 + testsuite/tests/typecheck/should_compile/tc163.hs | 39 + testsuite/tests/typecheck/should_compile/tc164.hs | 12 + testsuite/tests/typecheck/should_compile/tc165.hs | 14 + testsuite/tests/typecheck/should_compile/tc166.hs | 25 + testsuite/tests/typecheck/should_compile/tc167.hs | 21 + .../tests/typecheck/should_compile/tc167.stderr | 5 + testsuite/tests/typecheck/should_compile/tc168.hs | 17 + .../tests/typecheck/should_compile/tc168.stderr | 11 + testsuite/tests/typecheck/should_compile/tc169.hs | 27 + testsuite/tests/typecheck/should_compile/tc170.hs | 16 + testsuite/tests/typecheck/should_compile/tc171.hs | 12 + testsuite/tests/typecheck/should_compile/tc172.hs | 11 + testsuite/tests/typecheck/should_compile/tc174.hs | 5 + testsuite/tests/typecheck/should_compile/tc175.hs | 15 + .../tests/typecheck/should_compile/tc175.stderr | 5 + testsuite/tests/typecheck/should_compile/tc176.hs | 36 + testsuite/tests/typecheck/should_compile/tc177.hs | 108 + testsuite/tests/typecheck/should_compile/tc178.hs | 35 + testsuite/tests/typecheck/should_compile/tc179.hs | 23 + testsuite/tests/typecheck/should_compile/tc180.hs | 63 + testsuite/tests/typecheck/should_compile/tc181.hs | 46 + testsuite/tests/typecheck/should_compile/tc182.hs | 13 + .../tests/typecheck/should_compile/tc182.stderr | 3 + testsuite/tests/typecheck/should_compile/tc183.hs | 26 + testsuite/tests/typecheck/should_compile/tc184.hs | 19 + testsuite/tests/typecheck/should_compile/tc185.hs | 8 + testsuite/tests/typecheck/should_compile/tc186.hs | 16 + testsuite/tests/typecheck/should_compile/tc187.hs | 31 + testsuite/tests/typecheck/should_compile/tc188.hs | 26 + testsuite/tests/typecheck/should_compile/tc189.hs | 26 + testsuite/tests/typecheck/should_compile/tc190.hs | 11 + testsuite/tests/typecheck/should_compile/tc191.hs | 29 + testsuite/tests/typecheck/should_compile/tc192.hs | 145 + testsuite/tests/typecheck/should_compile/tc193.hs | 16 + testsuite/tests/typecheck/should_compile/tc194.hs | 11 + testsuite/tests/typecheck/should_compile/tc195.hs | 18 + testsuite/tests/typecheck/should_compile/tc196.hs | 18 + testsuite/tests/typecheck/should_compile/tc197.hs | 40 + testsuite/tests/typecheck/should_compile/tc198.hs | 9 + testsuite/tests/typecheck/should_compile/tc199.hs | 34 + testsuite/tests/typecheck/should_compile/tc200.hs | 13 + testsuite/tests/typecheck/should_compile/tc201.hs | 25 + testsuite/tests/typecheck/should_compile/tc202.hs | 8 + testsuite/tests/typecheck/should_compile/tc203.hs | 10 + testsuite/tests/typecheck/should_compile/tc204.hs | 19 + testsuite/tests/typecheck/should_compile/tc205.hs | 10 + testsuite/tests/typecheck/should_compile/tc206.hs | 17 + testsuite/tests/typecheck/should_compile/tc207.hs | 16 + testsuite/tests/typecheck/should_compile/tc208.hs | 13 + testsuite/tests/typecheck/should_compile/tc209.hs | 11 + testsuite/tests/typecheck/should_compile/tc210.hs | 12 + testsuite/tests/typecheck/should_compile/tc211.hs | 73 + .../tests/typecheck/should_compile/tc211.stderr | 82 + testsuite/tests/typecheck/should_compile/tc212.hs | 8 + testsuite/tests/typecheck/should_compile/tc213.hs | 49 + testsuite/tests/typecheck/should_compile/tc214.hs | 19 + testsuite/tests/typecheck/should_compile/tc215.hs | 15 + testsuite/tests/typecheck/should_compile/tc216.hs | 39 + testsuite/tests/typecheck/should_compile/tc217.hs | 20 + testsuite/tests/typecheck/should_compile/tc218.hs | 12 + testsuite/tests/typecheck/should_compile/tc219.hs | 10 + testsuite/tests/typecheck/should_compile/tc220.hs | 26 + testsuite/tests/typecheck/should_compile/tc221.hs | 16 + testsuite/tests/typecheck/should_compile/tc222.hs | 38 + testsuite/tests/typecheck/should_compile/tc223.hs | 14 + testsuite/tests/typecheck/should_compile/tc224.hs | 26 + testsuite/tests/typecheck/should_compile/tc225.hs | 7 + testsuite/tests/typecheck/should_compile/tc226.hs | 13 + testsuite/tests/typecheck/should_compile/tc227.hs | 6 + testsuite/tests/typecheck/should_compile/tc228.hs | 20 + testsuite/tests/typecheck/should_compile/tc229.hs | 35 + testsuite/tests/typecheck/should_compile/tc230.hs | 11 + testsuite/tests/typecheck/should_compile/tc231.hs | 29 + .../tests/typecheck/should_compile/tc231.stderr | 32 + testsuite/tests/typecheck/should_compile/tc232.hs | 19 + testsuite/tests/typecheck/should_compile/tc233.hs | 7 + testsuite/tests/typecheck/should_compile/tc234.hs | 11 + testsuite/tests/typecheck/should_compile/tc235.hs | 39 + testsuite/tests/typecheck/should_compile/tc236.hs | 11 + testsuite/tests/typecheck/should_compile/tc237.hs | 20 + testsuite/tests/typecheck/should_compile/tc238.hs | 20 + testsuite/tests/typecheck/should_compile/tc239.hs | 11 + testsuite/tests/typecheck/should_compile/tc240.hs | 14 + testsuite/tests/typecheck/should_compile/tc241.hs | 13 + testsuite/tests/typecheck/should_compile/tc242.hs | 18 + testsuite/tests/typecheck/should_compile/tc243.hs | 11 + .../tests/typecheck/should_compile/tc243.stderr | 3 + testsuite/tests/typecheck/should_compile/tc244.hs | 30 + testsuite/tests/typecheck/should_compile/tc245.hs | 11 + .../tests/typecheck/should_compile/tc245.stdout | 3 + testsuite/tests/typecheck/should_compile/tc246.hs | 7 + testsuite/tests/typecheck/should_compile/tc247.hs | 17 + testsuite/tests/typecheck/should_compile/tc248.hs | 6 + testsuite/tests/typecheck/should_compile/tc249.hs | 5 + testsuite/tests/typecheck/should_compile/tc250.hs | 16 + testsuite/tests/typecheck/should_compile/tc251.hs | 13 + testsuite/tests/typecheck/should_compile/tc252.hs | 17 + testsuite/tests/typecheck/should_compile/tc253.hs | 18 + testsuite/tests/typecheck/should_compile/tc254.hs | 9 + .../tests/typecheck/should_compile/tc254.stderr | 4 + testsuite/tests/typecheck/should_compile/tc255.hs | 13 + testsuite/tests/typecheck/should_compile/tc256.hs | 12 + testsuite/tests/typecheck/should_compile/tc257.hs | 25 + testsuite/tests/typecheck/should_compile/tc258.hs | 15 + testsuite/tests/typecheck/should_compile/tc259.hs | 8 + testsuite/tests/typecheck/should_compile/tc260.hs | 11 + testsuite/tests/typecheck/should_compile/tc261.hs | 4 + testsuite/tests/typecheck/should_compile/tc262.hs | 13 + testsuite/tests/typecheck/should_compile/tc263.hs | 12 + testsuite/tests/typecheck/should_compile/twins.hs | 27 + .../tests/typecheck/should_fail/AssocTyDef01.hs | 10 + .../typecheck/should_fail/AssocTyDef01.stderr | 3 + .../tests/typecheck/should_fail/AssocTyDef02.hs | 8 + .../typecheck/should_fail/AssocTyDef02.stderr | 6 + .../tests/typecheck/should_fail/AssocTyDef03.hs | 7 + .../typecheck/should_fail/AssocTyDef03.stderr | 5 + .../tests/typecheck/should_fail/AssocTyDef04.hs | 7 + .../typecheck/should_fail/AssocTyDef04.stderr | 7 + .../tests/typecheck/should_fail/AssocTyDef05.hs | 7 + .../typecheck/should_fail/AssocTyDef05.stderr | 5 + .../tests/typecheck/should_fail/AssocTyDef06.hs | 7 + .../typecheck/should_fail/AssocTyDef06.stderr | 5 + .../tests/typecheck/should_fail/AssocTyDef07.hs | 6 + .../typecheck/should_fail/AssocTyDef07.stderr | 3 + .../tests/typecheck/should_fail/AssocTyDef08.hs | 5 + .../typecheck/should_fail/AssocTyDef08.stderr | 3 + .../tests/typecheck/should_fail/AssocTyDef09.hs | 9 + .../typecheck/should_fail/AssocTyDef09.stderr | 3 + .../tests/typecheck/should_fail/ContextStack1.hs | 11 + .../typecheck/should_fail/ContextStack1.stderr | 7 + .../tests/typecheck/should_fail/ContextStack2.hs | 9 + .../typecheck/should_fail/ContextStack2.stderr | 9 + .../tests/typecheck/should_fail/FDsFromGivens.hs | 24 + .../typecheck/should_fail/FDsFromGivens.stderr | 10 + .../should_fail/FailDueToGivenOverlapping.hs | 27 + .../should_fail/FailDueToGivenOverlapping.stderr | 12 + .../typecheck/should_fail/FrozenErrorTests.hs | 49 + .../typecheck/should_fail/FrozenErrorTests.stderr | 53 + testsuite/tests/typecheck/should_fail/IPFail.hs | 6 + .../tests/typecheck/should_fail/IPFail.stderr | 9 + .../typecheck/should_fail/LongWayOverlapping.hs | 44 + .../should_fail/LongWayOverlapping.stderr | 7 + testsuite/tests/typecheck/should_fail/Makefile | 3 + testsuite/tests/typecheck/should_fail/SCLoop.hs | 55 + .../tests/typecheck/should_fail/SCLoop.stderr | 5 + .../should_fail/SilentParametersOverlapping.hs | 19 + .../should_fail/SilentParametersOverlapping.stderr | 13 + testsuite/tests/typecheck/should_fail/T1595.hs | 13 + testsuite/tests/typecheck/should_fail/T1595.stderr | 6 + testsuite/tests/typecheck/should_fail/T1633.hs | 6 + testsuite/tests/typecheck/should_fail/T1633.stderr | 5 + testsuite/tests/typecheck/should_fail/T1897a.hs | 11 + .../tests/typecheck/should_fail/T1897a.stderr | 11 + testsuite/tests/typecheck/should_fail/T1899.hs | 16 + testsuite/tests/typecheck/should_fail/T1899.stderr | 11 + .../tests/typecheck/should_fail/T1987a.stderr | 1 + testsuite/tests/typecheck/should_fail/T2126.hs | 5 + testsuite/tests/typecheck/should_fail/T2126.stderr | 4 + testsuite/tests/typecheck/should_fail/T2247.hs | 18 + testsuite/tests/typecheck/should_fail/T2247.stderr | 7 + testsuite/tests/typecheck/should_fail/T2307.hs | 12 + testsuite/tests/typecheck/should_fail/T2307.stderr | 7 + testsuite/tests/typecheck/should_fail/T2354.hs | 7 + testsuite/tests/typecheck/should_fail/T2354.stderr | 6 + testsuite/tests/typecheck/should_fail/T2414.hs | 9 + testsuite/tests/typecheck/should_fail/T2414.stderr | 7 + testsuite/tests/typecheck/should_fail/T2534.hs | 3 + testsuite/tests/typecheck/should_fail/T2534.stderr | 8 + testsuite/tests/typecheck/should_fail/T2538.hs | 13 + testsuite/tests/typecheck/should_fail/T2538.stderr | 14 + testsuite/tests/typecheck/should_fail/T2688.hs | 8 + testsuite/tests/typecheck/should_fail/T2688.stderr | 16 + testsuite/tests/typecheck/should_fail/T2714.hs | 26 + testsuite/tests/typecheck/should_fail/T2714.stderr | 24 + testsuite/tests/typecheck/should_fail/T2806.hs | 13 + testsuite/tests/typecheck/should_fail/T2806.stderr | 9 + testsuite/tests/typecheck/should_fail/T2846b.hs | 6 + .../tests/typecheck/should_fail/T2846b.stderr | 5 + testsuite/tests/typecheck/should_fail/T2994.hs | 15 + testsuite/tests/typecheck/should_fail/T2994.stderr | 16 + testsuite/tests/typecheck/should_fail/T3102.hs | 12 + testsuite/tests/typecheck/should_fail/T3102.stderr | 9 + testsuite/tests/typecheck/should_fail/T3155.hs | 14 + testsuite/tests/typecheck/should_fail/T3155.stderr | 5 + testsuite/tests/typecheck/should_fail/T3176.hs | 9 + testsuite/tests/typecheck/should_fail/T3176.stderr | 7 + testsuite/tests/typecheck/should_fail/T3323.hs | 18 + testsuite/tests/typecheck/should_fail/T3323.stderr | 5 + testsuite/tests/typecheck/should_fail/T3406.hs | 11 + testsuite/tests/typecheck/should_fail/T3406.stderr | 10 + testsuite/tests/typecheck/should_fail/T3468.hs | 8 + .../tests/typecheck/should_fail/T3468.hs-boot | 4 + testsuite/tests/typecheck/should_fail/T3468.stderr | 8 + testsuite/tests/typecheck/should_fail/T3540.hs | 17 + testsuite/tests/typecheck/should_fail/T3540.stderr | 20 + testsuite/tests/typecheck/should_fail/T3592.hs | 12 + testsuite/tests/typecheck/should_fail/T3592.stderr | 13 + testsuite/tests/typecheck/should_fail/T3613.hs | 19 + testsuite/tests/typecheck/should_fail/T3613.stderr | 16 + testsuite/tests/typecheck/should_fail/T3950.hs | 17 + testsuite/tests/typecheck/should_fail/T3950.stderr | 9 + testsuite/tests/typecheck/should_fail/T3966.hs | 5 + testsuite/tests/typecheck/should_fail/T3966.stderr | 8 + testsuite/tests/typecheck/should_fail/T4875.hs | 28 + testsuite/tests/typecheck/should_fail/T4875.stderr | 5 + testsuite/tests/typecheck/should_fail/T5051.hs | 34 + testsuite/tests/typecheck/should_fail/T5051.stderr | 11 + testsuite/tests/typecheck/should_fail/T5084.hs | 12 + testsuite/tests/typecheck/should_fail/T5084.stderr | 3 + testsuite/tests/typecheck/should_fail/T5095.hs | 11 + testsuite/tests/typecheck/should_fail/T5095.stderr | 66 + testsuite/tests/typecheck/should_fail/T5236.hs | 21 + testsuite/tests/typecheck/should_fail/T5236.stderr | 5 + testsuite/tests/typecheck/should_fail/T5246.hs | 11 + testsuite/tests/typecheck/should_fail/T5246.stderr | 9 + testsuite/tests/typecheck/should_fail/T5300.hs | 15 + testsuite/tests/typecheck/should_fail/T5300.stderr | 34 + testsuite/tests/typecheck/should_fail/T5570.hs | 7 + testsuite/tests/typecheck/should_fail/T5570.stderr | 8 + testsuite/tests/typecheck/should_fail/T5684.hs | 62 + testsuite/tests/typecheck/should_fail/T5684.stderr | 64 + testsuite/tests/typecheck/should_fail/T5689.hs | 15 + testsuite/tests/typecheck/should_fail/T5689.stderr | 32 + testsuite/tests/typecheck/should_fail/T5691.hs | 29 + testsuite/tests/typecheck/should_fail/T5691.stderr | 16 + testsuite/tests/typecheck/should_fail/T5853.hs | 16 + testsuite/tests/typecheck/should_fail/T5853.stderr | 17 + testsuite/tests/typecheck/should_fail/T5858.hs | 11 + testsuite/tests/typecheck/should_fail/T5858.stderr | 10 + testsuite/tests/typecheck/should_fail/T5957.hs | 4 + testsuite/tests/typecheck/should_fail/T5957.stderr | 6 + testsuite/tests/typecheck/should_fail/T5978.hs | 26 + testsuite/tests/typecheck/should_fail/T5978.stderr | 5 + testsuite/tests/typecheck/should_fail/T6001.hs | 9 + testsuite/tests/typecheck/should_fail/T6001.stderr | 5 + testsuite/tests/typecheck/should_fail/T6022.hs | 3 + testsuite/tests/typecheck/should_fail/T6022.stderr | 6 + testsuite/tests/typecheck/should_fail/T6069.hs | 17 + testsuite/tests/typecheck/should_fail/T6069.stderr | 21 + testsuite/tests/typecheck/should_fail/T6078.hs | 11 + testsuite/tests/typecheck/should_fail/T6078.stderr | 11 + testsuite/tests/typecheck/should_fail/T6161.hs | 29 + testsuite/tests/typecheck/should_fail/T6161.stderr | 5 + testsuite/tests/typecheck/should_fail/T7019.hs | 18 + testsuite/tests/typecheck/should_fail/T7019.stderr | 6 + testsuite/tests/typecheck/should_fail/T7019a.hs | 14 + .../tests/typecheck/should_fail/T7019a.stderr | 6 + testsuite/tests/typecheck/should_fail/T7175.hs | 11 + testsuite/tests/typecheck/should_fail/T7175.stderr | 6 + testsuite/tests/typecheck/should_fail/T7210.hs | 5 + testsuite/tests/typecheck/should_fail/T7210.stderr | 6 + testsuite/tests/typecheck/should_fail/T7220.hs | 48 + testsuite/tests/typecheck/should_fail/T7220.stderr | 9 + testsuite/tests/typecheck/should_fail/T7264.hs | 13 + testsuite/tests/typecheck/should_fail/T7264.stderr | 12 + testsuite/tests/typecheck/should_fail/T7279.hs | 6 + testsuite/tests/typecheck/should_fail/T7279.stderr | 11 + testsuite/tests/typecheck/should_fail/T7368.hs | 9 + testsuite/tests/typecheck/should_fail/T7368.stderr | 9 + testsuite/tests/typecheck/should_fail/T7368a.hs | 14 + .../tests/typecheck/should_fail/T7368a.stderr | 11 + testsuite/tests/typecheck/should_fail/T7410.hs | 4 + testsuite/tests/typecheck/should_fail/T7410.stderr | 6 + testsuite/tests/typecheck/should_fail/T7453.hs | 32 + testsuite/tests/typecheck/should_fail/T7453.stderr | 45 + testsuite/tests/typecheck/should_fail/T7525.hs | 15 + testsuite/tests/typecheck/should_fail/T7525.stderr | 9 + testsuite/tests/typecheck/should_fail/T7545.hs | 9 + testsuite/tests/typecheck/should_fail/T7545.stderr | 5 + testsuite/tests/typecheck/should_fail/T7609.hs | 11 + testsuite/tests/typecheck/should_fail/T7609.stderr | 10 + testsuite/tests/typecheck/should_fail/T7645.hs | 8 + testsuite/tests/typecheck/should_fail/T7645.stderr | 6 + testsuite/tests/typecheck/should_fail/T7696.hs | 17 + testsuite/tests/typecheck/should_fail/T7696.stderr | 7 + testsuite/tests/typecheck/should_fail/T7697.hs | 4 + testsuite/tests/typecheck/should_fail/T7697.stderr | 4 + testsuite/tests/typecheck/should_fail/T7734.hs | 5 + testsuite/tests/typecheck/should_fail/T7734.stderr | 16 + testsuite/tests/typecheck/should_fail/T7748a.hs | 36 + .../tests/typecheck/should_fail/T7748a.stderr | 15 + testsuite/tests/typecheck/should_fail/T7778.hs | 4 + testsuite/tests/typecheck/should_fail/T7778.stderr | 5 + testsuite/tests/typecheck/should_fail/T7809.hs | 9 + testsuite/tests/typecheck/should_fail/T7809.stderr | 5 + testsuite/tests/typecheck/should_fail/T7851.hs | 6 + testsuite/tests/typecheck/should_fail/T7851.stderr | 8 + testsuite/tests/typecheck/should_fail/T7856.hs | 19 + testsuite/tests/typecheck/should_fail/T7856.stderr | 11 + testsuite/tests/typecheck/should_fail/T7857.hs | 8 + testsuite/tests/typecheck/should_fail/T7857.stderr | 17 + testsuite/tests/typecheck/should_fail/T7869.hs | 3 + testsuite/tests/typecheck/should_fail/T7869.stderr | 28 + testsuite/tests/typecheck/should_fail/T7892.hs | 7 + testsuite/tests/typecheck/should_fail/T7892.stderr | 2 + testsuite/tests/typecheck/should_fail/T7989.hs | 11 + testsuite/tests/typecheck/should_fail/T7989.stderr | 15 + testsuite/tests/typecheck/should_fail/T8142.hs | 11 + testsuite/tests/typecheck/should_fail/T8142.stderr | 28 + testsuite/tests/typecheck/should_fail/T8262.hs | 5 + testsuite/tests/typecheck/should_fail/T8262.stderr | 10 + testsuite/tests/typecheck/should_fail/T8306.hs | 4 + testsuite/tests/typecheck/should_fail/T8306.stderr | 3 + testsuite/tests/typecheck/should_fail/T8392a.hs | 7 + .../tests/typecheck/should_fail/T8392a.stderr | 7 + testsuite/tests/typecheck/should_fail/T8428.hs | 13 + testsuite/tests/typecheck/should_fail/T8428.stderr | 10 + testsuite/tests/typecheck/should_fail/T8450.hs | 8 + testsuite/tests/typecheck/should_fail/T8450.stderr | 13 + testsuite/tests/typecheck/should_fail/T8514.hs | 3 + testsuite/tests/typecheck/should_fail/T8514.stderr | 7 + testsuite/tests/typecheck/should_fail/T8570.hs | 7 + testsuite/tests/typecheck/should_fail/T8570.stderr | 6 + testsuite/tests/typecheck/should_fail/T8570a.hs | 3 + testsuite/tests/typecheck/should_fail/T8570b.hs | 3 + .../tests/typecheck/should_fail/TcCoercibleFail.hs | 36 + .../typecheck/should_fail/TcCoercibleFail.stderr | 59 + .../typecheck/should_fail/TcCoercibleFail2.hs | 5 + .../typecheck/should_fail/TcCoercibleFail2.stderr | 5 + .../typecheck/should_fail/TcCoercibleFail3.hs | 14 + .../typecheck/should_fail/TcCoercibleFail3.stderr | 7 + .../typecheck/should_fail/TcCoercibleFailSafe.hs | 11 + .../should_fail/TcCoercibleFailSafe.stderr | 8 + .../typecheck/should_fail/TcMultiWayIfFail.hs | 8 + .../typecheck/should_fail/TcMultiWayIfFail.stderr | 16 + .../tests/typecheck/should_fail/TcNoNullaryTC.hs | 4 + .../typecheck/should_fail/TcNoNullaryTC.stderr | 5 + .../tests/typecheck/should_fail/TcNullaryTCFail.hs | 6 + .../typecheck/should_fail/TcNullaryTCFail.stderr | 5 + .../tests/typecheck/should_fail/Tcfail186_Help.hs | 5 + .../tests/typecheck/should_fail/Tcfail218_Help.hs | 7 + testsuite/tests/typecheck/should_fail/all.T | 331 + testsuite/tests/typecheck/should_fail/fd-loop.hs | 32 + .../tests/typecheck/should_fail/fd-loop.stderr | 12 + testsuite/tests/typecheck/should_fail/mc19.hs | 11 + testsuite/tests/typecheck/should_fail/mc19.stderr | 9 + testsuite/tests/typecheck/should_fail/mc20.hs | 15 + testsuite/tests/typecheck/should_fail/mc20.stderr | 7 + testsuite/tests/typecheck/should_fail/mc21.hs | 13 + testsuite/tests/typecheck/should_fail/mc21.stderr | 9 + testsuite/tests/typecheck/should_fail/mc22.hs | 11 + testsuite/tests/typecheck/should_fail/mc22.stderr | 21 + testsuite/tests/typecheck/should_fail/mc23.hs | 10 + testsuite/tests/typecheck/should_fail/mc23.stderr | 9 + testsuite/tests/typecheck/should_fail/mc24.hs | 11 + testsuite/tests/typecheck/should_fail/mc24.stderr | 8 + testsuite/tests/typecheck/should_fail/mc25.hs | 10 + testsuite/tests/typecheck/should_fail/mc25.stderr | 18 + testsuite/tests/typecheck/should_fail/tcfail001.hs | 9 + .../tests/typecheck/should_fail/tcfail001.stderr | 7 + .../typecheck/should_fail/tcfail001.stderr-hugs | 4 + testsuite/tests/typecheck/should_fail/tcfail002.hs | 4 + .../tests/typecheck/should_fail/tcfail002.stderr | 8 + .../typecheck/should_fail/tcfail002.stderr-hugs | 5 + testsuite/tests/typecheck/should_fail/tcfail003.hs | 3 + .../tests/typecheck/should_fail/tcfail003.stderr | 6 + .../typecheck/should_fail/tcfail003.stderr-hugs | 3 + testsuite/tests/typecheck/should_fail/tcfail004.hs | 3 + .../tests/typecheck/should_fail/tcfail004.stderr | 9 + .../typecheck/should_fail/tcfail004.stderr-hugs | 4 + testsuite/tests/typecheck/should_fail/tcfail005.hs | 3 + .../tests/typecheck/should_fail/tcfail005.stderr | 8 + .../typecheck/should_fail/tcfail005.stderr-hugs | 4 + testsuite/tests/typecheck/should_fail/tcfail006.hs | 5 + .../tests/typecheck/should_fail/tcfail006.stderr | 6 + .../typecheck/should_fail/tcfail006.stderr-hugs | 3 + testsuite/tests/typecheck/should_fail/tcfail007.hs | 4 + .../tests/typecheck/should_fail/tcfail007.stderr | 8 + .../typecheck/should_fail/tcfail007.stderr-hugs | 1 + testsuite/tests/typecheck/should_fail/tcfail008.hs | 3 + .../tests/typecheck/should_fail/tcfail008.stderr | 20 + .../typecheck/should_fail/tcfail008.stderr-hugs | 3 + testsuite/tests/typecheck/should_fail/tcfail009.hs | 3 + .../tests/typecheck/should_fail/tcfail009.stderr | 6 + .../typecheck/should_fail/tcfail009.stderr-hugs | 5 + testsuite/tests/typecheck/should_fail/tcfail010.hs | 3 + .../tests/typecheck/should_fail/tcfail010.stderr | 6 + .../typecheck/should_fail/tcfail010.stderr-hugs | 3 + testsuite/tests/typecheck/should_fail/tcfail011.hs | 3 + .../tests/typecheck/should_fail/tcfail011.stderr | 2 + .../typecheck/should_fail/tcfail011.stderr-hugs | 1 + testsuite/tests/typecheck/should_fail/tcfail012.hs | 3 + .../tests/typecheck/should_fail/tcfail012.stderr | 5 + .../typecheck/should_fail/tcfail012.stderr-hugs | 4 + testsuite/tests/typecheck/should_fail/tcfail013.hs | 4 + .../tests/typecheck/should_fail/tcfail013.stderr | 6 + .../typecheck/should_fail/tcfail013.stderr-hugs | 4 + testsuite/tests/typecheck/should_fail/tcfail014.hs | 5 + .../tests/typecheck/should_fail/tcfail014.stderr | 8 + .../typecheck/should_fail/tcfail014.stderr-hugs | 6 + testsuite/tests/typecheck/should_fail/tcfail015.hs | 9 + .../tests/typecheck/should_fail/tcfail015.stderr | 5 + .../typecheck/should_fail/tcfail015.stderr-hugs | 1 + testsuite/tests/typecheck/should_fail/tcfail016.hs | 9 + .../tests/typecheck/should_fail/tcfail016.stderr | 22 + .../typecheck/should_fail/tcfail016.stderr-ghc-7.0 | 8 + .../typecheck/should_fail/tcfail016.stderr-hugs | 5 + testsuite/tests/typecheck/should_fail/tcfail017.hs | 13 + .../tests/typecheck/should_fail/tcfail017.stderr | 7 + .../typecheck/should_fail/tcfail017.stderr-hugs | 4 + testsuite/tests/typecheck/should_fail/tcfail018.hs | 5 + .../tests/typecheck/should_fail/tcfail018.stderr | 5 + .../typecheck/should_fail/tcfail018.stderr-hugs | 3 + testsuite/tests/typecheck/should_fail/tcfail019.hs | 20 + .../tests/typecheck/should_fail/tcfail019.stderr | 5 + .../typecheck/should_fail/tcfail019.stderr-hugs | 4 + testsuite/tests/typecheck/should_fail/tcfail020.hs | 16 + .../tests/typecheck/should_fail/tcfail020.stderr | 7 + .../typecheck/should_fail/tcfail020.stderr-hugs | 4 + testsuite/tests/typecheck/should_fail/tcfail021.hs | 8 + .../tests/typecheck/should_fail/tcfail021.stderr | 4 + .../typecheck/should_fail/tcfail021.stderr-hugs | 1 + testsuite/tests/typecheck/should_fail/tcfail023.hs | 16 + .../tests/typecheck/should_fail/tcfail023.stderr | 5 + .../typecheck/should_fail/tcfail023.stderr-hugs | 4 + .../tests/typecheck/should_fail/tcfail025.stderr | 8 + .../tests/typecheck/should_fail/tcfail026.stderr | 13 + testsuite/tests/typecheck/should_fail/tcfail027.hs | 8 + .../tests/typecheck/should_fail/tcfail027.stderr | 8 + .../typecheck/should_fail/tcfail027.stderr-hugs | 1 + testsuite/tests/typecheck/should_fail/tcfail028.hs | 4 + .../tests/typecheck/should_fail/tcfail028.stderr | 7 + .../typecheck/should_fail/tcfail028.stderr-hugs | 1 + testsuite/tests/typecheck/should_fail/tcfail029.hs | 6 + .../tests/typecheck/should_fail/tcfail029.stderr | 5 + .../typecheck/should_fail/tcfail029.stderr-hugs | 1 + testsuite/tests/typecheck/should_fail/tcfail030.hs | 2 + .../tests/typecheck/should_fail/tcfail030.stderr | 3 + testsuite/tests/typecheck/should_fail/tcfail031.hs | 3 + .../tests/typecheck/should_fail/tcfail031.stderr | 6 + .../typecheck/should_fail/tcfail031.stderr-hugs | 5 + testsuite/tests/typecheck/should_fail/tcfail032.hs | 16 + .../tests/typecheck/should_fail/tcfail032.stderr | 12 + .../typecheck/should_fail/tcfail032.stderr-hugs | 4 + testsuite/tests/typecheck/should_fail/tcfail033.hs | 4 + .../tests/typecheck/should_fail/tcfail033.stderr | 9 + .../typecheck/should_fail/tcfail033.stderr-hugs | 5 + testsuite/tests/typecheck/should_fail/tcfail034.hs | 39 + .../tests/typecheck/should_fail/tcfail034.stderr | 12 + testsuite/tests/typecheck/should_fail/tcfail035.hs | 9 + .../tests/typecheck/should_fail/tcfail035.stderr | 5 + .../typecheck/should_fail/tcfail035.stderr-hugs | 4 + testsuite/tests/typecheck/should_fail/tcfail036.hs | 10 + .../tests/typecheck/should_fail/tcfail036.stderr | 11 + .../typecheck/should_fail/tcfail036.stderr-hugs | 4 + testsuite/tests/typecheck/should_fail/tcfail037.hs | 11 + .../tests/typecheck/should_fail/tcfail037.stderr | 8 + .../typecheck/should_fail/tcfail037.stderr-hugs | 2 + testsuite/tests/typecheck/should_fail/tcfail038.hs | 11 + .../tests/typecheck/should_fail/tcfail038.stderr | 10 + .../typecheck/should_fail/tcfail038.stderr-hugs | 1 + testsuite/tests/typecheck/should_fail/tcfail040.hs | 29 + .../tests/typecheck/should_fail/tcfail040.stderr | 9 + .../typecheck/should_fail/tcfail040.stderr-hugs | 3 + testsuite/tests/typecheck/should_fail/tcfail041.hs | 10 + .../tests/typecheck/should_fail/tcfail041.stderr | 5 + testsuite/tests/typecheck/should_fail/tcfail042.hs | 30 + .../tests/typecheck/should_fail/tcfail042.stderr | 9 + .../typecheck/should_fail/tcfail042.stderr-hugs | 4 + testsuite/tests/typecheck/should_fail/tcfail043.hs | 219 + .../tests/typecheck/should_fail/tcfail043.stderr | 40 + .../typecheck/should_fail/tcfail043.stderr-hugs | 3 + testsuite/tests/typecheck/should_fail/tcfail044.hs | 22 + .../tests/typecheck/should_fail/tcfail044.stderr | 16 + .../typecheck/should_fail/tcfail044.stderr-hugs | 1 + testsuite/tests/typecheck/should_fail/tcfail046.hs | 27 + .../tests/typecheck/should_fail/tcfail046.stderr | 16 + .../typecheck/should_fail/tcfail046.stderr-hugs | 1 + testsuite/tests/typecheck/should_fail/tcfail047.hs | 7 + .../tests/typecheck/should_fail/tcfail047.stderr | 8 + .../typecheck/should_fail/tcfail047.stderr-hugs | 1 + testsuite/tests/typecheck/should_fail/tcfail048.hs | 4 + .../tests/typecheck/should_fail/tcfail048.stderr | 2 + .../typecheck/should_fail/tcfail048.stderr-hugs | 1 + testsuite/tests/typecheck/should_fail/tcfail049.hs | 3 + .../tests/typecheck/should_fail/tcfail049.stderr | 2 + .../typecheck/should_fail/tcfail049.stderr-hugs | 1 + testsuite/tests/typecheck/should_fail/tcfail050.hs | 3 + .../tests/typecheck/should_fail/tcfail050.stderr | 2 + .../typecheck/should_fail/tcfail050.stderr-hugs | 1 + testsuite/tests/typecheck/should_fail/tcfail051.hs | 4 + .../tests/typecheck/should_fail/tcfail051.stderr | 2 + .../typecheck/should_fail/tcfail051.stderr-hugs | 1 + testsuite/tests/typecheck/should_fail/tcfail052.hs | 3 + .../tests/typecheck/should_fail/tcfail052.stderr | 2 + .../typecheck/should_fail/tcfail052.stderr-hugs | 1 + testsuite/tests/typecheck/should_fail/tcfail053.hs | 3 + .../tests/typecheck/should_fail/tcfail053.stderr | 2 + .../typecheck/should_fail/tcfail053.stderr-hugs | 1 + testsuite/tests/typecheck/should_fail/tcfail054.hs | 3 + .../tests/typecheck/should_fail/tcfail054.stderr | 2 + .../typecheck/should_fail/tcfail054.stderr-hugs | 1 + testsuite/tests/typecheck/should_fail/tcfail055.hs | 3 + .../tests/typecheck/should_fail/tcfail055.stderr | 5 + .../typecheck/should_fail/tcfail055.stderr-hugs | 4 + testsuite/tests/typecheck/should_fail/tcfail056.hs | 11 + .../tests/typecheck/should_fail/tcfail056.stderr | 2 + .../typecheck/should_fail/tcfail056.stderr-hugs | 4 + testsuite/tests/typecheck/should_fail/tcfail057.hs | 6 + .../tests/typecheck/should_fail/tcfail057.stderr | 4 + .../typecheck/should_fail/tcfail057.stderr-hugs | 1 + testsuite/tests/typecheck/should_fail/tcfail058.hs | 7 + .../tests/typecheck/should_fail/tcfail058.stderr | 5 + .../typecheck/should_fail/tcfail058.stderr-hugs | 1 + testsuite/tests/typecheck/should_fail/tcfail061.hs | 11 + .../tests/typecheck/should_fail/tcfail061.stderr | 8 + .../typecheck/should_fail/tcfail061.stderr-hugs | 1 + testsuite/tests/typecheck/should_fail/tcfail062.hs | 37 + .../tests/typecheck/should_fail/tcfail062.stderr | 6 + .../typecheck/should_fail/tcfail062.stderr-hugs | 1 + testsuite/tests/typecheck/should_fail/tcfail063.hs | 7 + .../tests/typecheck/should_fail/tcfail063.stderr | 5 + .../typecheck/should_fail/tcfail063.stderr-hugs | 1 + testsuite/tests/typecheck/should_fail/tcfail065.hs | 37 + .../tests/typecheck/should_fail/tcfail065.stderr | 13 + .../typecheck/should_fail/tcfail065.stderr-hugs | 4 + testsuite/tests/typecheck/should_fail/tcfail067.hs | 98 + .../tests/typecheck/should_fail/tcfail067.stderr | 76 + .../typecheck/should_fail/tcfail067.stderr-hugs | 5 + testsuite/tests/typecheck/should_fail/tcfail068.hs | 90 + .../tests/typecheck/should_fail/tcfail068.stderr | 121 + testsuite/tests/typecheck/should_fail/tcfail069.hs | 48 + .../tests/typecheck/should_fail/tcfail069.stderr | 7 + .../typecheck/should_fail/tcfail069.stderr-hugs | 4 + testsuite/tests/typecheck/should_fail/tcfail070.hs | 16 + .../tests/typecheck/should_fail/tcfail070.stderr | 5 + .../typecheck/should_fail/tcfail070.stderr-hugs | 1 + testsuite/tests/typecheck/should_fail/tcfail071.hs | 14 + testsuite/tests/typecheck/should_fail/tcfail072.hs | 24 + .../tests/typecheck/should_fail/tcfail072.stderr | 16 + .../typecheck/should_fail/tcfail072.stderr-hugs | 5 + testsuite/tests/typecheck/should_fail/tcfail073.hs | 10 + .../tests/typecheck/should_fail/tcfail073.stderr | 5 + .../typecheck/should_fail/tcfail073.stderr-hugs | 4 + testsuite/tests/typecheck/should_fail/tcfail075.hs | 20 + .../tests/typecheck/should_fail/tcfail075.stderr | 6 + testsuite/tests/typecheck/should_fail/tcfail076.hs | 30 + .../tests/typecheck/should_fail/tcfail076.stderr | 16 + .../typecheck/should_fail/tcfail076.stderr-hugs | 4 + testsuite/tests/typecheck/should_fail/tcfail077.hs | 8 + .../tests/typecheck/should_fail/tcfail077.stderr | 2 + .../typecheck/should_fail/tcfail077.stderr-hugs | 1 + testsuite/tests/typecheck/should_fail/tcfail078.hs | 6 + .../tests/typecheck/should_fail/tcfail078.stderr | 4 + .../typecheck/should_fail/tcfail078.stderr-hugs | 1 + testsuite/tests/typecheck/should_fail/tcfail079.hs | 11 + .../tests/typecheck/should_fail/tcfail079.stderr | 6 + testsuite/tests/typecheck/should_fail/tcfail080.hs | 29 + .../tests/typecheck/should_fail/tcfail080.stderr | 13 + .../typecheck/should_fail/tcfail080.stderr-hugs | 3 + testsuite/tests/typecheck/should_fail/tcfail082.hs | 9 + .../tests/typecheck/should_fail/tcfail082.stderr | 12 + .../typecheck/should_fail/tcfail082.stderr-hugs | 1 + testsuite/tests/typecheck/should_fail/tcfail083.hs | 16 + .../tests/typecheck/should_fail/tcfail083.stderr | 7 + .../typecheck/should_fail/tcfail083.stderr-hugs | 1 + testsuite/tests/typecheck/should_fail/tcfail084.hs | 11 + .../tests/typecheck/should_fail/tcfail084.stderr | 5 + .../typecheck/should_fail/tcfail084.stderr-hugs | 1 + testsuite/tests/typecheck/should_fail/tcfail085.hs | 10 + .../tests/typecheck/should_fail/tcfail085.stderr | 5 + .../typecheck/should_fail/tcfail085.stderr-hugs | 3 + testsuite/tests/typecheck/should_fail/tcfail086.hs | 7 + .../tests/typecheck/should_fail/tcfail086.stderr | 6 + .../typecheck/should_fail/tcfail086.stderr-hugs | 1 + testsuite/tests/typecheck/should_fail/tcfail088.hs | 15 + .../tests/typecheck/should_fail/tcfail088.stderr | 4 + .../typecheck/should_fail/tcfail088.stderr-hugs | 1 + testsuite/tests/typecheck/should_fail/tcfail089.hs | 10 + .../tests/typecheck/should_fail/tcfail089.stderr | 2 + .../typecheck/should_fail/tcfail089.stderr-hugs | 1 + testsuite/tests/typecheck/should_fail/tcfail090.hs | 11 + .../tests/typecheck/should_fail/tcfail090.stderr | 7 + .../tests/typecheck/should_fail/tcfail091.stderr | 6 + .../typecheck/should_fail/tcfail091.stderr-hugs | 1 + testsuite/tests/typecheck/should_fail/tcfail092.hs | 7 + .../tests/typecheck/should_fail/tcfail092.stderr | 3 + testsuite/tests/typecheck/should_fail/tcfail093.hs | 36 + testsuite/tests/typecheck/should_fail/tcfail094.hs | 10 + .../tests/typecheck/should_fail/tcfail094.stderr | 3 + .../typecheck/should_fail/tcfail094.stderr-hugs | 1 + testsuite/tests/typecheck/should_fail/tcfail095.hs | 9 + .../tests/typecheck/should_fail/tcfail095.stderr | 3 + testsuite/tests/typecheck/should_fail/tcfail096.hs | 25 + .../tests/typecheck/should_fail/tcfail096.stderr | 6 + .../typecheck/should_fail/tcfail096.stderr-hugs | 5 + testsuite/tests/typecheck/should_fail/tcfail097.hs | 6 + .../tests/typecheck/should_fail/tcfail097.stderr | 10 + .../typecheck/should_fail/tcfail097.stderr-hugs | 3 + testsuite/tests/typecheck/should_fail/tcfail098.hs | 13 + .../tests/typecheck/should_fail/tcfail098.stderr | 11 + .../typecheck/should_fail/tcfail098.stderr-hugs | 1 + testsuite/tests/typecheck/should_fail/tcfail099.hs | 9 + .../tests/typecheck/should_fail/tcfail099.stderr | 15 + .../typecheck/should_fail/tcfail099.stderr-hugs | 4 + testsuite/tests/typecheck/should_fail/tcfail100.hs | 7 + .../tests/typecheck/should_fail/tcfail100.stderr | 4 + .../typecheck/should_fail/tcfail100.stderr-hugs | 1 + testsuite/tests/typecheck/should_fail/tcfail101.hs | 10 + .../tests/typecheck/should_fail/tcfail101.stderr | 4 + .../typecheck/should_fail/tcfail101.stderr-hugs | 1 + testsuite/tests/typecheck/should_fail/tcfail102.hs | 9 + .../tests/typecheck/should_fail/tcfail102.stderr | 13 + .../typecheck/should_fail/tcfail102.stderr-hugs | 5 + testsuite/tests/typecheck/should_fail/tcfail103.hs | 16 + .../tests/typecheck/should_fail/tcfail103.stderr | 15 + testsuite/tests/typecheck/should_fail/tcfail104.hs | 23 + .../tests/typecheck/should_fail/tcfail104.stderr | 12 + testsuite/tests/typecheck/should_fail/tcfail105.hs | 13 + .../typecheck/should_fail/tcfail105.stderr-hugs | 1 + testsuite/tests/typecheck/should_fail/tcfail106.hs | 15 + .../tests/typecheck/should_fail/tcfail106.stderr | 5 + .../typecheck/should_fail/tcfail106.stderr-hugs | 4 + testsuite/tests/typecheck/should_fail/tcfail107.hs | 14 + .../tests/typecheck/should_fail/tcfail107.stderr | 5 + .../typecheck/should_fail/tcfail107.stderr-hugs | 1 + testsuite/tests/typecheck/should_fail/tcfail108.hs | 9 + .../tests/typecheck/should_fail/tcfail108.stderr | 7 + .../typecheck/should_fail/tcfail108.stderr-hugs | 2 + testsuite/tests/typecheck/should_fail/tcfail109.hs | 16 + .../tests/typecheck/should_fail/tcfail109.stderr | 5 + .../typecheck/should_fail/tcfail109.stderr-hugs | 4 + testsuite/tests/typecheck/should_fail/tcfail110.hs | 9 + .../tests/typecheck/should_fail/tcfail110.stderr | 6 + .../typecheck/should_fail/tcfail110.stderr-hugs | 1 + .../typecheck/should_fail/tcfail111.stderr-hugs | 1 + testsuite/tests/typecheck/should_fail/tcfail112.hs | 15 + .../tests/typecheck/should_fail/tcfail112.stderr | 15 + .../typecheck/should_fail/tcfail112.stderr-hugs | 3 + testsuite/tests/typecheck/should_fail/tcfail113.hs | 19 + .../tests/typecheck/should_fail/tcfail113.stderr | 14 + .../typecheck/should_fail/tcfail113.stderr-hugs | 1 + testsuite/tests/typecheck/should_fail/tcfail114.hs | 13 + .../tests/typecheck/should_fail/tcfail114.stderr | 5 + .../typecheck/should_fail/tcfail114.stderr-hugs | 1 + testsuite/tests/typecheck/should_fail/tcfail116.hs | 6 + .../tests/typecheck/should_fail/tcfail116.stderr | 6 + .../typecheck/should_fail/tcfail116.stderr-hugs | 3 + testsuite/tests/typecheck/should_fail/tcfail117.hs | 6 + .../tests/typecheck/should_fail/tcfail117.stderr | 13 + .../typecheck/should_fail/tcfail117.stderr-hugs | 1 + testsuite/tests/typecheck/should_fail/tcfail118.hs | 15 + .../tests/typecheck/should_fail/tcfail118.stderr | 8 + .../typecheck/should_fail/tcfail118.stderr-hugs | 4 + testsuite/tests/typecheck/should_fail/tcfail119.hs | 14 + .../tests/typecheck/should_fail/tcfail119.stderr | 5 + .../typecheck/should_fail/tcfail119.stderr-hugs | 4 + testsuite/tests/typecheck/should_fail/tcfail121.hs | 14 + .../tests/typecheck/should_fail/tcfail121.stderr | 12 + testsuite/tests/typecheck/should_fail/tcfail122.hs | 8 + .../tests/typecheck/should_fail/tcfail122.stderr | 17 + testsuite/tests/typecheck/should_fail/tcfail123.hs | 12 + .../tests/typecheck/should_fail/tcfail123.stderr | 8 + testsuite/tests/typecheck/should_fail/tcfail124.hs | 14 + testsuite/tests/typecheck/should_fail/tcfail125.hs | 11 + .../tests/typecheck/should_fail/tcfail125.stderr | 11 + .../typecheck/should_fail/tcfail125.stderr-hugs | 5 + testsuite/tests/typecheck/should_fail/tcfail126.hs | 31 + testsuite/tests/typecheck/should_fail/tcfail127.hs | 7 + .../tests/typecheck/should_fail/tcfail127.stderr | 5 + testsuite/tests/typecheck/should_fail/tcfail128.hs | 29 + .../tests/typecheck/should_fail/tcfail128.stderr | 21 + .../typecheck/should_fail/tcfail128.stderr-hugs | 5 + testsuite/tests/typecheck/should_fail/tcfail129.hs | 19 + .../tests/typecheck/should_fail/tcfail129.stderr | 12 + .../typecheck/should_fail/tcfail129.stderr-hugs | 1 + testsuite/tests/typecheck/should_fail/tcfail130.hs | 16 + .../tests/typecheck/should_fail/tcfail130.stderr | 5 + .../typecheck/should_fail/tcfail130.stderr-hugs | 3 + testsuite/tests/typecheck/should_fail/tcfail131.hs | 7 + .../tests/typecheck/should_fail/tcfail131.stderr | 13 + testsuite/tests/typecheck/should_fail/tcfail132.hs | 19 + .../tests/typecheck/should_fail/tcfail132.stderr | 6 + .../typecheck/should_fail/tcfail132.stderr-hugs | 1 + testsuite/tests/typecheck/should_fail/tcfail133.hs | 79 + .../tests/typecheck/should_fail/tcfail133.stderr | 26 + testsuite/tests/typecheck/should_fail/tcfail134.hs | 5 + .../tests/typecheck/should_fail/tcfail134.stderr | 6 + .../typecheck/should_fail/tcfail134.stderr-hugs | 1 + testsuite/tests/typecheck/should_fail/tcfail135.hs | 9 + .../tests/typecheck/should_fail/tcfail135.stderr | 6 + .../typecheck/should_fail/tcfail135.stderr-hugs | 1 + testsuite/tests/typecheck/should_fail/tcfail136.hs | 9 + .../tests/typecheck/should_fail/tcfail136.stderr | 7 + testsuite/tests/typecheck/should_fail/tcfail137.hs | 8 + .../tests/typecheck/should_fail/tcfail137.stderr | 8 + testsuite/tests/typecheck/should_fail/tcfail138.hs | 36 + testsuite/tests/typecheck/should_fail/tcfail139.hs | 6 + .../tests/typecheck/should_fail/tcfail139.stderr | 7 + testsuite/tests/typecheck/should_fail/tcfail140.hs | 22 + .../tests/typecheck/should_fail/tcfail140.stderr | 38 + testsuite/tests/typecheck/should_fail/tcfail142.hs | 21 + .../tests/typecheck/should_fail/tcfail142.stderr | 11 + testsuite/tests/typecheck/should_fail/tcfail143.hs | 116 + .../tests/typecheck/should_fail/tcfail143.stderr | 5 + testsuite/tests/typecheck/should_fail/tcfail144.hs | 18 + testsuite/tests/typecheck/should_fail/tcfail145.hs | 12 + testsuite/tests/typecheck/should_fail/tcfail146.hs | 7 + .../tests/typecheck/should_fail/tcfail146.stderr | 6 + testsuite/tests/typecheck/should_fail/tcfail147.hs | 7 + .../tests/typecheck/should_fail/tcfail147.stderr | 7 + testsuite/tests/typecheck/should_fail/tcfail148.hs | 8 + .../tests/typecheck/should_fail/tcfail148.stderr | 7 + testsuite/tests/typecheck/should_fail/tcfail149.hs | 14 + .../tests/typecheck/should_fail/tcfail149.stdout | 1 + testsuite/tests/typecheck/should_fail/tcfail150.hs | 6 + testsuite/tests/typecheck/should_fail/tcfail151.hs | 11 + .../tests/typecheck/should_fail/tcfail151.stderr | 8 + testsuite/tests/typecheck/should_fail/tcfail152.hs | 10 + .../tests/typecheck/should_fail/tcfail152.stderr | 7 + testsuite/tests/typecheck/should_fail/tcfail153.hs | 8 + .../tests/typecheck/should_fail/tcfail153.stderr | 16 + testsuite/tests/typecheck/should_fail/tcfail154.hs | 13 + .../tests/typecheck/should_fail/tcfail154.stderr | 6 + testsuite/tests/typecheck/should_fail/tcfail155.hs | 11 + .../tests/typecheck/should_fail/tcfail155.stderr | 6 + testsuite/tests/typecheck/should_fail/tcfail156.hs | 8 + .../tests/typecheck/should_fail/tcfail156.stderr | 6 + testsuite/tests/typecheck/should_fail/tcfail157.hs | 39 + .../tests/typecheck/should_fail/tcfail157.stderr | 12 + testsuite/tests/typecheck/should_fail/tcfail158.hs | 15 + .../tests/typecheck/should_fail/tcfail158.stderr | 5 + testsuite/tests/typecheck/should_fail/tcfail159.hs | 9 + .../tests/typecheck/should_fail/tcfail159.stderr | 8 + testsuite/tests/typecheck/should_fail/tcfail160.hs | 8 + .../tests/typecheck/should_fail/tcfail160.stderr | 5 + testsuite/tests/typecheck/should_fail/tcfail161.hs | 7 + .../tests/typecheck/should_fail/tcfail161.stderr | 5 + testsuite/tests/typecheck/should_fail/tcfail162.hs | 12 + .../tests/typecheck/should_fail/tcfail162.stderr | 7 + testsuite/tests/typecheck/should_fail/tcfail164.hs | 18 + .../tests/typecheck/should_fail/tcfail164.stderr | 15 + testsuite/tests/typecheck/should_fail/tcfail165.hs | 16 + .../tests/typecheck/should_fail/tcfail165.stderr | 12 + testsuite/tests/typecheck/should_fail/tcfail166.hs | 6 + .../tests/typecheck/should_fail/tcfail166.stderr | 5 + testsuite/tests/typecheck/should_fail/tcfail167.hs | 15 + .../tests/typecheck/should_fail/tcfail167.stderr | 9 + testsuite/tests/typecheck/should_fail/tcfail168.hs | 65 + .../tests/typecheck/should_fail/tcfail168.stderr | 12 + testsuite/tests/typecheck/should_fail/tcfail169.hs | 8 + .../tests/typecheck/should_fail/tcfail169.stderr | 8 + testsuite/tests/typecheck/should_fail/tcfail170.hs | 8 + .../tests/typecheck/should_fail/tcfail170.stderr | 7 + testsuite/tests/typecheck/should_fail/tcfail171.hs | 9 + .../tests/typecheck/should_fail/tcfail171.stderr | 8 + testsuite/tests/typecheck/should_fail/tcfail172.hs | 22 + testsuite/tests/typecheck/should_fail/tcfail173.hs | 5 + .../tests/typecheck/should_fail/tcfail173.stderr | 4 + testsuite/tests/typecheck/should_fail/tcfail174.hs | 17 + .../tests/typecheck/should_fail/tcfail174.stderr | 32 + testsuite/tests/typecheck/should_fail/tcfail175.hs | 12 + .../tests/typecheck/should_fail/tcfail175.stderr | 10 + testsuite/tests/typecheck/should_fail/tcfail176.hs | 7 + .../tests/typecheck/should_fail/tcfail176.stderr | 6 + testsuite/tests/typecheck/should_fail/tcfail177.hs | 34 + .../tests/typecheck/should_fail/tcfail177.stderr | 170 + testsuite/tests/typecheck/should_fail/tcfail178.hs | 19 + .../tests/typecheck/should_fail/tcfail178.stderr | 14 + testsuite/tests/typecheck/should_fail/tcfail179.hs | 16 + .../tests/typecheck/should_fail/tcfail179.stderr | 17 + testsuite/tests/typecheck/should_fail/tcfail180.hs | 10 + .../tests/typecheck/should_fail/tcfail180.stderr | 6 + testsuite/tests/typecheck/should_fail/tcfail181.hs | 18 + .../tests/typecheck/should_fail/tcfail181.stderr | 16 + testsuite/tests/typecheck/should_fail/tcfail182.hs | 9 + .../tests/typecheck/should_fail/tcfail182.stderr | 10 + testsuite/tests/typecheck/should_fail/tcfail183.hs | 4 + .../tests/typecheck/should_fail/tcfail183.stderr | 5 + testsuite/tests/typecheck/should_fail/tcfail184.hs | 8 + .../tests/typecheck/should_fail/tcfail184.stderr | 7 + testsuite/tests/typecheck/should_fail/tcfail185.hs | 13 + .../tests/typecheck/should_fail/tcfail185.stderr | 11 + testsuite/tests/typecheck/should_fail/tcfail186.hs | 7 + .../tests/typecheck/should_fail/tcfail186.stderr | 8 + .../typecheck/should_fail/tcfail186.stderr-ghc-7.0 | 7 + testsuite/tests/typecheck/should_fail/tcfail187.hs | 7 + .../tests/typecheck/should_fail/tcfail187.stderr | 5 + testsuite/tests/typecheck/should_fail/tcfail188.hs | 17 + testsuite/tests/typecheck/should_fail/tcfail189.hs | 11 + .../tests/typecheck/should_fail/tcfail189.stderr | 8 + testsuite/tests/typecheck/should_fail/tcfail190.hs | 15 + .../tests/typecheck/should_fail/tcfail190.stderr | 7 + testsuite/tests/typecheck/should_fail/tcfail191.hs | 12 + .../tests/typecheck/should_fail/tcfail191.stderr | 9 + testsuite/tests/typecheck/should_fail/tcfail192.hs | 11 + .../tests/typecheck/should_fail/tcfail192.stderr | 9 + testsuite/tests/typecheck/should_fail/tcfail193.hs | 11 + .../tests/typecheck/should_fail/tcfail193.stderr | 9 + testsuite/tests/typecheck/should_fail/tcfail194.hs | 10 + .../tests/typecheck/should_fail/tcfail194.stderr | 9 + testsuite/tests/typecheck/should_fail/tcfail195.hs | 6 + .../tests/typecheck/should_fail/tcfail195.stderr | 5 + testsuite/tests/typecheck/should_fail/tcfail196.hs | 7 + .../tests/typecheck/should_fail/tcfail196.stderr | 5 + testsuite/tests/typecheck/should_fail/tcfail197.hs | 7 + .../tests/typecheck/should_fail/tcfail197.stderr | 5 + testsuite/tests/typecheck/should_fail/tcfail198.hs | 7 + .../tests/typecheck/should_fail/tcfail198.stderr | 13 + testsuite/tests/typecheck/should_fail/tcfail199.hs | 5 + .../tests/typecheck/should_fail/tcfail199.stderr | 5 + testsuite/tests/typecheck/should_fail/tcfail200.hs | 5 + .../tests/typecheck/should_fail/tcfail200.stderr | 10 + testsuite/tests/typecheck/should_fail/tcfail201.hs | 23 + .../tests/typecheck/should_fail/tcfail201.stderr | 19 + testsuite/tests/typecheck/should_fail/tcfail202.hs | 13 + .../tests/typecheck/should_fail/tcfail202.stderr | 7 + testsuite/tests/typecheck/should_fail/tcfail203.hs | 54 + .../tests/typecheck/should_fail/tcfail203.stderr | 36 + .../tests/typecheck/should_fail/tcfail203a.hs | 10 + .../tests/typecheck/should_fail/tcfail203a.stderr | 6 + testsuite/tests/typecheck/should_fail/tcfail204.hs | 11 + .../tests/typecheck/should_fail/tcfail204.stderr | 12 + testsuite/tests/typecheck/should_fail/tcfail205.hs | 3 + testsuite/tests/typecheck/should_fail/tcfail206.hs | 20 + .../tests/typecheck/should_fail/tcfail206.stderr | 50 + testsuite/tests/typecheck/should_fail/tcfail207.hs | 9 + .../tests/typecheck/should_fail/tcfail207.stderr | 14 + testsuite/tests/typecheck/should_fail/tcfail208.hs | 5 + .../tests/typecheck/should_fail/tcfail208.stderr | 9 + testsuite/tests/typecheck/should_fail/tcfail209.hs | 7 + .../tests/typecheck/should_fail/tcfail209.stderr | 5 + .../tests/typecheck/should_fail/tcfail209a.hs | 4 + .../tests/typecheck/should_fail/tcfail209a.stderr | 6 + testsuite/tests/typecheck/should_fail/tcfail210.hs | 9 + .../tests/typecheck/should_fail/tcfail210.stderr | 3 + testsuite/tests/typecheck/should_fail/tcfail211.hs | 16 + .../tests/typecheck/should_fail/tcfail211.stderr | 6 + testsuite/tests/typecheck/should_fail/tcfail212.hs | 14 + .../tests/typecheck/should_fail/tcfail212.stderr | 10 + testsuite/tests/typecheck/should_fail/tcfail213.hs | 8 + .../tests/typecheck/should_fail/tcfail213.stderr | 7 + testsuite/tests/typecheck/should_fail/tcfail214.hs | 9 + .../tests/typecheck/should_fail/tcfail214.stderr | 7 + testsuite/tests/typecheck/should_fail/tcfail215.hs | 9 + .../tests/typecheck/should_fail/tcfail215.stderr | 4 + testsuite/tests/typecheck/should_fail/tcfail216.hs | 5 + .../tests/typecheck/should_fail/tcfail216.stderr | 4 + testsuite/tests/typecheck/should_fail/tcfail217.hs | 7 + .../tests/typecheck/should_fail/tcfail217.stderr | 4 + testsuite/tests/typecheck/should_fail/tcfail218.hs | 12 + .../tests/typecheck/should_fail/tcfail218.stderr | 11 + testsuite/tests/typecheck/should_run/Defer01.hs | 53 + .../tests/typecheck/should_run/Defer01.stdout | 1 + testsuite/tests/typecheck/should_run/IPRun.hs | 26 + testsuite/tests/typecheck/should_run/IPRun.stdout | 4 + testsuite/tests/typecheck/should_run/Makefile | 3 + testsuite/tests/typecheck/should_run/T1624.hs | 16 + testsuite/tests/typecheck/should_run/T1624.stdout | 2 + testsuite/tests/typecheck/should_run/T1735.hs | 61 + testsuite/tests/typecheck/should_run/T1735.stdout | 1 + .../typecheck/should_run/T1735_Help/Basics.hs | 487 + .../typecheck/should_run/T1735_Help/Context.hs | 57 + .../typecheck/should_run/T1735_Help/Instances.hs | 41 + .../tests/typecheck/should_run/T1735_Help/Main.hs | 62 + .../tests/typecheck/should_run/T1735_Help/State.hs | 18 + .../tests/typecheck/should_run/T1735_Help/Xml.hs | 143 + testsuite/tests/typecheck/should_run/T2722.hs | 34 + testsuite/tests/typecheck/should_run/T2722.stdout | 1 + testsuite/tests/typecheck/should_run/T3500a.hs | 18 + testsuite/tests/typecheck/should_run/T3500a.stdout | 1 + testsuite/tests/typecheck/should_run/T3500b.hs | 20 + testsuite/tests/typecheck/should_run/T3500b.stdout | 1 + .../tests/typecheck/should_run/T3731-short.hs | 88 + .../tests/typecheck/should_run/T3731-short.stdout | 1 + testsuite/tests/typecheck/should_run/T3731.hs | 212 + testsuite/tests/typecheck/should_run/T3731.stdout | 1 + testsuite/tests/typecheck/should_run/T4809.hs | 18 + testsuite/tests/typecheck/should_run/T4809.stdout | 5 + .../tests/typecheck/should_run/T4809_IdentityT.hs | 41 + .../typecheck/should_run/T4809_XMLGenerator.hs | 74 + testsuite/tests/typecheck/should_run/T5573a.hs | 17 + testsuite/tests/typecheck/should_run/T5573a.stdout | 1 + testsuite/tests/typecheck/should_run/T5573b.hs | 12 + testsuite/tests/typecheck/should_run/T5573b.stdout | 1 + testsuite/tests/typecheck/should_run/T5751.hs | 38 + testsuite/tests/typecheck/should_run/T5751.stdout | 3 + testsuite/tests/typecheck/should_run/T5759.hs | 19 + testsuite/tests/typecheck/should_run/T5759.stdout | 1 + testsuite/tests/typecheck/should_run/T5913.hs | 32 + testsuite/tests/typecheck/should_run/T5913.stdout | 4 + testsuite/tests/typecheck/should_run/T6117.hs | 53 + testsuite/tests/typecheck/should_run/T6117.stdout | 1 + testsuite/tests/typecheck/should_run/T7023.hs | 9 + testsuite/tests/typecheck/should_run/T7023.stdout | 1 + testsuite/tests/typecheck/should_run/T7126.hs | 35 + testsuite/tests/typecheck/should_run/T7126.stdout | 2 + testsuite/tests/typecheck/should_run/T7748.hs | 40 + testsuite/tests/typecheck/should_run/T7748.stdout | 1 + testsuite/tests/typecheck/should_run/T7861.hs | 13 + testsuite/tests/typecheck/should_run/T7861.stderr | 10 + testsuite/tests/typecheck/should_run/T7861.stdout | 1 + testsuite/tests/typecheck/should_run/T8119.hs | 3 + testsuite/tests/typecheck/should_run/T8119.script | 3 + testsuite/tests/typecheck/should_run/T8119.stdout | 2 + testsuite/tests/typecheck/should_run/T8492.hs | 6 + testsuite/tests/typecheck/should_run/T8492.stdout | 1 + .../tests/typecheck/should_run/TcCoercible.hs | 73 + .../tests/typecheck/should_run/TcCoercible.stdout | 20 + .../tests/typecheck/should_run/TcNullaryTC.hs | 13 + .../tests/typecheck/should_run/TcNullaryTC.stdout | 1 + testsuite/tests/typecheck/should_run/TcRun025_B.hs | 38 + testsuite/tests/typecheck/should_run/TcRun038_B.hs | 13 + .../typecheck/should_run/TcTypeNatSimpleRun.hs | 34 + .../typecheck/should_run/TcTypeNatSimpleRun.stdout | 1 + testsuite/tests/typecheck/should_run/all.T | 116 + testsuite/tests/typecheck/should_run/church.hs | 44 + testsuite/tests/typecheck/should_run/church.stdout | 1 + testsuite/tests/typecheck/should_run/mc17.hs | 10 + testsuite/tests/typecheck/should_run/mc17.stdout | 1 + testsuite/tests/typecheck/should_run/tcrun001.hs | 16 + .../tests/typecheck/should_run/tcrun001.stdout | 1 + testsuite/tests/typecheck/should_run/tcrun002.hs | 16 + .../tests/typecheck/should_run/tcrun002.stdout | 1 + .../should_run/tcrun002.stdout-alpha-dec-osf3 | 1 + .../should_run/tcrun002.stdout-mips-sgi-irix | 1 + .../typecheck/should_run/tcrun002.stdout-ws-64 | 1 + .../tcrun002.stdout-x86_64-unknown-openbsd | 1 + testsuite/tests/typecheck/should_run/tcrun003.hs | 27 + .../tests/typecheck/should_run/tcrun003.stdout | 1 + .../tests/typecheck/should_run/tcrun003.stdout-ghc | 1 + testsuite/tests/typecheck/should_run/tcrun004.hs | 72 + .../tests/typecheck/should_run/tcrun004.stdout | 2 + testsuite/tests/typecheck/should_run/tcrun005.hs | 25 + .../tests/typecheck/should_run/tcrun005.stdout | 1 + testsuite/tests/typecheck/should_run/tcrun006.hs | 16 + .../tests/typecheck/should_run/tcrun006.stdout | 1 + testsuite/tests/typecheck/should_run/tcrun008.hs | 26 + .../tests/typecheck/should_run/tcrun008.stdout | 2 + testsuite/tests/typecheck/should_run/tcrun009.hs | 25 + .../tests/typecheck/should_run/tcrun009.stdout | 1 + testsuite/tests/typecheck/should_run/tcrun010.hs | 44 + .../tests/typecheck/should_run/tcrun010.stdout | 1 + testsuite/tests/typecheck/should_run/tcrun011.hs | 25 + .../tests/typecheck/should_run/tcrun011.stdout | 1 + testsuite/tests/typecheck/should_run/tcrun012.hs | 15 + .../tests/typecheck/should_run/tcrun012.stdout | 2 + testsuite/tests/typecheck/should_run/tcrun013.hs | 10 + .../tests/typecheck/should_run/tcrun013.stdout | 1 + testsuite/tests/typecheck/should_run/tcrun014.hs | 22 + .../tests/typecheck/should_run/tcrun014.stdout | 1 + testsuite/tests/typecheck/should_run/tcrun015.hs | 21 + .../tests/typecheck/should_run/tcrun015.stdout | 1 + testsuite/tests/typecheck/should_run/tcrun016.hs | 48 + .../tests/typecheck/should_run/tcrun016.stdout | 1 + testsuite/tests/typecheck/should_run/tcrun017.hs | 14 + .../tests/typecheck/should_run/tcrun017.stdout | 2 + testsuite/tests/typecheck/should_run/tcrun018.hs | 84 + .../tests/typecheck/should_run/tcrun018.stdout | 2 + testsuite/tests/typecheck/should_run/tcrun019.hs | 21 + .../tests/typecheck/should_run/tcrun019.stdout | 1 + testsuite/tests/typecheck/should_run/tcrun020.hs | 22 + .../tests/typecheck/should_run/tcrun020.stdout | 1 + testsuite/tests/typecheck/should_run/tcrun021.hs | 60 + .../tests/typecheck/should_run/tcrun021.stdout | 1 + testsuite/tests/typecheck/should_run/tcrun022.hs | 23 + .../tests/typecheck/should_run/tcrun022.stdout | 1 + testsuite/tests/typecheck/should_run/tcrun023.hs | 13 + .../tests/typecheck/should_run/tcrun023.stdout | 2 + testsuite/tests/typecheck/should_run/tcrun024.hs | 43 + .../tests/typecheck/should_run/tcrun024.stdout | 4 + testsuite/tests/typecheck/should_run/tcrun025.hs | 15 + .../tests/typecheck/should_run/tcrun025.stdout | 4 + testsuite/tests/typecheck/should_run/tcrun026.hs | 22 + .../tests/typecheck/should_run/tcrun026.stdout | 1 + testsuite/tests/typecheck/should_run/tcrun027.hs | 12 + .../tests/typecheck/should_run/tcrun027.stdout | 1 + testsuite/tests/typecheck/should_run/tcrun028.hs | 63 + .../tests/typecheck/should_run/tcrun028.stdout | 1 + testsuite/tests/typecheck/should_run/tcrun029.hs | 29 + .../tests/typecheck/should_run/tcrun029.stdout | 1 + testsuite/tests/typecheck/should_run/tcrun030.hs | 20 + .../tests/typecheck/should_run/tcrun030.stdout | 1 + testsuite/tests/typecheck/should_run/tcrun031.hs | 16 + .../tests/typecheck/should_run/tcrun031.stdout | 2 + testsuite/tests/typecheck/should_run/tcrun032.hs | 20 + .../tests/typecheck/should_run/tcrun032.stdout | 2 + testsuite/tests/typecheck/should_run/tcrun033.hs | 31 + .../tests/typecheck/should_run/tcrun033.stdout | 1 + testsuite/tests/typecheck/should_run/tcrun034.hs | 17 + .../tests/typecheck/should_run/tcrun034.stdout | 1 + testsuite/tests/typecheck/should_run/tcrun035.hs | 16 + .../tests/typecheck/should_run/tcrun035.stderr | 11 + testsuite/tests/typecheck/should_run/tcrun036.hs | 58 + .../tests/typecheck/should_run/tcrun036.stdout | 1 + testsuite/tests/typecheck/should_run/tcrun037.hs | 13 + .../tests/typecheck/should_run/tcrun037.stdout | 2 + testsuite/tests/typecheck/should_run/tcrun038.hs | 8 + .../tests/typecheck/should_run/tcrun038.stdout | 1 + testsuite/tests/typecheck/should_run/tcrun039.hs | 22 + .../tests/typecheck/should_run/tcrun039.stdout | 2 + testsuite/tests/typecheck/should_run/tcrun040.hs | 27 + .../tests/typecheck/should_run/tcrun040.stdout | 4 + testsuite/tests/typecheck/should_run/tcrun041.hs | 36 + .../tests/typecheck/should_run/tcrun041.stdout | 2 + testsuite/tests/typecheck/should_run/tcrun042.hs | 10 + .../tests/typecheck/should_run/tcrun042.stdout | 1 + testsuite/tests/typecheck/should_run/tcrun043.hs | 47 + .../tests/typecheck/should_run/tcrun043.stdout | 8 + testsuite/tests/typecheck/should_run/tcrun044.hs | 28 + .../tests/typecheck/should_run/tcrun044.stdout | 2 + testsuite/tests/typecheck/should_run/tcrun045.hs | 47 + .../tests/typecheck/should_run/tcrun045.stdout | 5 + testsuite/tests/typecheck/should_run/tcrun046.hs | 17 + .../tests/typecheck/should_run/tcrun046.stdout | 1 + testsuite/tests/typecheck/should_run/tcrun047.hs | 16 + .../tests/typecheck/should_run/tcrun047.stdout | 1 + testsuite/tests/typecheck/should_run/tcrun048.hs | 13 + .../tests/typecheck/should_run/tcrun048.stdout | 1 + testsuite/tests/typecheck/should_run/tcrun049.hs | 12 + .../tests/typecheck/should_run/tcrun049.stdout | 1 + testsuite/tests/typecheck/should_run/tcrun050.hs | 16 + .../tests/typecheck/should_run/tcrun050.stdout | 1 + testsuite/tests/typecheck/should_run/tcrun051.hs | 26 + .../tests/typecheck/should_run/tcrun051.stdout | 1 + testsuite/tests/typecheck/should_run/testeq2.hs | 68 + .../tests/typecheck/should_run/testeq2.stdout | 1 + testsuite/tests/typecheck/testeq1/FakePrelude.hs | 41 + testsuite/tests/typecheck/testeq1/Main.hs | 24 + testsuite/tests/typecheck/testeq1/Makefile | 3 + testsuite/tests/typecheck/testeq1/TypeCast.hs | 16 + testsuite/tests/typecheck/testeq1/TypeEq.hs | 22 + testsuite/tests/typecheck/testeq1/test.T | 9 + .../typecheck/testeq1/typecheck.testeq1.stdout | 1 + testsuite/tests/warnings/Makefile | 3 + testsuite/tests/warnings/minimal/Makefile | 3 + testsuite/tests/warnings/minimal/WarnMinimal.hs | 116 + .../tests/warnings/minimal/WarnMinimal.stderr | 54 + .../tests/warnings/minimal/WarnMinimalFail1.hs | 5 + .../tests/warnings/minimal/WarnMinimalFail1.stderr | 3 + .../tests/warnings/minimal/WarnMinimalFail2.hs | 8 + .../tests/warnings/minimal/WarnMinimalFail2.stderr | 3 + .../tests/warnings/minimal/WarnMinimalFail3.hs | 13 + .../tests/warnings/minimal/WarnMinimalFail3.stderr | 3 + testsuite/tests/warnings/minimal/all.T | 4 + testsuite/timeout/Makefile | 69 + testsuite/timeout/Setup.hs | 6 + testsuite/timeout/TimeMe.hs | 6 + testsuite/timeout/WinCBindings.hsc | 143 + testsuite/timeout/calibrate | 28 + testsuite/timeout/timeout.cabal | 22 + testsuite/timeout/timeout.hs | 141 + testsuite/timeout/timeout.py | 53 + validate | 3 +- 7568 files changed, 265317 insertions(+), 14 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 e45b9f57a9044e8a20e3cc13bcff86b12b3da405 From git at git.haskell.org Thu Dec 5 13:04:45 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 5 Dec 2013 13:04:45 +0000 (UTC) Subject: [commit: ghc] master: Add `.mailmap` file (8157a26) Message-ID: <20131205130445.623EA2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8157a26640bc88fad263d6396da5d8313ffbfee4/ghc >--------------------------------------------------------------- commit 8157a26640bc88fad263d6396da5d8313ffbfee4 Author: Herbert Valerio Riedel Date: Thu Dec 5 13:54:47 2013 +0100 Add `.mailmap` file This improves the output of `git shortlog` and others, see http://git-scm.com/docs/git-shortlog for more details. The mapping is in part derived from the Darcs author-spelling file which was removed some time ago via 47a018026aee9faef28ddc9b4550425dd0000ceb. There's still a couple of unmapped `` authors in the Git history which will be hopefully mapped in the future as well to provide complete authorship information throughout all of GHC's recorded development history. Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- 8157a26640bc88fad263d6396da5d8313ffbfee4 .mailmap | 71 ++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 71 insertions(+) diff --git a/.mailmap b/.mailmap new file mode 100644 index 0000000..e3b2582 --- /dev/null +++ b/.mailmap @@ -0,0 +1,71 @@ +# see 'man git-shortlog' for more details +# formats: Proper Name [ [Commit Name]] +# +Andy Gill andy at galois.com +Andy Gill andy at unsafeperformio.com +Andy Gill andy +Andy Gill andygill at ku.edu +Audrey Tang audreyt at audreyt.org +Bas van Dijk basvandijk at home.nl +Bas van Dijk v.dijk.bas at gmail.com +Ben Gamari +Ben Lippmeier Ben.Lippmeier.anu.edu.au +Ben Lippmeier Ben.Lippmeier at anu.edu.au +Ben Lippmeier benl at cse.unsw.edu.au +Ben Lippmeier benl at ouroborus.net +Bernie Pope bjpop at csse.unimelb.edu.au +Daan Leijen daan +Dimitrios Vytiniotis +Dimitrios Vytiniotis +Dimitrios Vytiniotis dimitris at microsoft.com +Don Stewart +Don Stewart dons +Don Stewart dons at cse.unsw.edu.au +Don Syme dsyme +Duncan Coutts +Duncan Coutts +Gabriele Keller keller +Gabriele Keller keller at .cse.unsw.edu.au +Gabriele Keller keller at cse.unsw.edu.au +Hans-Wolfgang Loidl hwloidl +Ian Lynagh igloo +John Dias dias at cs.tufts.edu +John Dias dias at eecs.harvard.edu +John Dias dias at eecs.tufts.edu +Jose Pedro Magalhaes +Judah Jacobson judah.jacobson at gmail.com +Julian Seward sewardj +Lennart Augustsson lennart.augustsson at credit-suisse.com +Lennart Augustsson lennart at augustsson.net +Malcolm Wallace malcolm +Manuel M T Chakravarty chak +Marcin 'Qrczak' Kowalczyk qrczak +Neil Mitchell +Neil Mitchell Neil Mitchell +Norman Ramsey nr at eecs.harvard.edu +Pepe Iborra pepe +Reuben Thomas rrt +Roman Leshchinskiy rl at cse.unsw.edu.au +Ross Paterson ross +Sigbjorn Finne sof +Sigbjorn Finne sof at galois.com +Simon Marlow +Simon Marlow +Simon Marlow +Simon Marlow simonm +Simon Marlow simonmar +Simon Marlow simonmar at microsoft.com +Simon Peyton Jones +Simon Peyton Jones +Simon Peyton Jones +Simon Peyton Jones +Simon Peyton Jones +Simon Peyton Jones simonpj +Simon Peyton Jones simonpj at microsoft.com +Sven Panne panne +Sven Panne sven.panne at aedion.de +Tim Harris tharris +Tim Harris tharris at microsoft.com +Will Partain partain +Wolfgang Thaller wolfgang +Wolfgang Thaller wolfgang.thaller at gmx.net From git at git.haskell.org Thu Dec 5 13:06:10 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 5 Dec 2013 13:06:10 +0000 (UTC) Subject: [commit: testsuite] master: More different quotes in error messages following lexer clean-up (27c42f4) Message-ID: <20131205130610.21A852406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/testsuite On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/27c42f4022c491feb52c2c60a17394b0fbd49c86/testsuite >--------------------------------------------------------------- commit 27c42f4022c491feb52c2c60a17394b0fbd49c86 Author: Joachim Breitner Date: Thu Dec 5 13:06:35 2013 +0000 More different quotes in error messages following lexer clean-up >--------------------------------------------------------------- 27c42f4022c491feb52c2c60a17394b0fbd49c86 tests/parser/should_fail/T8431.stderr | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/tests/parser/should_fail/T8431.stderr b/tests/parser/should_fail/T8431.stderr index 25d6e59..2f05838 100644 --- a/tests/parser/should_fail/T8431.stderr +++ b/tests/parser/should_fail/T8431.stderr @@ -1,2 +1,2 @@ -T8431.hs:1:1: parse error on input `)' +T8431.hs:1:1: parse error on input ?)? From git at git.haskell.org Thu Dec 5 14:13:37 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 5 Dec 2013 14:13:37 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Try hard to avoid useless w/w for (# .. #)-returning things (52356ac) Message-ID: <20131205141337.C27C02406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/52356ac0a367b3111bced98eeae50c5d277019b8/ghc >--------------------------------------------------------------- commit 52356ac0a367b3111bced98eeae50c5d277019b8 Author: Joachim Breitner Date: Thu Dec 5 08:54:00 2013 +0000 Try hard to avoid useless w/w for (# .. #)-returning things >--------------------------------------------------------------- 52356ac0a367b3111bced98eeae50c5d277019b8 compiler/stranal/DmdAnal.lhs | 7 ++++++- 1 file changed, 6 insertions(+), 1 deletion(-) diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index 633cf32..fa92cfd 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -518,7 +518,12 @@ dmdAnalVarApp env dmd fun args | Just con <- isDataConWorkId_maybe fun -- Data constructor , isVanillaDataCon con , n_val_args == dataConRepArity con -- Saturated - , let cpr_info = Converges (cprConRes (dataConTag con) arg_rets) + , let -- This removes nested CPR information from applications of (#...#) + -- TODO: This duplicates isWWUseless in WwLib; remove one of them + cpr_info | isUnboxedTupleCon con + , all (not . isJust . returnsCPR_maybe True) arg_rets + = topRes + | otherwise = Converges $ cprConRes (dataConTag con) arg_rets res_ty = foldl bothDmdType (DmdType emptyDmdEnv [] cpr_info) arg_tys = -- pprTrace "dmdAnalVarApp" (vcat [ ppr con, ppr args, ppr n_val_args, ppr cxt_ds -- , ppr arg_tys, ppr cpr_info, ppr res_ty]) $ From git at git.haskell.org Thu Dec 5 14:13:40 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 5 Dec 2013 14:13:40 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Avoid CPR w/w for something that already returns an unboxed tuple (49d188b) Message-ID: <20131205141340.3BD182406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/49d188b7af36aebbbf54810b135f99a465e0a5c2/ghc >--------------------------------------------------------------- commit 49d188b7af36aebbbf54810b135f99a465e0a5c2 Author: Joachim Breitner Date: Wed Dec 4 18:39:16 2013 +0000 Avoid CPR w/w for something that already returns an unboxed tuple >--------------------------------------------------------------- 49d188b7af36aebbbf54810b135f99a465e0a5c2 compiler/basicTypes/Demand.lhs | 1 - compiler/stranal/WwLib.lhs | 14 ++++++++++++++ 2 files changed, 14 insertions(+), 1 deletion(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 50ca43f..9688cdd 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -779,7 +779,6 @@ seqCPRResult :: CPRResult -> () seqCPRResult NoCPR = () seqCPRResult (RetCon n rs) = n `seq` seqListWith seqDmdResult rs - ------------------------------------------------------------------------ -- Combined demand result -- ------------------------------------------------------------------------ diff --git a/compiler/stranal/WwLib.lhs b/compiler/stranal/WwLib.lhs index 8eeac2a..ba56060 100644 --- a/compiler/stranal/WwLib.lhs +++ b/compiler/stranal/WwLib.lhs @@ -542,6 +542,7 @@ mkWWcpr body_ty res , \ body -> decon body (Var arg_var) , idType arg_var ) + _ | isWWUseless body_ty res -> return (id, id, body_ty) _ -> do wrap_wild_uniq <- getUniqueM @@ -593,6 +594,19 @@ mkWWcpr_help inner ty res , \e body -> mkRename e var body ) +-- If something is known to return (# t1, t2 #), this is a CPR property. But it would +-- be useless to then add a wrapper that unwraps that unboxed tuple and recreates it. +-- So try to detect that situation here. +isWWUseless :: Type -> DmdResult -> Bool +isWWUseless ty res + | Just (con_tag, rs) <- returnsCPR_maybe False res + , all isTopRes rs + , Just (data_con, _, _, _) <- deepSplitCprType_maybe con_tag ty + , isUnboxedTupleCon data_con + = True + | otherwise + = False + -- mkRename e v body -- binds v to e in body. This will later be removed by the simplifiers mkRename :: CoreExpr -> Var -> CoreExpr -> CoreExpr From git at git.haskell.org Thu Dec 5 14:13:42 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 5 Dec 2013 14:13:42 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Comments and small refactor (43c2a05) Message-ID: <20131205141342.66E782406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/43c2a059b28b1f307421d2b8f357b0ab28655aed/ghc >--------------------------------------------------------------- commit 43c2a059b28b1f307421d2b8f357b0ab28655aed Author: Simon Peyton Jones Date: Wed Dec 4 16:00:24 2013 +0000 Comments and small refactor >--------------------------------------------------------------- 43c2a059b28b1f307421d2b8f357b0ab28655aed compiler/basicTypes/Demand.lhs | 8 ++++---- compiler/stranal/DmdAnal.lhs | 31 ++++++++++++++----------------- 2 files changed, 18 insertions(+), 21 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index bb2e215..b0c7f01 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -725,16 +725,16 @@ We have lubs, but not glbs; but that is ok. -- Constructed Product Result ------------------------------------------------------------------------ -data CPRResult = NoCPR -- Top of the lattice - | RetCon ConTag [DmdResult] -- Returns a constructor from a data type - deriving( Eq, Show ) - data DmdResult = Diverges -- Definitely diverges | Converges CPRResult -- Definitely converges | Dunno CPRResult -- Might diverge or converge, but in the latter case the -- result shape is described by CPRResult deriving( Eq, Show ) +data CPRResult = NoCPR -- Top of the lattice + | RetCon ConTag [DmdResult] -- Returns a constructor from a data type + deriving( Eq, Show ) + lubCPR :: CPRResult -> CPRResult -> CPRResult lubCPR (RetCon ct1 ds1) (RetCon ct2 ds2) | ct1 == ct2 diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index dc346b3..633cf32 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -524,34 +524,31 @@ dmdAnalVarApp env dmd fun args -- , ppr arg_tys, ppr cpr_info, ppr res_ty]) $ ( res_ty , foldl App (Var fun) args') - - | otherwise - = --pprTrace "dmdAnalVarApp" (vcat [ ppr fun, ppr args, ppr n_val_args - -- , ppr dmd - -- , ppr (mkCallDmdN n_val_args dmd) - -- , ppr $ dmdTransform env fun (mkCallDmdN n_val_args dmd) - -- , ppr $ completeApp env (dmdTransform env fun (mkCallDmdN n_val_args dmd), Var fun) args - -- ]) - completeApp env (dmdTransform env fun (mkCallDmdN n_val_args dmd), Var fun) args where n_val_args = valArgCount args cxt_ds = splitProdCleanDmd n_val_args dmd - (arg_tys, arg_rets, args') = anal_args cxt_ds args + (arg_tys, arg_rets, args') = anal_con_args cxt_ds args -- The constructor itself is lazy -- See Note [Data-con worker strictness] in MkId - anal_args :: [Demand] -> [CoreExpr] -> ([DmdType], [DmdResult], [CoreExpr]) - anal_args _ [] = ([],[],[]) - anal_args ds (arg : args) + anal_con_args :: [Demand] -> [CoreExpr] -> ([DmdType], [DmdResult], [CoreExpr]) + anal_con_args _ [] = ([],[],[]) + anal_con_args ds (arg : args) | isTypeArg arg - , (arg_tys, arg_rets, args') <- anal_args ds args + , (arg_tys, arg_rets, args') <- anal_con_args ds args = (arg_tys, arg_rets, arg:args') - anal_args (d:ds) (arg : args) + anal_con_args (d:ds) (arg : args) | (arg_ty, arg_ret, arg') <- dmdAnalStar env (dmdTransformThunkDmd arg d) arg - , (arg_tys, arg_rets, args') <- anal_args ds args + , (arg_tys, arg_rets, args') <- anal_con_args ds args = --pprTrace "dmdAnalVarApp arg" (vcat [ ppr d, ppr arg, ppr arg_ty, ppr arg' ]) (arg_ty:arg_tys, arg_ret:arg_rets, arg':args') - anal_args ds args = pprPanic "anal_args" (ppr args $$ ppr ds) + anal_con_args ds args = pprPanic "anal_con_args" (ppr args $$ ppr ds) + +dmdAnalVarApp env dmd fun args + = --pprTrace "dmdAnalVarApp" (vcat [ ppr fun, ppr args + -- , ppr $ completeApp env (dmdTransform env fun (mkCallDmdN n_val_args dmd), Var fun) args + -- ]) + completeApp env (dmdTransform env fun (mkCallDmdN (valArgCount args) dmd), Var fun) args \end{code} %************************************************************************ From git at git.haskell.org Thu Dec 5 14:13:44 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 5 Dec 2013 14:13:44 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Leave singleton (# . #) in place if they were already there (6729a76) Message-ID: <20131205141344.B3C872406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/6729a76e0250d2dd8c5b458a825aabf2c2de204d/ghc >--------------------------------------------------------------- commit 6729a76e0250d2dd8c5b458a825aabf2c2de204d Author: Joachim Breitner Date: Thu Dec 5 11:49:14 2013 +0000 Leave singleton (# . #) in place if they were already there >--------------------------------------------------------------- 6729a76e0250d2dd8c5b458a825aabf2c2de204d compiler/stranal/WwLib.lhs | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/compiler/stranal/WwLib.lhs b/compiler/stranal/WwLib.lhs index ba56060..b79dc05 100644 --- a/compiler/stranal/WwLib.lhs +++ b/compiler/stranal/WwLib.lhs @@ -536,13 +536,16 @@ mkWWcpr :: Type -- function body type mkWWcpr body_ty res = do (arg_vars, con_app, decon) <- mkWWcpr_help False body_ty res case arg_vars of + -- Do leave things alone if it is a non-nested unboxed tuple. + -- How does this relates to the next case? Seems to make a difference + -- in Text.Read.Lex, for example. + _ | isWWUseless body_ty res -> return (id, id, body_ty) + -- When we have to wrap only on argument, skip the (# .. #) [arg_var] -> do return ( \ wkr_call -> mkRename wkr_call arg_var con_app , \ body -> decon body (Var arg_var) , idType arg_var ) - - _ | isWWUseless body_ty res -> return (id, id, body_ty) _ -> do wrap_wild_uniq <- getUniqueM From git at git.haskell.org Thu Dec 5 14:13:46 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 5 Dec 2013 14:13:46 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Special-case Var in mkRename (f3eec59) Message-ID: <20131205141347.0118D2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/f3eec593dc08cfe6b616693cb3699f76a9da68e7/ghc >--------------------------------------------------------------- commit f3eec593dc08cfe6b616693cb3699f76a9da68e7 Author: Joachim Breitner Date: Thu Dec 5 09:11:34 2013 +0000 Special-case Var in mkRename >--------------------------------------------------------------- f3eec593dc08cfe6b616693cb3699f76a9da68e7 compiler/stranal/WwLib.lhs | 1 + 1 file changed, 1 insertion(+) diff --git a/compiler/stranal/WwLib.lhs b/compiler/stranal/WwLib.lhs index 4ab2609..8eeac2a 100644 --- a/compiler/stranal/WwLib.lhs +++ b/compiler/stranal/WwLib.lhs @@ -596,6 +596,7 @@ mkWWcpr_help inner ty res -- mkRename e v body -- binds v to e in body. This will later be removed by the simplifiers mkRename :: CoreExpr -> Var -> CoreExpr -> CoreExpr +mkRename e v (Var v') | v == v' = e mkRename e v body = ASSERT( idType v `eqType` exprType e) mkCoreLet (NonRec v e) body From git at git.haskell.org Thu Dec 5 14:13:49 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 5 Dec 2013 14:13:49 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Disable avoiding singleton (# #), for compatibility with old code (3d05abc) Message-ID: <20131205141349.39D572406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/3d05abc113bb9c14fcd70bbcd79176bd5b5c70bc/ghc >--------------------------------------------------------------- commit 3d05abc113bb9c14fcd70bbcd79176bd5b5c70bc Author: Joachim Breitner Date: Thu Dec 5 11:59:24 2013 +0000 Disable avoiding singleton (# #), for compatibility with old code >--------------------------------------------------------------- 3d05abc113bb9c14fcd70bbcd79176bd5b5c70bc compiler/stranal/WwLib.lhs | 3 +++ 1 file changed, 3 insertions(+) diff --git a/compiler/stranal/WwLib.lhs b/compiler/stranal/WwLib.lhs index b79dc05..0fad56b 100644 --- a/compiler/stranal/WwLib.lhs +++ b/compiler/stranal/WwLib.lhs @@ -541,11 +541,14 @@ mkWWcpr body_ty res -- in Text.Read.Lex, for example. _ | isWWUseless body_ty res -> return (id, id, body_ty) + {- -- When we have to wrap only on argument, skip the (# .. #) [arg_var] -> do return ( \ wkr_call -> mkRename wkr_call arg_var con_app , \ body -> decon body (Var arg_var) , idType arg_var ) + -} + _ -> do wrap_wild_uniq <- getUniqueM From git at git.haskell.org Thu Dec 5 14:13:51 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 5 Dec 2013 14:13:51 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Improve pprIfaceStrictSig (c6e4760) Message-ID: <20131205141351.9718B2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/c6e47601667945d51d686718c04e3b8e6cb383e3/ghc >--------------------------------------------------------------- commit c6e47601667945d51d686718c04e3b8e6cb383e3 Author: Joachim Breitner Date: Thu Dec 5 11:41:31 2013 +0000 Improve pprIfaceStrictSig >--------------------------------------------------------------- c6e47601667945d51d686718c04e3b8e6cb383e3 compiler/basicTypes/Demand.lhs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index b0c7f01..50ca43f 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -1507,7 +1507,9 @@ seqStrictSig (StrictSig ty) = seqDmdType ty -- Used for printing top-level strictness pragmas in interface files pprIfaceStrictSig :: StrictSig -> SDoc pprIfaceStrictSig (StrictSig (DmdType _ dmds res)) - = hcat (map ppr dmds) <> ppr res + = hcat (map ppr dmds) <> ppr_res + where + ppr_res = if isTopRes res then empty else ppr res \end{code} Zap absence or one-shot information, under control of flags From git at git.haskell.org Thu Dec 5 14:13:53 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 5 Dec 2013 14:13:53 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Clarify the default demand on demand environments (79e9ef8) Message-ID: <20131205141354.104122406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/79e9ef8929d6bf2f507e3a6f01d4c9c334e2b8da/ghc >--------------------------------------------------------------- commit 79e9ef8929d6bf2f507e3a6f01d4c9c334e2b8da Author: Joachim Breitner Date: Wed Dec 4 17:59:09 2013 +0000 Clarify the default demand on demand environments by adding Notes and using easier to understand combinators. >--------------------------------------------------------------- 79e9ef8929d6bf2f507e3a6f01d4c9c334e2b8da compiler/basicTypes/Demand.lhs | 87 ++++++++++++++++++---------------------- compiler/basicTypes/VarEnv.lhs | 4 +- compiler/stranal/DmdAnal.lhs | 10 ----- compiler/utils/UniqFM.lhs | 12 ++++++ 4 files changed, 54 insertions(+), 59 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 79e9ef8929d6bf2f507e3a6f01d4c9c334e2b8da From git at git.haskell.org Thu Dec 5 14:15:10 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 5 Dec 2013 14:15:10 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Clarify the default demand on demand environments (f7a448d) Message-ID: <20131205141510.23C592406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/f7a448d4e47d9477b63b15f886ddb70a22936ee9/ghc >--------------------------------------------------------------- commit f7a448d4e47d9477b63b15f886ddb70a22936ee9 Author: Joachim Breitner Date: Wed Dec 4 17:59:09 2013 +0000 Clarify the default demand on demand environments by adding Notes and using easier to understand combinators. >--------------------------------------------------------------- f7a448d4e47d9477b63b15f886ddb70a22936ee9 compiler/basicTypes/Demand.lhs | 86 ++++++++++++++++++---------------------- compiler/basicTypes/VarEnv.lhs | 4 +- compiler/stranal/DmdAnal.lhs | 10 ----- compiler/utils/UniqFM.lhs | 12 ++++++ 4 files changed, 53 insertions(+), 59 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 f7a448d4e47d9477b63b15f886ddb70a22936ee9 From git at git.haskell.org Thu Dec 5 18:59:50 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 5 Dec 2013 18:59:50 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Move peelFV from DmdAnal to Demand (1d9620e) Message-ID: <20131205185950.A77FE2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/1d9620ea9b12b17f68014ec83ab336754a8c31e0/ghc >--------------------------------------------------------------- commit 1d9620ea9b12b17f68014ec83ab336754a8c31e0 Author: Joachim Breitner Date: Wed Dec 4 16:09:34 2013 +0000 Move peelFV from DmdAnal to Demand >--------------------------------------------------------------- 1d9620ea9b12b17f68014ec83ab336754a8c31e0 compiler/basicTypes/Demand.lhs | 19 ++++++++++++++++++- compiler/stranal/DmdAnal.lhs | 31 ++++++++++--------------------- 2 files changed, 28 insertions(+), 22 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index ea3719f..a2aa830 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -20,8 +20,10 @@ module Demand ( DmdType(..), dmdTypeDepth, lubDmdType, bothDmdEnv, bothDmdType, topDmdType, botDmdType, mkDmdType, mkTopDmdType, + addDemand, DmdEnv, emptyDmdEnv, + peelFV, DmdResult, CPRResult, isBotRes, isTopRes, resTypeArgDmd, @@ -54,12 +56,13 @@ module Demand ( import StaticFlags import DynFlags import Outputable +import Var ( Var ) import VarEnv import UniqFM import Util import BasicTypes import Binary -import Maybes ( isJust, expectJust ) +import Maybes ( isJust, expectJust, orElse ) import Type ( Type ) import TyCon ( isNewTyCon, isClassTyCon ) @@ -1133,6 +1136,20 @@ peelManyCalls arg_ds (CD { sd = str, ud = abs }) go_abs [] _ = One -- one UCall Many in the demand go_abs (_:as) (UCall One d') = go_abs as d' go_abs _ _ = Many + + +peelFV :: DmdType -> Var -> (DmdType, Demand) +peelFV (DmdType fv ds res) id = -- pprTrace "rfv" (ppr id <+> ppr dmd $$ ppr fv) + (DmdType fv' ds res, dmd) + where + fv' = fv `delVarEnv` id + dmd = lookupVarEnv fv id `orElse` deflt + -- See note [Default demand for variables] + deflt | isBotRes res = botDmd + | otherwise = absDmd + +addDemand :: Demand -> DmdType -> DmdType +addDemand dmd (DmdType fv ds res) = DmdType fv (dmd:ds) res \end{code} Note [Always analyse in virgin pass] diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index ad3cf28..a3c7654 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -32,7 +32,7 @@ import Type ( eqType ) -- import Pair -- import Coercion ( coercionKind ) import Util -import Maybes ( isJust, orElse ) +import Maybes ( isJust ) import TysWiredIn ( unboxedPairDataCon ) import TysPrim ( realWorldStatePrimTy ) \end{code} @@ -719,16 +719,6 @@ addLazyFVs dmd_ty lazy_fvs -- which floats out of the defn for h. Without the modifyEnv, that -- L demand doesn't get both'd with the Bot coming up from the inner -- call to f. So we just get an L demand for x for g. - -peelFV :: DmdEnv -> Var -> DmdResult -> (DmdEnv, Demand) -peelFV fv id res = -- pprTrace "rfv" (ppr id <+> ppr dmd $$ ppr fv) - (fv', dmd) - where - fv' = fv `delVarEnv` id - dmd = lookupVarEnv fv id `orElse` deflt - -- See note [Default demand for variables] - deflt | isBotRes res = botDmd - | otherwise = absDmd \end{code} Note [Default demand for variables] @@ -754,11 +744,11 @@ annotateBndr :: AnalEnv -> DmdType -> Var -> (DmdType, Var) -- The returned var is annotated with demand info -- according to the result demand of the provided demand type -- No effect on the argument demands -annotateBndr env dmd_ty@(DmdType fv ds res) var +annotateBndr env dmd_ty var | isTyVar var = (dmd_ty, var) - | otherwise = (DmdType fv' ds res, set_idDemandInfo env var dmd') + | otherwise = (dmd_ty', set_idDemandInfo env var dmd') where - (fv', dmd) = peelFV fv var res + (dmd_ty', dmd) = peelFV dmd_ty var dmd' | gopt Opt_DictsStrict (ae_dflags env) -- We never want to strictify a recursive let. At the moment @@ -779,13 +769,13 @@ annotateLamBndrs env args_of_dfun ty bndrs = mapAccumR annotate ty bndrs annotateLamIdBndr :: AnalEnv -> DFunFlag -- is this lambda at the top of the RHS of a dfun? - -> DmdType -- Demand type of body + -> DmdType -- Demand type of body -> Count -- One-shot-ness of the lambda - -> Id -- Lambda binder - -> (DmdType, -- Demand type of lambda + -> Id -- Lambda binder + -> (DmdType, -- Demand type of lambda Id) -- and binder annotated with demand -annotateLamIdBndr env arg_of_dfun _dmd_ty@(DmdType fv ds res) one_shot id +annotateLamIdBndr env arg_of_dfun dmd_ty one_shot id -- For lambdas we add the demand to the argument demands -- Only called for Ids = ASSERT( isId id ) @@ -799,9 +789,8 @@ annotateLamIdBndr env arg_of_dfun _dmd_ty@(DmdType fv ds res) one_shot id where (unf_ty, _) = dmdAnalStar env dmd unf - main_ty = DmdType fv' (dmd:ds) res - - (fv', dmd) = peelFV fv id res + main_ty = addDemand dmd dmd_ty' + (dmd_ty', dmd) = peelFV dmd_ty id dmd' | gopt Opt_DictsStrict (ae_dflags env), -- see Note [do not strictify the argument dictionaries of a dfun] From git at git.haskell.org Thu Dec 5 18:59:52 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 5 Dec 2013 18:59:52 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Clarify the default demand on demand environments (d75393c) Message-ID: <20131205185952.DA38A2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/d75393c8237588153451a52bdbd49cdec1c06828/ghc >--------------------------------------------------------------- commit d75393c8237588153451a52bdbd49cdec1c06828 Author: Joachim Breitner Date: Wed Dec 4 17:59:09 2013 +0000 Clarify the default demand on demand environments by adding Notes and using easier to understand combinators. >--------------------------------------------------------------- d75393c8237588153451a52bdbd49cdec1c06828 compiler/basicTypes/Demand.lhs | 84 +++++++++++++++++++--------------------- compiler/basicTypes/VarEnv.lhs | 4 +- compiler/stranal/DmdAnal.lhs | 10 ----- compiler/utils/UniqFM.lhs | 10 +++++ 4 files changed, 52 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 d75393c8237588153451a52bdbd49cdec1c06828 From git at git.haskell.org Thu Dec 5 18:59:55 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 5 Dec 2013 18:59:55 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Remove dmdAnalArg and replace by easier to understand code (b2e931a) Message-ID: <20131205185955.26C342406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/b2e931ae896b2e12222b33962cb7962683f3c739/ghc >--------------------------------------------------------------- commit b2e931ae896b2e12222b33962cb7962683f3c739 Author: Joachim Breitner Date: Wed Dec 4 17:38:25 2013 +0000 Remove dmdAnalArg and replace by easier to understand code >--------------------------------------------------------------- b2e931ae896b2e12222b33962cb7962683f3c739 compiler/stranal/DmdAnal.lhs | 16 ++++++++-------- 1 file changed, 8 insertions(+), 8 deletions(-) diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index ffe66ad..2553226 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -98,13 +98,12 @@ c) The application rule wouldn't be right either evaluation of f in a C(L) demand! \begin{code} -dmdAnalArg :: AnalEnv - -> Demand -- This one takes a *Demand* - -> CoreExpr -> (DmdType, CoreExpr) --- Used for function arguments -dmdAnalArg env dmd e - | exprIsTrivial e = dmdAnalStar env dmd e - | otherwise = dmdAnalStar env (oneifyDmd dmd) e +-- If e is complicated enough to become a thunk, its contents will be evaluated +-- at most once, so oneify it. +dmdTransformThunkDmd :: CoreExpr -> Demand -> Demand +dmdTransformThunkDmd e + | exprIsTrivial e = id + | otherwise = oneifyDmd -- Do not process absent demands -- Otherwise act like in a normal demand analysis @@ -172,7 +171,7 @@ dmdAnal env dmd (App fun arg) -- Non-type arguments call_dmd = mkCallDmd dmd (fun_ty, fun') = dmdAnal env call_dmd fun (arg_dmd, res_ty) = splitDmdTy fun_ty - (arg_ty, arg') = dmdAnalArg env arg_dmd arg + (arg_ty, arg') = dmdAnalStar env (dmdTransformThunkDmd arg arg_dmd) arg in -- pprTrace "dmdAnal:app" (vcat -- [ text "dmd =" <+> ppr dmd @@ -503,6 +502,7 @@ dmdTransform env var dmd | otherwise -- Local non-letrec-bound thing = unitVarDmd var (mkOnceUsedDmd dmd) + \end{code} %************************************************************************ From git at git.haskell.org Thu Dec 5 18:59:57 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 5 Dec 2013 18:59:57 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Add Note [non-algebraic or open body type warning] (8ea1f82) Message-ID: <20131205185957.228BB2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/8ea1f82ae9ad93282ac223281532d0477a608c12/ghc >--------------------------------------------------------------- commit 8ea1f82ae9ad93282ac223281532d0477a608c12 Author: Joachim Breitner Date: Wed Dec 4 17:12:07 2013 +0000 Add Note [non-algebraic or open body type warning] >--------------------------------------------------------------- 8ea1f82ae9ad93282ac223281532d0477a608c12 compiler/stranal/WwLib.lhs | 20 ++++++++++++++++++++ 1 file changed, 20 insertions(+) diff --git a/compiler/stranal/WwLib.lhs b/compiler/stranal/WwLib.lhs index fc94c9b..4acf255 100644 --- a/compiler/stranal/WwLib.lhs +++ b/compiler/stranal/WwLib.lhs @@ -540,6 +540,7 @@ mkWWcpr body_ty res Just con_tag | Just stuff <- deepSplitCprType_maybe con_tag body_ty -> mkWWcpr_help stuff | otherwise + -- See Note [non-algebraic or open body type warning] -> WARN( True, text "mkWWcpr: non-algebraic or open body type" <+> ppr body_ty ) return (id, id, body_ty) @@ -590,6 +591,25 @@ mkUnpackCase scrut co uniq boxing_con unpk_args body bndr = mk_ww_local uniq (exprType casted_scrut) \end{code} +Note [non-algebraic or open body type warning] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + +There are a few cases where the W/W transformation is told that something +returns a constructor, but the type at hand doesn't really match this. One +real-world example involves unsafeCoerce: + foo = IO a + foo = unsafeCoere c_exit + foreign import ccall "c_exit" c_exit :: IO () +Here CPR will tell you that `foo` returns a () constructor for sure, but trying +to create a worker/wrapper for type `a` obviously fails. +(This was a real example until ee8e792 in libraries/base.) + +It does not seem feasilbe to avoid all such cases already in the analyser (and +after all, the analysis is not really wrong), so we simply do nothing here in +mkWWcpr. But we still want to emit warning with -DDEBUG, to hopefully catch +other cases where something went avoidably wrong. + + Note [Profiling and unpacking] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ If the original function looked like From git at git.haskell.org Thu Dec 5 18:59:59 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 5 Dec 2013 18:59:59 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Initial work on Nested CPR (b77ca1c) Message-ID: <20131205185959.63A7F2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/b77ca1cf15d39080159037d6195b39f3fce74225/ghc >--------------------------------------------------------------- commit b77ca1cf15d39080159037d6195b39f3fce74225 Author: Simon Peyton Jones Date: Mon Nov 25 09:59:16 2013 +0000 Initial work on Nested CPR >--------------------------------------------------------------- b77ca1cf15d39080159037d6195b39f3fce74225 compiler/basicTypes/Demand.lhs | 283 ++++++++++++++++++++++++++-------------- compiler/basicTypes/MkId.lhs | 40 +++--- compiler/stranal/DmdAnal.lhs | 115 ++++++++++------ 3 files changed, 284 insertions(+), 154 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 b77ca1cf15d39080159037d6195b39f3fce74225 From git at git.haskell.org Thu Dec 5 19:00:01 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 5 Dec 2013 19:00:01 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Comments and small refactor (229576f) Message-ID: <20131205190001.71D452406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/229576f00283145730afd8c800a08c6a6452399f/ghc >--------------------------------------------------------------- commit 229576f00283145730afd8c800a08c6a6452399f Author: Simon Peyton Jones Date: Wed Dec 4 16:00:24 2013 +0000 Comments and small refactor >--------------------------------------------------------------- 229576f00283145730afd8c800a08c6a6452399f compiler/basicTypes/Demand.lhs | 13 +++++++------ compiler/stranal/DmdAnal.lhs | 25 ++++++++++++++----------- 2 files changed, 21 insertions(+), 17 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index e195191..06ac324 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -555,7 +555,7 @@ splitFVs is_thunk rhs_fvs %* * %************************************************************************ -This domain differst from JointDemand in the sense that pure absence +This domain differs from JointDemand in the sense that pure absence is taken away, i.e., we deal *only* with non-absent demands. Note [Strict demands] @@ -723,17 +723,18 @@ We have lubs, but not glbs; but that is ok. -- Constructed Product Result ------------------------------------------------------------------------ +data DmdResult = Diverges -- Definitely diverges + | Converges CPRResult -- Definitely converges + | Dunno CPRResult -- Might diverge or converge, but in the latter case the + -- result shape is described by CPRResult + deriving( Eq, Show ) + data CPRResult = NoCPR -- Top of the lattice | RetProd [DmdResult] -- Returns a constructor from a product type -- We use RetProd [] to mean RetProd [top,...,top] | RetSum ConTag -- Returns a constructor from a sum type with this tag deriving( Eq, Show ) -data DmdResult = Diverges -- Definitely diverges - | Converges CPRResult -- Definitely converges - | Dunno CPRResult -- Might diverge or converge, but in the latter case the - -- result shape is described by CPRResult - deriving( Eq, Show ) lubCPR :: CPRResult -> CPRResult -> CPRResult lubCPR (RetSum t1) (RetSum t2) diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index c3e813c..0a84550 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -519,27 +519,30 @@ dmdAnalVarApp env dmd fun args , ppr arg_tys, ppr (Converges cpr_info), ppr res_ty]) $ ( res_ty , foldl App (Var fun) args') - - | otherwise - = completeApp env (dmdTransform env fun (mkCallDmdN n_val_args dmd), Var fun) args where n_val_args = valArgCount args cxt_ds = splitProdCleanDmd n_val_args dmd - (arg_tys, args') = anal_args cxt_ds args + (arg_tys, args') = anal_con_args cxt_ds args -- The constructor itself is lazy -- See Note [Data-con worker strictness] in MkId - anal_args :: [Demand] -> [CoreExpr] -> ([DmdType], [CoreExpr]) - anal_args _ [] = ([],[]) - anal_args ds (arg : args) + anal_con_args :: [Demand] -> [CoreExpr] -> ([DmdType], [CoreExpr]) + anal_con_args _ [] = ([],[]) + anal_con_args ds (arg : args) | isTyCoArg arg - , (arg_tys, args') <- anal_args ds args + , (arg_tys, args') <- anal_con_args ds args = (arg_tys, arg:args') - anal_args (d:ds) (arg : args) + anal_con_args (d:ds) (arg : args) | (arg_ty, arg') <- dmdAnalStar env (dmdTransformThunkDmd arg d) arg - , (arg_tys, args') <- anal_args ds args + , (arg_tys, args') <- anal_con_args ds args = (arg_ty:arg_tys, arg':args') - anal_args ds args = pprPanic "anal_args" (ppr args $$ ppr ds) + anal_con_args ds args = pprPanic "anal_con_args" (ppr args $$ ppr ds) + +dmdAnalVarApp env dmd fun args + = --pprTrace "dmdAnalVarApp" (vcat [ ppr fun, ppr args + -- , ppr $ completeApp env (dmdTransform env fun (mkCallDmdN n_val_args dmd), Var fun) args + -- ]) + completeApp env (dmdTransform env fun (mkCallDmdN (valArgCount args) dmd), Var fun) args \end{code} %************************************************************************ From git at git.haskell.org Thu Dec 5 19:00:03 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 5 Dec 2013 19:00:03 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Add a flag -fnested-cpr-off to conveniently test the effect of nested CPR (aead791) Message-ID: <20131205190003.BF8CF2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/aead791edb7ede760575343b61cce5086574a9fa/ghc >--------------------------------------------------------------- commit aead791edb7ede760575343b61cce5086574a9fa Author: Joachim Breitner Date: Wed Dec 4 09:14:26 2013 +0000 Add a flag -fnested-cpr-off to conveniently test the effect of nested CPR >--------------------------------------------------------------- aead791edb7ede760575343b61cce5086574a9fa compiler/basicTypes/Demand.lhs | 29 ++++++++++++++++++++--------- compiler/main/StaticFlags.hs | 9 +++++++-- 2 files changed, 27 insertions(+), 11 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 8a4b5c2..5f140df 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -800,19 +800,29 @@ botRes = Diverges maxCPRDepth :: Int maxCPRDepth = 3 +-- This is the depth we use with -fnested-cpr-off, in order +-- to get precisely the same behaviour as before introduction of nested cpr +-- -fnested-cpr-off can eventually be removed if nested cpr is deemd to be +-- a good thing always. +flatCPRDepth :: Int +flatCPRDepth = 1 + -- With nested CPR, DmdResult can be arbitrarily deep; consider e.g. the -- DmdResult of repeat +-- -- So we need to forget information at a certain depth. We do that at all points -- where we are building RetCon constructors. -cutDmdResult :: Int -> DmdResult -> DmdResult -cutDmdResult 0 _ = topRes -cutDmdResult _ Diverges = Diverges -cutDmdResult n (Converges c) = Converges (cutCPRResult n c) -cutDmdResult n (Dunno c) = Dunno (cutCPRResult n c) - cutCPRResult :: Int -> CPRResult -> CPRResult -cutCPRResult _ NoCPR = NoCPR +cutCPRResult 0 _ = NoCPR +cutCPRResult _ NoCPR = NoCPR cutCPRResult n (RetCon tag rs) = RetCon tag (map (cutDmdResult (n-1)) rs) + where + cutDmdResult :: Int -> DmdResult -> DmdResult + cutDmdResult 0 _ = topRes + cutDmdResult _ Diverges = Diverges + cutDmdResult n (Converges c) = Converges (cutCPRResult n c) + cutDmdResult n (Dunno c) = Dunno (cutCPRResult n c) + -- Forget that something might converge for sure divergeDmdResult :: DmdResult -> DmdResult @@ -827,8 +837,9 @@ forgetCPR (Dunno _) = Dunno NoCPR cprConRes :: ConTag -> [DmdResult] -> CPRResult cprConRes tag arg_ress - | opt_CprOff = NoCPR - | otherwise = cutCPRResult maxCPRDepth $ RetCon tag arg_ress + | opt_CprOff = NoCPR + | opt_NestedCprOff = cutCPRResult flatCPRDepth $ RetCon tag arg_ress + | otherwise = cutCPRResult maxCPRDepth $ RetCon tag arg_ress getDmdResult :: DmdType -> DmdResult getDmdResult (DmdType _ [] r) = r -- Only for data-typed arguments! diff --git a/compiler/main/StaticFlags.hs b/compiler/main/StaticFlags.hs index 01dc3b7..feb7235 100644 --- a/compiler/main/StaticFlags.hs +++ b/compiler/main/StaticFlags.hs @@ -27,6 +27,7 @@ module StaticFlags ( -- optimisation opts opt_NoStateHack, opt_CprOff, + opt_NestedCprOff, opt_NoOptCoercion, -- For the parser @@ -140,7 +141,8 @@ flagsStaticNames :: [String] flagsStaticNames = [ "fno-state-hack", "fno-opt-coercion", - "fcpr-off" + "fcpr-off", + "fnested-cpr-off" ] -- We specifically need to discard static flags for clients of the @@ -195,10 +197,13 @@ opt_NoDebugOutput = lookUp (fsLit "-dno-debug-output") opt_NoStateHack :: Bool opt_NoStateHack = lookUp (fsLit "-fno-state-hack") --- Switch off CPR analysis in the new demand analyser +-- Switch off CPR analysis in the demand analyser opt_CprOff :: Bool opt_CprOff = lookUp (fsLit "-fcpr-off") +opt_NestedCprOff :: Bool +opt_NestedCprOff = lookUp (fsLit "-fnested-cpr-off") + opt_NoOptCoercion :: Bool opt_NoOptCoercion = lookUp (fsLit "-fno-opt-coercion") From git at git.haskell.org Thu Dec 5 19:00:05 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 5 Dec 2013 19:00:05 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Apply IO stricness hack only to information about arguments (4f055ee) Message-ID: <20131205190005.A2FF02406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/4f055ee8d890e23c8ad02a5864d0b6069420bbec/ghc >--------------------------------------------------------------- commit 4f055ee8d890e23c8ad02a5864d0b6069420bbec Author: Joachim Breitner Date: Thu Nov 28 10:29:47 2013 +0000 Apply IO stricness hack only to information about arguments but retain the CPR information in the result. >--------------------------------------------------------------- 4f055ee8d890e23c8ad02a5864d0b6069420bbec compiler/basicTypes/Demand.lhs | 9 ++++++++- compiler/stranal/DmdAnal.lhs | 4 +++- compiler/stranal/WwLib.lhs | 3 ++- 3 files changed, 13 insertions(+), 3 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 5f140df..aee44ba 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -20,7 +20,7 @@ module Demand ( DmdType(..), dmdTypeDepth, lubDmdType, bothDmdType, topDmdType, botDmdType, mkDmdType, mkTopDmdType, - addDemand, + addDemand, dmdTypeArgTop, DmdEnv, emptyDmdEnv, peelFV, @@ -1132,6 +1132,13 @@ splitDmdTy :: DmdType -> (Demand, DmdType) splitDmdTy (DmdType fv (dmd:dmds) res_ty) = (dmd, DmdType fv dmds res_ty) splitDmdTy ty@(DmdType _ [] res_ty) = (resTypeArgDmd res_ty, ty) +-- We want to forget what we know about the arguments, but keep the information +-- of the result, see Note [IO Strictness Hack] +dmdTypeArgTop :: DmdType -> DmdType +dmdTypeArgTop d@(DmdType _ _ res) + = let (DmdType env' ds' res') = d `lubDmdType` topDmdType + in DmdType env' ds' (if opt_NestedCprOff then res' else res) + strictenDmd :: JointDmd -> CleanDemand strictenDmd (JD {strd = s, absd = u}) = CD { sd = poke_s s, ud = poke_u u } diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index 9863610..0d7c8fe 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -310,9 +310,11 @@ dmdAnalAlt env dmd (con,bndrs,rhs) (rhs_ty, rhs') = dmdAnal env dmd rhs rhs_ty' = addDataConPatDmds con bndrs rhs_ty (alt_ty, bndrs') = annotateBndrs env rhs_ty' bndrs - final_alt_ty | io_hack_reqd = alt_ty `lubDmdType` topDmdType + final_alt_ty | io_hack_reqd = dmdTypeArgTop alt_ty | otherwise = alt_ty + -- Note [IO Strictness Hack] + -- -- There's a hack here for I/O operations. Consider -- case foo x s of { (# s, r #) -> y } -- Is this strict in 'y'. Normally yes, but what if 'foo' is an I/O diff --git a/compiler/stranal/WwLib.lhs b/compiler/stranal/WwLib.lhs index 4acf255..7dfff78 100644 --- a/compiler/stranal/WwLib.lhs +++ b/compiler/stranal/WwLib.lhs @@ -32,6 +32,7 @@ import Maybes import Util import Outputable import DynFlags +import StaticFlags ( opt_NestedCprOff ) import FastString \end{code} @@ -503,7 +504,7 @@ deepSplitCprType_maybe :: ConTag -> Type -> Maybe (DataCon, [Type], [Type], Coer deepSplitCprType_maybe con_tag ty | let (co, ty1) = topNormaliseNewType_maybe ty `orElse` (mkReflCo Representational ty, ty) , Just (tc, tc_args) <- splitTyConApp_maybe ty1 - , isDataTyCon tc + , isDataTyCon tc || (not opt_NestedCprOff && isUnboxedTupleTyCon tc) , let cons = tyConDataCons tc con = ASSERT( cons `lengthAtLeast` con_tag ) cons !! (con_tag - fIRST_TAG) = Just (con, tc_args, dataConInstArgTys con tc_args, co) From git at git.haskell.org Thu Dec 5 19:00:07 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 5 Dec 2013 19:00:07 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Use isTypeArg instead of isTyCoArg (forgot why) (38a35e4) Message-ID: <20131205190007.CFB0C2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/38a35e419ddf54b0ba17b69d382550efc17a151f/ghc >--------------------------------------------------------------- commit 38a35e419ddf54b0ba17b69d382550efc17a151f Author: Joachim Breitner Date: Thu Dec 5 16:14:07 2013 +0000 Use isTypeArg instead of isTyCoArg (forgot why) >--------------------------------------------------------------- 38a35e419ddf54b0ba17b69d382550efc17a151f compiler/stranal/DmdAnal.lhs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index ae99609..ba015bf 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -498,7 +498,7 @@ completeApp :: AnalEnv completeApp _ fun_ty_fun [] = fun_ty_fun completeApp env (fun_ty, fun') (arg:args) - | isTyCoArg arg = completeApp env (fun_ty, App fun' arg) args + | isTypeArg arg = completeApp env (fun_ty, App fun' arg) args | otherwise = completeApp env (res_ty `bothDmdType` arg_ty, App fun' arg') args where (arg_dmd, res_ty) = splitDmdTy fun_ty From git at git.haskell.org Thu Dec 5 19:00:09 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 5 Dec 2013 19:00:09 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Recover [CPR for sum types] (slightly differently) (7279cbc) Message-ID: <20131205190009.E365E2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/7279cbc4869fcf179863694b4edb65b19e4c7d5b/ghc >--------------------------------------------------------------- commit 7279cbc4869fcf179863694b4edb65b19e4c7d5b Author: Joachim Breitner Date: Thu Nov 28 11:17:16 2013 +0000 Recover [CPR for sum types] (slightly differently) >--------------------------------------------------------------- 7279cbc4869fcf179863694b4edb65b19e4c7d5b compiler/basicTypes/Demand.lhs | 24 +++++++++--------------- compiler/stranal/DmdAnal.lhs | 14 ++++++++------ 2 files changed, 17 insertions(+), 21 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 66ea620..9811882 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -29,7 +29,8 @@ module Demand ( isBotRes, isTopRes, resTypeArgDmd, topRes, botRes, cprConRes, vanillaCprConRes, appIsBottom, isBottomingSig, pprIfaceStrictSig, - trimCPRInfo, returnsCPR, returnsCPR_maybe, + returnsCPR, returnsCPR_maybe, + forgetCPR, StrictSig(..), mkStrictSig, topSig, botSig, cprProdSig, isTopSig, splitStrictSig, increaseStrictSigArity, @@ -817,6 +818,13 @@ cutCPRResult :: Int -> CPRResult -> CPRResult cutCPRResult _ NoCPR = NoCPR cutCPRResult n (RetCon tag rs) = RetCon tag (map (cutDmdResult (n-1)) rs) +-- Forget the CPR information, but remember if it converges or diverges +-- Used for non-strict thunks and non-top-level things with sum type +forgetCPR :: DmdResult -> DmdResult +forgetCPR Diverges = Diverges +forgetCPR (Converges _) = Converges NoCPR +forgetCPR (Dunno _) = Dunno NoCPR + cprConRes :: ConTag -> [DmdType] -> CPRResult cprConRes tag arg_tys | opt_CprOff = NoCPR @@ -839,20 +847,6 @@ isBotRes :: DmdResult -> Bool isBotRes Diverges = True isBotRes _ = False --- TODO: This currently ignores trim_sums. Evaluate if still required, and fix --- Note [CPR for sum types] -trimCPRInfo :: Bool -> Bool -> DmdResult -> DmdResult -trimCPRInfo trim_all _trim_sums res - = trimR res - where - trimR (Converges c) = Converges (trimC c) - trimR (Dunno c) = Dunno (trimC c) - trimR Diverges = Diverges - - trimC (RetCon n rs) | trim_all = NoCPR - | otherwise = RetCon n (map trimR rs) - trimC NoCPR = NoCPR - returnsCPR :: DmdResult -> Bool returnsCPR dr = isJust (returnsCPR_maybe dr) diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index ba015bf..9239a64 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -643,9 +643,10 @@ dmdAnalRhs top_lvl rec_flag env id rhs -- See Note [NOINLINE and strictness] -- See Note [Product demands for function body] - body_dmd = case deepSplitProductType_maybe (exprType body) of - Nothing -> cleanEvalDmd - Just (dc, _, _, _) -> cleanEvalProdDmd (dataConRepArity dc) + (is_sum_type, body_dmd) + = case deepSplitProductType_maybe (exprType body) of + Nothing -> (True, cleanEvalDmd) + Just (dc, _, _, _) -> (False, cleanEvalProdDmd (dataConRepArity dc)) -- See Note [Lazy and unleashable free variables] -- See Note [Aggregated demand for cardinality] @@ -655,9 +656,10 @@ dmdAnalRhs top_lvl rec_flag env id rhs (lazy_fv, sig_fv) = splitFVs is_thunk rhs_fv1 - rhs_res' = trimCPRInfo trim_all trim_sums rhs_res - trim_all = is_thunk && not_strict - trim_sums = not (isTopLevel top_lvl) -- See Note [CPR for sum types] + -- Note [CPR for sum types] + rhs_res' | (is_sum_type && not (isTopLevel top_lvl)) || + (is_thunk && not_strict) = forgetCPR rhs_res + | otherwise = rhs_res -- See Note [CPR for thunks] is_thunk = not (exprIsHNF rhs) From git at git.haskell.org Thu Dec 5 19:00:11 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 5 Dec 2013 19:00:11 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Improve pprIfaceStrictSig (781e4ca) Message-ID: <20131205190012.146E72406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/781e4cad108ca2e242dbc5686a3a0aeafe3d6c24/ghc >--------------------------------------------------------------- commit 781e4cad108ca2e242dbc5686a3a0aeafe3d6c24 Author: Joachim Breitner Date: Thu Dec 5 11:41:31 2013 +0000 Improve pprIfaceStrictSig >--------------------------------------------------------------- 781e4cad108ca2e242dbc5686a3a0aeafe3d6c24 compiler/basicTypes/Demand.lhs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 5d011e8..29ddc7a 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -1474,7 +1474,9 @@ seqStrictSig (StrictSig ty) = seqDmdType ty -- Used for printing top-level strictness pragmas in interface files pprIfaceStrictSig :: StrictSig -> SDoc pprIfaceStrictSig (StrictSig (DmdType _ dmds res)) - = hcat (map ppr dmds) <> ppr res + = hcat (map ppr dmds) <> ppr_res + where + ppr_res = if isTopRes res then empty else ppr res \end{code} Zap absence or one-shot information, under control of flags From git at git.haskell.org Thu Dec 5 19:00:14 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 5 Dec 2013 19:00:14 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Fix a lubDmdResult equation (dc45272) Message-ID: <20131205190014.2869F2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/dc45272e9cf69a4e75fd96e6e60e6f186740f8ab/ghc >--------------------------------------------------------------- commit dc45272e9cf69a4e75fd96e6e60e6f186740f8ab Author: Joachim Breitner Date: Tue Nov 26 10:17:57 2013 +0000 Fix a lubDmdResult equation >--------------------------------------------------------------- dc45272e9cf69a4e75fd96e6e60e6f186740f8ab compiler/basicTypes/Demand.lhs | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 06ac324..97dc453 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -747,8 +747,10 @@ lubCPR (RetProd ds1) (RetProd ds2) lubCPR _ _ = NoCPR lubDmdResult :: DmdResult -> DmdResult -> DmdResult -lubDmdResult Diverges r = r -lubDmdResult (Converges c1) Diverges = Converges c1 +lubDmdResult Diverges (Dunno c2) = Dunno c2 +lubDmdResult Diverges Diverges = Diverges +lubDmdResult Diverges (Converges c2) = Dunno c2 +lubDmdResult (Converges c1) Diverges = Dunno c1 lubDmdResult (Converges c1) (Converges c2) = Converges (c1 `lubCPR` c2) lubDmdResult (Converges c1) (Dunno c2) = Dunno (c1 `lubCPR` c2) lubDmdResult (Dunno c1) Diverges = Dunno c1 From git at git.haskell.org Thu Dec 5 19:00:16 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 5 Dec 2013 19:00:16 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Use the un-postprocessed DmdResult to build nested CPR (b40ce5f) Message-ID: <20131205190016.2ECE82406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/b40ce5ff1c2009055eeb8cb3695f7cf475f136ed/ghc >--------------------------------------------------------------- commit b40ce5ff1c2009055eeb8cb3695f7cf475f136ed Author: Joachim Breitner Date: Wed Dec 4 16:29:35 2013 +0000 Use the un-postprocessed DmdResult to build nested CPR >--------------------------------------------------------------- b40ce5ff1c2009055eeb8cb3695f7cf475f136ed compiler/basicTypes/Demand.lhs | 16 ++++++++-------- compiler/stranal/DmdAnal.lhs | 33 +++++++++++++++++++-------------- 2 files changed, 27 insertions(+), 22 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 29ddc7a..8a4b5c2 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -26,7 +26,7 @@ module Demand ( peelFV, DmdResult(..), CPRResult(..), - isBotRes, isTopRes, resTypeArgDmd, + isBotRes, isTopRes, getDmdResult, resTypeArgDmd, topRes, botRes, cprConRes, vanillaCprConRes, appIsBottom, isBottomingSig, pprIfaceStrictSig, returnsCPR, returnsCPR_maybe, @@ -825,14 +825,14 @@ forgetCPR Diverges = Diverges forgetCPR (Converges _) = Converges NoCPR forgetCPR (Dunno _) = Dunno NoCPR -cprConRes :: ConTag -> [DmdType] -> CPRResult -cprConRes tag arg_tys +cprConRes :: ConTag -> [DmdResult] -> CPRResult +cprConRes tag arg_ress | opt_CprOff = NoCPR - | otherwise = cutCPRResult maxCPRDepth $ RetCon tag (map get_res arg_tys) - where - get_res :: DmdType -> DmdResult - get_res (DmdType _ [] r) = r -- Only for data-typed arguments! - get_res _ = topRes + | otherwise = cutCPRResult maxCPRDepth $ RetCon tag arg_ress + +getDmdResult :: DmdType -> DmdResult +getDmdResult (DmdType _ [] r) = r -- Only for data-typed arguments! +getDmdResult _ = topRes vanillaCprConRes :: ConTag -> Arity -> CPRResult vanillaCprConRes tag arity diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index e0876e0..c493e85 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -110,11 +110,15 @@ dmdTransformThunkDmd e -- See |-* relation in the companion paper dmdAnalStar :: AnalEnv -> Demand -- This one takes a *Demand* - -> CoreExpr -> (DmdType, CoreExpr) + -> CoreExpr + -> (DmdType, DmdResult, CoreExpr) dmdAnalStar env dmd e | (cd, defer_and_use) <- toCleanDmd dmd , (dmd_ty, e') <- dmdAnal env cd e - = (postProcessDmdTypeM defer_and_use dmd_ty, e') + = let dmd_ty' = postProcessDmdTypeM defer_and_use dmd_ty + in -- pprTrace "dmdAnalStar" (vcat [ppr e, ppr dmd, ppr defer_and_use, ppr dmd_ty, ppr dmd_ty']) + -- We also return the unmodified DmdResult, to store it in nested CPR information + (dmd_ty', getDmdResult dmd_ty, e') -- Main Demand Analsysis machinery dmdAnal :: AnalEnv @@ -502,7 +506,7 @@ completeApp env (fun_ty, fun') (arg:args) | otherwise = completeApp env (res_ty `bothDmdType` arg_ty, App fun' arg') args where (arg_dmd, res_ty) = splitDmdTy fun_ty - (arg_ty, arg') = dmdAnalStar env (dmdTransformThunkDmd arg arg_dmd) arg + (arg_ty, _, arg') = dmdAnalStar env (dmdTransformThunkDmd arg arg_dmd) arg ---------------- dmdAnalVarApp :: AnalEnv -> CleanDemand -> Id @@ -511,7 +515,7 @@ dmdAnalVarApp env dmd fun args | Just con <- isDataConWorkId_maybe fun -- Data constructor , isVanillaDataCon con , n_val_args == dataConRepArity con -- Saturated - , let cpr_info = Converges (cprConRes (dataConTag con) arg_tys) + , let cpr_info = Converges (cprConRes (dataConTag con) arg_rets) res_ty = foldl bothDmdType (DmdType emptyDmdEnv [] cpr_info) arg_tys = -- pprTrace "dmdAnalVarApp" (vcat [ ppr con, ppr args, ppr n_val_args, ppr cxt_ds -- , ppr arg_tys, ppr (Converges cpr_info), ppr res_ty]) $ @@ -520,20 +524,21 @@ dmdAnalVarApp env dmd fun args where n_val_args = valArgCount args cxt_ds = splitProdCleanDmd n_val_args dmd - (arg_tys, args') = anal_con_args cxt_ds args + + (arg_tys, arg_rets, args') = anal_con_args cxt_ds args -- The constructor itself is lazy -- See Note [Data-con worker strictness] in MkId - anal_con_args :: [Demand] -> [CoreExpr] -> ([DmdType], [CoreExpr]) - anal_con_args _ [] = ([],[]) + anal_con_args :: [Demand] -> [CoreExpr] -> ([DmdType], [DmdResult], [CoreExpr]) + anal_con_args _ [] = ([],[],[]) anal_con_args ds (arg : args) - | isTyCoArg arg - , (arg_tys, args') <- anal_con_args ds args - = (arg_tys, arg:args') + | isTypeArg arg + , (arg_tys, arg_rets, args') <- anal_con_args ds args + = (arg_tys, arg_rets, arg:args') anal_con_args (d:ds) (arg : args) - | (arg_ty, arg') <- dmdAnalStar env (dmdTransformThunkDmd arg d) arg - , (arg_tys, args') <- anal_con_args ds args - = (arg_ty:arg_tys, arg':args') + | (arg_ty, arg_ret, arg') <- dmdAnalStar env (dmdTransformThunkDmd arg d) arg + , (arg_tys, arg_rets, args') <- anal_con_args ds args + = (arg_ty:arg_tys, arg_ret:arg_rets, arg':args') anal_con_args ds args = pprPanic "anal_con_args" (ppr args $$ ppr ds) dmdAnalVarApp env dmd fun args @@ -813,7 +818,7 @@ annotateLamIdBndr env arg_of_dfun dmd_ty one_shot id Nothing -> main_ty Just unf -> main_ty `bothDmdType` unf_ty where - (unf_ty, _) = dmdAnalStar env dmd unf + (unf_ty, _, _) = dmdAnalStar env dmd unf main_ty = addDemand dmd dmd_ty' (dmd_ty', dmd) = peelFV dmd_ty id From git at git.haskell.org Thu Dec 5 19:00:18 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 5 Dec 2013 19:00:18 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Unify RetProd and RetSum to RetCon in CPRResult (be941af) Message-ID: <20131205190021.ACF042406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/be941afec4ad209f16cbf83ef0a620a2b5254b5e/ghc >--------------------------------------------------------------- commit be941afec4ad209f16cbf83ef0a620a2b5254b5e Author: Joachim Breitner Date: Thu Dec 5 16:13:41 2013 +0000 Unify RetProd and RetSum to RetCon in CPRResult >--------------------------------------------------------------- be941afec4ad209f16cbf83ef0a620a2b5254b5e compiler/basicTypes/Demand.lhs | 99 ++++++++++++++++++++++------------------ compiler/basicTypes/MkId.lhs | 4 +- compiler/stranal/DmdAnal.lhs | 10 ++-- 3 files changed, 60 insertions(+), 53 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 be941afec4ad209f16cbf83ef0a620a2b5254b5e From git at git.haskell.org Thu Dec 5 19:00:20 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 5 Dec 2013 19:00:20 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Check mAX_CPR_SIZE in dmdAnalVarApp (1e5c120) Message-ID: <20131205190021.B310124069@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/1e5c1203c82b061ef85849adcd399bff25b05a67/ghc >--------------------------------------------------------------- commit 1e5c1203c82b061ef85849adcd399bff25b05a67 Author: Joachim Breitner Date: Thu Dec 5 18:01:34 2013 +0000 Check mAX_CPR_SIZE in dmdAnalVarApp >--------------------------------------------------------------- 1e5c1203c82b061ef85849adcd399bff25b05a67 compiler/stranal/DmdAnal.lhs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index c493e85..9863610 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -515,6 +515,8 @@ dmdAnalVarApp env dmd fun args | Just con <- isDataConWorkId_maybe fun -- Data constructor , isVanillaDataCon con , n_val_args == dataConRepArity con -- Saturated + , dataConRepArity con > 0 + , dataConRepArity con < 10 -- TODO: Sync with mAX_CPR_SIZE in MkId , let cpr_info = Converges (cprConRes (dataConTag con) arg_rets) res_ty = foldl bothDmdType (DmdType emptyDmdEnv [] cpr_info) arg_tys = -- pprTrace "dmdAnalVarApp" (vcat [ ppr con, ppr args, ppr n_val_args, ppr cxt_ds From git at git.haskell.org Thu Dec 5 19:00:22 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 5 Dec 2013 19:00:22 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Loop breakers are not allowed to have a Converges DmdResult (44b6b17) Message-ID: <20131205190022.B2F922406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/44b6b1765251f7dabab2f7da014e043904fdb53d/ghc >--------------------------------------------------------------- commit 44b6b1765251f7dabab2f7da014e043904fdb53d Author: Joachim Breitner Date: Tue Nov 26 10:18:35 2013 +0000 Loop breakers are not allowed to have a Converges DmdResult Conflicts: compiler/basicTypes/Demand.lhs >--------------------------------------------------------------- 44b6b1765251f7dabab2f7da014e043904fdb53d compiler/basicTypes/Demand.lhs | 19 +++++++++++-------- compiler/stranal/DmdAnal.lhs | 5 ++++- 2 files changed, 15 insertions(+), 9 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 9811882..5d011e8 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -33,6 +33,7 @@ module Demand ( forgetCPR, StrictSig(..), mkStrictSig, topSig, botSig, cprProdSig, isTopSig, splitStrictSig, increaseStrictSigArity, + sigMayConverge, seqDemand, seqDemandList, seqDmdType, seqStrictSig, @@ -799,15 +800,10 @@ botRes = Diverges maxCPRDepth :: Int maxCPRDepth = 3 --- With nested CPR, DmdResult can be arbitrarily deep; consider --- data Rec1 = Foo Rec2 Rec2 --- data Rec2 = Bar Rec1 Rec1 --- --- x = Foo y y --- y = Bar x x --- +-- With nested CPR, DmdResult can be arbitrarily deep; consider e.g. the +-- DmdResult of repeat -- So we need to forget information at a certain depth. We do that at all points --- where we are constructing new RetCon constructors. +-- where we are building RetCon constructors. cutDmdResult :: Int -> DmdResult -> DmdResult cutDmdResult 0 _ = topRes cutDmdResult _ Diverges = Diverges @@ -818,6 +814,10 @@ cutCPRResult :: Int -> CPRResult -> CPRResult cutCPRResult _ NoCPR = NoCPR cutCPRResult n (RetCon tag rs) = RetCon tag (map (cutDmdResult (n-1)) rs) +-- Forget that something might converge for sure +divergeDmdResult :: DmdResult -> DmdResult +divergeDmdResult r = r `lubDmdResult` botRes + -- Forget the CPR information, but remember if it converges or diverges -- Used for non-strict thunks and non-top-level things with sum type forgetCPR :: DmdResult -> DmdResult @@ -1348,6 +1348,9 @@ botSig = StrictSig botDmdType cprProdSig :: Arity -> StrictSig cprProdSig arity = StrictSig (cprProdDmdType arity) +sigMayConverge :: StrictSig -> StrictSig +sigMayConverge (StrictSig (DmdType env ds res)) = (StrictSig (DmdType env ds (divergeDmdResult res))) + argsOneShots :: StrictSig -> Arity -> [[OneShotInfo]] argsOneShots (StrictSig (DmdType _ arg_ds _)) n_val_args = go arg_ds diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index 9239a64..e0876e0 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -1072,7 +1072,10 @@ updSigEnv env sigs = env { ae_sigs = sigs } extendAnalEnv :: TopLevelFlag -> AnalEnv -> Id -> StrictSig -> AnalEnv extendAnalEnv top_lvl env var sig - = env { ae_sigs = extendSigEnv top_lvl (ae_sigs env) var sig } + = env { ae_sigs = extendSigEnv top_lvl (ae_sigs env) var sig' } + where + sig' | isWeakLoopBreaker (idOccInfo var) = sigMayConverge sig + | otherwise = sig extendSigEnv :: TopLevelFlag -> SigEnv -> Id -> StrictSig -> SigEnv extendSigEnv top_lvl sigs var sig = extendVarEnv sigs var (sig, top_lvl) From git at git.haskell.org Thu Dec 5 19:00:24 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 5 Dec 2013 19:00:24 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Actually create a nested CPR worker-wrapper (2c24d66) Message-ID: <20131205190024.DB4632406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/2c24d66e34fff92a8f1ef9f321abdd9fb6dac52c/ghc >--------------------------------------------------------------- commit 2c24d66e34fff92a8f1ef9f321abdd9fb6dac52c Author: Joachim Breitner Date: Thu Dec 5 18:58:07 2013 +0000 Actually create a nested CPR worker-wrapper >--------------------------------------------------------------- 2c24d66e34fff92a8f1ef9f321abdd9fb6dac52c compiler/basicTypes/Demand.lhs | 15 ++-- compiler/stranal/WwLib.lhs | 151 ++++++++++++++++++++++++++-------------- 2 files changed, 105 insertions(+), 61 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 2c24d66e34fff92a8f1ef9f321abdd9fb6dac52c From git at git.haskell.org Fri Dec 6 00:07:41 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 6 Dec 2013 00:07:41 +0000 (UTC) Subject: [commit: packages/dph] master: minor wibbles to make examples compile (3e8b135) Message-ID: <20131206000741.87E042406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/dph On branch : master Link : http://git.haskell.org/packages/dph.git/commitdiff/3e8b135e741533a37bacb51c63dcd0fb8af2f912 >--------------------------------------------------------------- commit 3e8b135e741533a37bacb51c63dcd0fb8af2f912 Author: Amos Robinson Date: Tue Nov 26 18:12:38 2013 +1100 minor wibbles to make examples compile >--------------------------------------------------------------- 3e8b135e741533a37bacb51c63dcd0fb8af2f912 dph-event-seer/dph-event-seer.cabal | 1 - dph-examples/examples/spectral/ClosestPairs/dph/Vectorised1.hs | 2 +- dph-examples/examples/spectral/QuickSelect/dph/Vectorised.hs | 2 +- 3 files changed, 2 insertions(+), 3 deletions(-) diff --git a/dph-event-seer/dph-event-seer.cabal b/dph-event-seer/dph-event-seer.cabal index a47fc87..73fdedd 100644 --- a/dph-event-seer/dph-event-seer.cabal +++ b/dph-event-seer/dph-event-seer.cabal @@ -15,7 +15,6 @@ Synopsis: Analyse eventlog files for time spent in garbage collection Executable dph-event-seer Build-depends: base == 4.*, - dph-prim-par == 0.6.*, containers == 0.5.*, ghc-events == 0.4.*, pretty >= 1.1 diff --git a/dph-examples/examples/spectral/ClosestPairs/dph/Vectorised1.hs b/dph-examples/examples/spectral/ClosestPairs/dph/Vectorised1.hs index cd08897..8480003 100644 --- a/dph-examples/examples/spectral/ClosestPairs/dph/Vectorised1.hs +++ b/dph-examples/examples/spectral/ClosestPairs/dph/Vectorised1.hs @@ -114,7 +114,7 @@ closeststupid1PA ps = closeststupid (fromPArrayP ps) median :: [: Double :] -> Double median xs = median' xs (lengthP xs `I.div` 2) -median':: [: Double :] -> Int -> Double +median':: [: Double :] -> P.Int -> Double median' xs k = let p = xs !: (lengthP xs `I.div` 2) ls = [:x | x <- xs, x D.< p:] diff --git a/dph-examples/examples/spectral/QuickSelect/dph/Vectorised.hs b/dph-examples/examples/spectral/QuickSelect/dph/Vectorised.hs index d08103e..00139a3 100644 --- a/dph-examples/examples/spectral/QuickSelect/dph/Vectorised.hs +++ b/dph-examples/examples/spectral/QuickSelect/dph/Vectorised.hs @@ -4,7 +4,7 @@ module Vectorised (quickselectPA) where import Data.Array.Parallel import Data.Array.Parallel.Prelude.Double as D -import qualified Data.Array.Parallel.Prelude.Int as I +import Data.Array.Parallel.Prelude.Int as I import qualified Prelude From git at git.haskell.org Fri Dec 6 00:07:43 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 6 Dec 2013 00:07:43 +0000 (UTC) Subject: [commit: packages/dph] master: dph test driver: add -dynamic to compilation of hs (962c999) Message-ID: <20131206000743.893632406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/dph On branch : master Link : http://git.haskell.org/packages/dph.git/commitdiff/962c99970bb8cfe0d0e712f313db1dda98f7a6bf >--------------------------------------------------------------- commit 962c99970bb8cfe0d0e712f313db1dda98f7a6bf Author: Amos Robinson Date: Fri Nov 29 10:27:50 2013 +1100 dph test driver: add -dynamic to compilation of hs >--------------------------------------------------------------- 962c99970bb8cfe0d0e712f313db1dda98f7a6bf dph-test/framework/DPH/War/Job/Compile.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/dph-test/framework/DPH/War/Job/Compile.hs b/dph-test/framework/DPH/War/Job/Compile.hs index 76c957b..959fd01 100644 --- a/dph-test/framework/DPH/War/Job/Compile.hs +++ b/dph-test/framework/DPH/War/Job/Compile.hs @@ -43,6 +43,7 @@ jobCompile (JobCompile ++ " -Idph-prim-interface/interface" ++ " -Idph-base/include" ++ dph_code_includes + ++ " -dynamic" ++ " -package ghc" ++ " -Odph -fno-liberate-case" ++ " -outputdir " ++ buildDir From git at git.haskell.org Fri Dec 6 04:41:29 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 6 Dec 2013 04:41:29 +0000 (UTC) Subject: [commit: ghc] master: Remove the LFBlackHole constructor (980badd) Message-ID: <20131206044129.247CE2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/980badd133d0e8694bfe2fad7c123da0e51c3250/ghc >--------------------------------------------------------------- commit 980badd133d0e8694bfe2fad7c123da0e51c3250 Author: Patrick Palka Date: Thu Dec 5 11:19:25 2013 -0500 Remove the LFBlackHole constructor After commit 55c703b8fdb0, this code is no longer used anywhere. >--------------------------------------------------------------- 980badd133d0e8694bfe2fad7c123da0e51c3250 compiler/codeGen/StgCmmClosure.hs | 27 --------------------------- 1 file changed, 27 deletions(-) diff --git a/compiler/codeGen/StgCmmClosure.hs b/compiler/codeGen/StgCmmClosure.hs index 037ba97..af9c7b8 100644 --- a/compiler/codeGen/StgCmmClosure.hs +++ b/compiler/codeGen/StgCmmClosure.hs @@ -23,7 +23,6 @@ module StgCmmClosure ( StandardFormInfo, -- ...ditto... mkLFThunk, mkLFReEntrant, mkConLFInfo, mkSelectorLFInfo, mkApLFInfo, mkLFImported, mkLFArgument, mkLFLetNoEscape, - mkLFBlackHole, lfDynTag, maybeIsLFCon, isLFThunk, isLFReEntrant, lfUpdatable, @@ -180,13 +179,6 @@ data LambdaFormInfo | LFLetNoEscape -- See LetNoEscape module for precise description - | LFBlackHole -- Used for the closures allocated to hold the result - -- of a CAF. We want the target of the update frame to - -- be in the heap, so we make a black hole to hold it. - - -- XXX we can very nearly get rid of this, but - -- allocDynClosure needs a LambdaFormInfo - ------------------------- -- StandardFormInfo tells whether this thunk has one of @@ -294,10 +286,6 @@ mkLFImported id where arity = idRepArity id ------------- -mkLFBlackHole :: LambdaFormInfo -mkLFBlackHole = LFBlackHole - ----------------------------------------------------- -- Dynamic pointer tagging ----------------------------------------------------- @@ -361,10 +349,6 @@ maybeIsLFCon _ = Nothing ------------ isLFThunk :: LambdaFormInfo -> Bool isLFThunk (LFThunk {}) = True -isLFThunk LFBlackHole = True - -- return True for a blackhole: this function is used to determine - -- whether to use the thunk header in SMP mode, and a blackhole - -- must have one. isLFThunk _ = False isLFReEntrant :: LambdaFormInfo -> Bool @@ -439,7 +423,6 @@ nodeMustPointToIt _ (LFCon _) = True nodeMustPointToIt _ (LFUnknown _) = True nodeMustPointToIt _ LFUnLifted = False -nodeMustPointToIt _ LFBlackHole = True -- BH entry may require Node to point nodeMustPointToIt _ LFLetNoEscape = False {- Note [GC recovery] @@ -579,11 +562,6 @@ getCallMethod _ name _ (LFUnknown False) n_args _cg_loc _self_loop_info = ASSERT2( n_args == 0, ppr name <+> ppr n_args ) EnterIt -- Not a function -getCallMethod _ _name _ LFBlackHole _n_args _cg_loc _self_loop_info - = SlowCall -- Presumably the black hole has by now - -- been updated, but we don't know with - -- what, so we slow call it - getCallMethod _ _name _ LFLetNoEscape _n_args (LneLoc blk_id lne_regs) _self_loop_info = JumpToIt blk_id lne_regs @@ -787,9 +765,6 @@ closureUpdReqd ClosureInfo{ closureLFInfo = lf_info } = lfUpdatable lf_info lfUpdatable :: LambdaFormInfo -> Bool lfUpdatable (LFThunk _ _ upd _ _) = upd -lfUpdatable LFBlackHole = True - -- Black-hole closures are allocated to receive the results of an - -- alg case with a named default... so they need to be updated. lfUpdatable _ = False closureSingleEntry :: ClosureInfo -> Bool @@ -836,8 +811,6 @@ closureLocalEntryLabel dflags mkClosureInfoTableLabel :: Id -> LambdaFormInfo -> CLabel mkClosureInfoTableLabel id lf_info = case lf_info of - LFBlackHole -> mkCAFBlackHoleInfoTableLabel - LFThunk _ _ upd_flag (SelectorThunk offset) _ -> mkSelectorInfoLabel upd_flag offset From git at git.haskell.org Fri Dec 6 17:01:25 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 6 Dec 2013 17:01:25 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Revert "Apply IO stricness hack only to information about arguments" (02557dd) Message-ID: <20131206170125.C94152406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/02557dd0457eebc23877d1816b04d7714d28c0e8/ghc >--------------------------------------------------------------- commit 02557dd0457eebc23877d1816b04d7714d28c0e8 Author: Joachim Breitner Date: Fri Dec 6 10:55:43 2013 +0000 Revert "Apply IO stricness hack only to information about arguments" This reverts commit 4f055ee8d890e23c8ad02a5864d0b6069420bbec. We need a discussion about this in #8598 first, and I do not want this to influence my nested CPR nofib results. >--------------------------------------------------------------- 02557dd0457eebc23877d1816b04d7714d28c0e8 compiler/basicTypes/Demand.lhs | 9 +-------- compiler/stranal/DmdAnal.lhs | 4 +--- compiler/stranal/WwLib.lhs | 3 +-- 3 files changed, 3 insertions(+), 13 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index aee44ba..5f140df 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -20,7 +20,7 @@ module Demand ( DmdType(..), dmdTypeDepth, lubDmdType, bothDmdType, topDmdType, botDmdType, mkDmdType, mkTopDmdType, - addDemand, dmdTypeArgTop, + addDemand, DmdEnv, emptyDmdEnv, peelFV, @@ -1132,13 +1132,6 @@ splitDmdTy :: DmdType -> (Demand, DmdType) splitDmdTy (DmdType fv (dmd:dmds) res_ty) = (dmd, DmdType fv dmds res_ty) splitDmdTy ty@(DmdType _ [] res_ty) = (resTypeArgDmd res_ty, ty) --- We want to forget what we know about the arguments, but keep the information --- of the result, see Note [IO Strictness Hack] -dmdTypeArgTop :: DmdType -> DmdType -dmdTypeArgTop d@(DmdType _ _ res) - = let (DmdType env' ds' res') = d `lubDmdType` topDmdType - in DmdType env' ds' (if opt_NestedCprOff then res' else res) - strictenDmd :: JointDmd -> CleanDemand strictenDmd (JD {strd = s, absd = u}) = CD { sd = poke_s s, ud = poke_u u } diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index 0d7c8fe..9863610 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -310,11 +310,9 @@ dmdAnalAlt env dmd (con,bndrs,rhs) (rhs_ty, rhs') = dmdAnal env dmd rhs rhs_ty' = addDataConPatDmds con bndrs rhs_ty (alt_ty, bndrs') = annotateBndrs env rhs_ty' bndrs - final_alt_ty | io_hack_reqd = dmdTypeArgTop alt_ty + final_alt_ty | io_hack_reqd = alt_ty `lubDmdType` topDmdType | otherwise = alt_ty - -- Note [IO Strictness Hack] - -- -- There's a hack here for I/O operations. Consider -- case foo x s of { (# s, r #) -> y } -- Is this strict in 'y'. Normally yes, but what if 'foo' is an I/O diff --git a/compiler/stranal/WwLib.lhs b/compiler/stranal/WwLib.lhs index 7dfff78..4acf255 100644 --- a/compiler/stranal/WwLib.lhs +++ b/compiler/stranal/WwLib.lhs @@ -32,7 +32,6 @@ import Maybes import Util import Outputable import DynFlags -import StaticFlags ( opt_NestedCprOff ) import FastString \end{code} @@ -504,7 +503,7 @@ deepSplitCprType_maybe :: ConTag -> Type -> Maybe (DataCon, [Type], [Type], Coer deepSplitCprType_maybe con_tag ty | let (co, ty1) = topNormaliseNewType_maybe ty `orElse` (mkReflCo Representational ty, ty) , Just (tc, tc_args) <- splitTyConApp_maybe ty1 - , isDataTyCon tc || (not opt_NestedCprOff && isUnboxedTupleTyCon tc) + , isDataTyCon tc , let cons = tyConDataCons tc con = ASSERT( cons `lengthAtLeast` con_tag ) cons !! (con_tag - fIRST_TAG) = Just (con, tc_args, dataConInstArgTys con tc_args, co) From git at git.haskell.org Fri Dec 6 17:01:27 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 6 Dec 2013 17:01:27 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: In deferType, return convRes = Converges NoCPR (19eece6) Message-ID: <20131206170128.965072406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/19eece6d7d76f281b0b1686ad56136bb86d59a3f/ghc >--------------------------------------------------------------- commit 19eece6d7d76f281b0b1686ad56136bb86d59a3f Author: Joachim Breitner Date: Wed Dec 4 16:55:18 2013 +0000 In deferType, return convRes = Converges NoCPR because this is the right-identity to `bothDmdResult`, and this is the right thing to do in a lazy context. >--------------------------------------------------------------- 19eece6d7d76f281b0b1686ad56136bb86d59a3f compiler/basicTypes/Demand.lhs | 9 ++++++--- 1 file changed, 6 insertions(+), 3 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 5f140df..092a950 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -793,8 +793,9 @@ seqCPRResult (RetCon n rs) = n `seq` seqListWith seqDmdResult rs -- [cprRes] lets us switch off CPR analysis -- by making sure that everything uses TopRes -topRes, botRes :: DmdResult +topRes, convRes, botRes :: DmdResult topRes = Dunno NoCPR +convRes = Converges NoCPR botRes = Diverges maxCPRDepth :: Int @@ -1173,10 +1174,12 @@ postProcessDmdType (False, Many) ty = useType ty postProcessDmdType (True, One) ty = deferType ty postProcessDmdType (False, One) ty = ty +-- If we use something lazily, we want to ignore any possible divergence +-- (Otherwise we'd lose the termination information of constructors in in dmdAnalVarApp deferType, useType, deferAndUse :: DmdType -> DmdType -deferType (DmdType fv ds _) = DmdType (deferEnv fv) (map deferDmd ds) topRes +deferType (DmdType fv ds _) = DmdType (deferEnv fv) (map deferDmd ds) convRes useType (DmdType fv ds res_ty) = DmdType (useEnv fv) (map useDmd ds) res_ty -deferAndUse (DmdType fv ds _) = DmdType (deferUseEnv fv) (map deferUseDmd ds) topRes +deferAndUse (DmdType fv ds _) = DmdType (deferUseEnv fv) (map deferUseDmd ds) convRes deferEnv, useEnv, deferUseEnv :: DmdEnv -> DmdEnv deferEnv fv = mapVarEnv deferDmd fv From git at git.haskell.org Fri Dec 6 17:01:29 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 6 Dec 2013 17:01:29 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Actually create a nested CPR worker-wrapper (81b3b12) Message-ID: <20131206170130.00BA82406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/81b3b12b104f63a057dcd2aa2a69cdd2a5220315/ghc >--------------------------------------------------------------- commit 81b3b12b104f63a057dcd2aa2a69cdd2a5220315 Author: Joachim Breitner Date: Thu Dec 5 18:58:07 2013 +0000 Actually create a nested CPR worker-wrapper >--------------------------------------------------------------- 81b3b12b104f63a057dcd2aa2a69cdd2a5220315 compiler/basicTypes/Demand.lhs | 15 +++-- compiler/stranal/WwLib.lhs | 141 +++++++++++++++++++++++++--------------- 2 files changed, 95 insertions(+), 61 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 81b3b12b104f63a057dcd2aa2a69cdd2a5220315 From git at git.haskell.org Fri Dec 6 23:15:16 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 6 Dec 2013 23:15:16 +0000 (UTC) Subject: [commit: ghc] branch 'wip/T8598' created Message-ID: <20131206231516.1AB812406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/T8598 Referencing: a2f7d686fbbcd822a59211b16142d151b99ffa43 From git at git.haskell.org Fri Dec 6 23:15:18 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 6 Dec 2013 23:15:18 +0000 (UTC) Subject: [commit: ghc] wip/T8598: Do not forget CPR information after an IO action (a2f7d68) Message-ID: <20131206231519.2AFDE2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8598 Link : http://ghc.haskell.org/trac/ghc/changeset/a2f7d686fbbcd822a59211b16142d151b99ffa43/ghc >--------------------------------------------------------------- commit a2f7d686fbbcd822a59211b16142d151b99ffa43 Author: Joachim Breitner Date: Fri Dec 6 17:58:29 2013 +0000 Do not forget CPR information after an IO action but do forget about certain divergence, if required. Fixes one part of ticket #8598. >--------------------------------------------------------------- a2f7d686fbbcd822a59211b16142d151b99ffa43 compiler/basicTypes/Demand.lhs | 31 +++++++++++++++++++------------ compiler/stranal/DmdAnal.lhs | 2 +- 2 files changed, 20 insertions(+), 13 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index cd844a1..f03de42 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -19,7 +19,7 @@ module Demand ( peelUseCall, cleanUseDmd_maybe, strictenDmd, bothCleanDmd, DmdType(..), dmdTypeDepth, lubDmdType, bothDmdEnv, bothDmdType, - topDmdType, botDmdType, mkDmdType, mkTopDmdType, + topDmdType, botDmdType, exitDmdType, mkDmdType, mkTopDmdType, DmdEnv, emptyDmdEnv, @@ -715,14 +715,15 @@ splitProdDmd_maybe (JD {strd = s, absd = u}) data CPRResult = NoCPR -- Top of the lattice | RetProd -- Returns a constructor from a product type | RetSum ConTag -- Returns a constructor from a sum type with this tag - | BotCPR -- Returns a constructor with any tag - -- Bottom of the domain + | ExitCPR -- Exits cleanly + | BotCPR -- Diverges deriving( Eq, Show ) lubCPR :: CPRResult -> CPRResult -> CPRResult lubCPR BotCPR r = r -lubCPR RetProd BotCPR = RetProd -lubCPR (RetSum t) BotCPR = RetSum t +lubCPR r BotCPR = r +lubCPR ExitCPR r = r +lubCPR r ExitCPR = r lubCPR (RetSum t1) (RetSum t2) | t1 == t2 = RetSum t1 lubCPR RetProd RetProd = RetProd @@ -730,12 +731,14 @@ lubCPR _ _ = NoCPR bothCPR :: CPRResult -> CPRResult -> CPRResult -- See Note [Asymmetry of 'both' for DmdType and DmdResult] -bothCPR _ BotCPR = BotCPR -- If either diverges, we diverge -bothCPR r _ = r +bothCPR _ BotCPR = BotCPR -- If either diverges, we diverge +bothCPR _ ExitCPR = ExitCPR -- If either exists, we exit +bothCPR r _ = r -- otherwise, the second argument is irrelevant instance Outputable DmdResult where ppr RetProd = char 'm' ppr (RetSum n) = char 'm' <> int n + ppr ExitCPR = char 'e' ppr BotCPR = char 'b' ppr NoCPR = empty -- Keep these distinct from Demand letters @@ -755,8 +758,9 @@ seqDmdResult r = r `seq` () -- [cprRes] lets us switch off CPR analysis -- by making sure that everything uses TopRes -topRes, botRes :: DmdResult +topRes, exitRes, botRes :: DmdResult topRes = NoCPR +exitRes = ExitCPR botRes = BotCPR cprSumRes :: ConTag -> DmdResult @@ -1030,9 +1034,10 @@ instance Outputable DmdType where emptyDmdEnv :: VarEnv Demand emptyDmdEnv = emptyVarEnv -topDmdType, botDmdType :: DmdType -topDmdType = DmdType emptyDmdEnv [] topRes -botDmdType = DmdType emptyDmdEnv [] botRes +topDmdType, exitDmdType, botDmdType :: DmdType +topDmdType = DmdType emptyDmdEnv [] topRes +exitDmdType = DmdType emptyDmdEnv [] exitRes +botDmdType = DmdType emptyDmdEnv [] botRes cprProdDmdType :: DmdType cprProdDmdType = DmdType emptyDmdEnv [] cprProdRes @@ -1583,6 +1588,7 @@ instance Binary CPRResult where put_ bh RetProd = putByte bh 1 put_ bh NoCPR = putByte bh 2 put_ bh BotCPR = putByte bh 3 + put_ bh ExitCPR = putByte bh 4 get bh = do h <- getByte bh @@ -1590,5 +1596,6 @@ instance Binary CPRResult where 0 -> do { n <- get bh; return (RetSum n) } 1 -> return RetProd 2 -> return NoCPR - _ -> return BotCPR + 3 -> return BotCPR + _ -> return ExitCPR \end{code} diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index 99eb7ac..094f74a 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -332,7 +332,7 @@ dmdAnalAlt env dmd (con,bndrs,rhs) (rhs_ty, rhs') = dmdAnal env dmd rhs rhs_ty' = addDataConPatDmds con bndrs rhs_ty (alt_ty, bndrs') = annotateBndrs env rhs_ty' bndrs - final_alt_ty | io_hack_reqd = alt_ty `lubDmdType` topDmdType + final_alt_ty | io_hack_reqd = alt_ty `lubDmdType` exitDmdType | otherwise = alt_ty -- There's a hack here for I/O operations. Consider From git at git.haskell.org Fri Dec 6 23:19:09 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 6 Dec 2013 23:19:09 +0000 (UTC) Subject: [commit: testsuite] wip/nested-cpr: More nested CPR test output (9daeda0) Message-ID: <20131206231909.689BE2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/testsuite On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/9daeda021b359f4c11aed301a177254c6154c3eb/testsuite >--------------------------------------------------------------- commit 9daeda021b359f4c11aed301a177254c6154c3eb Author: Joachim Breitner Date: Fri Dec 6 18:03:53 2013 +0000 More nested CPR test output >--------------------------------------------------------------- 9daeda021b359f4c11aed301a177254c6154c3eb tests/simplCore/should_compile/T3717.stderr | 8 ++++---- tests/simplCore/should_compile/T4908.stderr | 6 +++--- tests/simplCore/should_compile/T4918.stdout | 4 ++-- tests/simplCore/should_compile/spec-inline.stderr | 2 +- tests/stranal/sigs/HyperStrUse.hs | 2 +- 5 files changed, 11 insertions(+), 11 deletions(-) diff --git a/tests/simplCore/should_compile/T3717.stderr b/tests/simplCore/should_compile/T3717.stderr index 58f1349..753d081 100644 --- a/tests/simplCore/should_compile/T3717.stderr +++ b/tests/simplCore/should_compile/T3717.stderr @@ -22,13 +22,13 @@ T3717.foo [InlPrag=INLINE[0]] :: GHC.Types.Int -> GHC.Types.Int ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(unsat_ok=True,boring_ok=False) Tmpl= \ (w [Occ=Once!] :: GHC.Types.Int) -> - case w of _ [Occ=Dead] { GHC.Types.I# ww1 [Occ=Once] -> - case T3717.$wfoo ww1 of ww2 { __DEFAULT -> GHC.Types.I# ww2 } + case w of _ [Occ=Dead] { GHC.Types.I# ww [Occ=Once] -> + case T3717.$wfoo ww of ww1 { __DEFAULT -> GHC.Types.I# ww1 } }}] T3717.foo = \ (w :: GHC.Types.Int) -> - case w of _ [Occ=Dead] { GHC.Types.I# ww1 -> - case T3717.$wfoo ww1 of ww2 { __DEFAULT -> GHC.Types.I# ww2 } + case w of _ [Occ=Dead] { GHC.Types.I# ww -> + case T3717.$wfoo ww of ww1 { __DEFAULT -> GHC.Types.I# ww1 } } diff --git a/tests/simplCore/should_compile/T4908.stderr b/tests/simplCore/should_compile/T4908.stderr index 3acef2f..b1d74d8 100644 --- a/tests/simplCore/should_compile/T4908.stderr +++ b/tests/simplCore/should_compile/T4908.stderr @@ -58,12 +58,12 @@ T4908.f [InlPrag=INLINE[0]] Guidance=ALWAYS_IF(unsat_ok=True,boring_ok=False) Tmpl= \ (w [Occ=Once!] :: GHC.Types.Int) (w1 [Occ=Once] :: (GHC.Types.Int, GHC.Types.Int)) -> - case w of _ [Occ=Dead] { GHC.Types.I# ww1 [Occ=Once] -> - T4908.$wf ww1 w1 + case w of _ [Occ=Dead] { GHC.Types.I# ww [Occ=Once] -> + T4908.$wf ww w1 }}] T4908.f = \ (w :: GHC.Types.Int) (w1 :: (GHC.Types.Int, GHC.Types.Int)) -> - case w of _ [Occ=Dead] { GHC.Types.I# ww1 -> T4908.$wf ww1 w1 } + case w of _ [Occ=Dead] { GHC.Types.I# ww -> T4908.$wf ww w1 } ------ Local rules for imported ids -------- diff --git a/tests/simplCore/should_compile/T4918.stdout b/tests/simplCore/should_compile/T4918.stdout index c79b116..cfffda7 100644 --- a/tests/simplCore/should_compile/T4918.stdout +++ b/tests/simplCore/should_compile/T4918.stdout @@ -1,2 +1,2 @@ - {- HasNoCafRefs, Strictness: m, Unfolding: (GHC.Types.C# 'p') -} - {- HasNoCafRefs, Strictness: m, Unfolding: (GHC.Types.C# 'q') -} + Unfolding: (GHC.Types.C# 'p') -} + Unfolding: (GHC.Types.C# 'q') -} diff --git a/tests/simplCore/should_compile/spec-inline.stderr b/tests/simplCore/should_compile/spec-inline.stderr index f931af3..c0a7b58 100644 --- a/tests/simplCore/should_compile/spec-inline.stderr +++ b/tests/simplCore/should_compile/spec-inline.stderr @@ -122,7 +122,7 @@ Roman.foo2 = GHC.Types.I# 6 Roman.foo1 :: Data.Maybe.Maybe GHC.Types.Int [GblId, Caf=NoCafRefs, - Str=DmdType t, + Str=DmdType tm2(tm1(d)), Unf=Unf{Src=, TopLvl=True, Arity=0, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}] diff --git a/tests/stranal/sigs/HyperStrUse.hs b/tests/stranal/sigs/HyperStrUse.hs index 88ba3e3..6febf3d 100644 --- a/tests/stranal/sigs/HyperStrUse.hs +++ b/tests/stranal/sigs/HyperStrUse.hs @@ -6,4 +6,4 @@ import StrAnalAnnotation (StrAnal(StrAnal)) f :: (Int, Int) -> Bool -> Int f (x,y) True = error (show x) f (x,y) False = x +1 -{-# ANN f (StrAnal "m") #-} +{-# ANN f (StrAnal "dm1(d)") #-} From git at git.haskell.org Mon Dec 9 10:13:30 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 9 Dec 2013 10:13:30 +0000 (UTC) Subject: [commit: testsuite] master: Add testcase for #8598 (7e5c115) Message-ID: <20131209101330.539272406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/testsuite On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7e5c115b88f0bae2e70f5d3fb7512c12a0f5744a/testsuite >--------------------------------------------------------------- commit 7e5c115b88f0bae2e70f5d3fb7512c12a0f5744a Author: Joachim Breitner Date: Mon Dec 9 10:14:00 2013 +0000 Add testcase for #8598 >--------------------------------------------------------------- 7e5c115b88f0bae2e70f5d3fb7512c12a0f5744a tests/stranal/sigs/T8598.hs | 20 ++++++++++++++++++++ tests/stranal/sigs/all.T | 1 + 2 files changed, 21 insertions(+) diff --git a/tests/stranal/sigs/T8598.hs b/tests/stranal/sigs/T8598.hs new file mode 100644 index 0000000..55c1a35 --- /dev/null +++ b/tests/stranal/sigs/T8598.hs @@ -0,0 +1,20 @@ +{-# OPTIONS_GHC -fplugin StrAnalAnnotation #-} +{-# LANGUAGE MagicHash , UnboxedTuples #-} + +module T8598(fun) where + +import GHC.Float (Double(..)) +import GHC.Integer (decodeDoubleInteger, encodeDoubleInteger) +import StrAnalAnnotation (StrAnal(StrAnal)) + +-- Float.scaleFloat for Doubles, slightly simplified +fun :: Double -> Double +fun x | isFix = x + | otherwise = case x of + (D# x#) -> case decodeDoubleInteger x# of + (# i, j #) -> D# (encodeDoubleInteger i j) + where + isFix = isDoubleFinite x == 0 +{-# ANN fun (StrAnal "m") #-} + +foreign import ccall unsafe "isDoubleFinite" isDoubleFinite :: Double -> Int diff --git a/tests/stranal/sigs/all.T b/tests/stranal/sigs/all.T index 4080eb9..aee2ab3 100644 --- a/tests/stranal/sigs/all.T +++ b/tests/stranal/sigs/all.T @@ -18,4 +18,5 @@ test('StrAnalExample', normal, compile, ['--make -package ghc -v0 ' + config.ghc test('T8569', expect_broken(8569), compile, ['--make -package ghc -v0 ' + config.ghc_th_way_flags]) test('HyperStrUse', normal, compile, ['--make -package ghc -v0 ' + config.ghc_th_way_flags]) +test('T8598', expect_broken(8598), compile, ['--make -package ghc -v0 ' + config.ghc_th_way_flags]) From git at git.haskell.org Mon Dec 9 12:31:49 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 9 Dec 2013 12:31:49 +0000 (UTC) Subject: [commit: ghc] master: Fix windows x86_64 build. (8528165) Message-ID: <20131209123149.DCDE12406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8528165d08391f328ac39b7c65f8e1f22fbfd8e8/ghc >--------------------------------------------------------------- commit 8528165d08391f328ac39b7c65f8e1f22fbfd8e8 Author: Austin Seipp Date: Mon Dec 9 06:08:31 2013 -0600 Fix windows x86_64 build. On win64 sizeof(long) != sizeof(void*), so debugTrace was casting a value of incorrect size causing a validate failure. Signed-off-by: Austin Seipp >--------------------------------------------------------------- 8528165d08391f328ac39b7c65f8e1f22fbfd8e8 rts/sm/GC.c | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/rts/sm/GC.c b/rts/sm/GC.c index 8cae2c9..1ecbaf5 100644 --- a/rts/sm/GC.c +++ b/rts/sm/GC.c @@ -1755,7 +1755,7 @@ static void gcCAFs(void) ASSERT(info->type == IND_STATIC); if (p->static_link == NULL) { - debugTrace(DEBUG_gccafs, "CAF gc'd at 0x%04lx", (long)p); + debugTrace(DEBUG_gccafs, "CAF gc'd at 0x%p", p); SET_INFO((StgClosure*)p,&stg_GCD_CAF_info); // stub it if (prev == NULL) { debug_caf_list = (StgIndStatic*)p->saved_info; From git at git.haskell.org Mon Dec 9 12:34:34 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 9 Dec 2013 12:34:34 +0000 (UTC) Subject: [commit: packages/base] master: Properly detect msys2/x64 shell as Windows. (5139ca9) Message-ID: <20131209123434.ECBDC2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/base On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5139ca93e0942f0a5f70c23d73ff1d1fddfdef99/base >--------------------------------------------------------------- commit 5139ca93e0942f0a5f70c23d73ff1d1fddfdef99 Author: Austin Seipp Date: Mon Dec 9 06:32:45 2013 -0600 Properly detect msys2/x64 shell as Windows. Signed-off-by: Austin Seipp >--------------------------------------------------------------- 5139ca93e0942f0a5f70c23d73ff1d1fddfdef99 configure.ac | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/configure.ac b/configure.ac index d84c3cf..06e8a5d 100644 --- a/configure.ac +++ b/configure.ac @@ -16,7 +16,7 @@ AC_PROG_CC() AC_MSG_CHECKING(for WINDOWS platform) case $host in - *mingw32*|*cygwin*) + *mingw32*|*mingw64*|*cygwin*) WINDOWS=YES;; *) WINDOWS=NO;; From git at git.haskell.org Mon Dec 9 14:46:40 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 9 Dec 2013 14:46:40 +0000 (UTC) Subject: [commit: ghc] wip/T8598: Do not forget CPR information after an IO action (f316aed) Message-ID: <20131209144640.B4A4C2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8598 Link : http://ghc.haskell.org/trac/ghc/changeset/f316aed3108782d09bb91763c1e2eeec92228d76/ghc >--------------------------------------------------------------- commit f316aed3108782d09bb91763c1e2eeec92228d76 Author: Joachim Breitner Date: Fri Dec 6 17:58:29 2013 +0000 Do not forget CPR information after an IO action but do forget about certain divergence, if required. Fixes one part of ticket #8598. The added function (deferAfterIO) can maybe be merged with existing code, but given the ongoing work in the nested-cpr branch, I defer that work. >--------------------------------------------------------------- f316aed3108782d09bb91763c1e2eeec92228d76 compiler/basicTypes/Demand.lhs | 19 ++++++++++++++++++- compiler/stranal/DmdAnal.lhs | 2 +- 2 files changed, 19 insertions(+), 2 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index cd844a1..ff6c59f 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -35,7 +35,7 @@ module Demand ( evalDmd, cleanEvalDmd, cleanEvalProdDmd, isStrictDmd, splitDmdTy, splitFVs, - deferDmd, deferType, deferAndUse, deferEnv, modifyEnv, + deferDmd, deferType, deferAndUse, deferAfterIO, deferEnv, modifyEnv, splitProdDmd, splitProdDmd_maybe, peelCallDmd, mkCallDmd, dmdTransformSig, dmdTransformDataConSig, dmdTransformDictSelSig, @@ -1086,6 +1086,23 @@ useType (DmdType fv ds res_ty) = DmdType (useEnv fv) ds res_ty useEnv :: DmdEnv -> DmdEnv useEnv fv = mapVarEnv useDmd fv +-- When e is evaluated after executing an IO action, and d is e's demand, then +-- what of this demand should we consider, given that the IO action can cleanly +-- exit? +-- * We have to kill all strictness demands (i.e. lub with a lazy demand) +-- * We can keep demand information (i.e. lub with an absent deman) +-- * We have to kill definite divergence +-- * We can keep CPR information. +-- See Note [IO hack in the demand analyser] +deferAfterIO :: DmdType -> DmdType +deferAfterIO d@(DmdType _ _ res) = + case d `lubDmdType` topDmdType of + DmdType fv ds _ -> DmdType fv ds (defer_res res) + where + defer_res BotCPR = NoCPR + defer_res r = r + + modifyEnv :: Bool -- No-op if False -> (Demand -> Demand) -- The zapper -> DmdEnv -> DmdEnv -- Env1 and Env2 diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index 99eb7ac..5e0453ca8 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -332,7 +332,7 @@ dmdAnalAlt env dmd (con,bndrs,rhs) (rhs_ty, rhs') = dmdAnal env dmd rhs rhs_ty' = addDataConPatDmds con bndrs rhs_ty (alt_ty, bndrs') = annotateBndrs env rhs_ty' bndrs - final_alt_ty | io_hack_reqd = alt_ty `lubDmdType` topDmdType + final_alt_ty | io_hack_reqd = deferAfterIO alt_ty | otherwise = alt_ty -- There's a hack here for I/O operations. Consider From git at git.haskell.org Mon Dec 9 14:46:42 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 9 Dec 2013 14:46:42 +0000 (UTC) Subject: [commit: ghc] wip/T8598: Rename topDmdType to nopDmdType (972c1d7) Message-ID: <20131209144642.D51E22406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8598 Link : http://ghc.haskell.org/trac/ghc/changeset/972c1d7a6808b5a1c96978ed560dedc8d748c704/ghc >--------------------------------------------------------------- commit 972c1d7a6808b5a1c96978ed560dedc8d748c704 Author: Joachim Breitner Date: Mon Dec 9 14:36:25 2013 +0000 Rename topDmdType to nopDmdType because topDmdType is ''no'' the top of the lattice, as it puts an implicit absent demand on free variables, but Abs is the bottom of the Usage lattice. Why nopDmdType? Becuase it is the demand of doing nothing: Everything lazy, everything absent, no definite divergence. >--------------------------------------------------------------- 972c1d7a6808b5a1c96978ed560dedc8d748c704 compiler/basicTypes/Demand.lhs | 40 ++++++++++++++++++++++------------------ compiler/basicTypes/Id.lhs | 2 +- compiler/basicTypes/IdInfo.lhs | 2 +- compiler/coreSyn/CoreArity.lhs | 2 +- compiler/iface/MkIface.lhs | 2 +- compiler/main/TidyPgm.lhs | 4 ++-- compiler/stranal/DmdAnal.lhs | 10 ++++++---- 7 files changed, 34 insertions(+), 28 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 972c1d7a6808b5a1c96978ed560dedc8d748c704 From git at git.haskell.org Mon Dec 9 14:52:55 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 9 Dec 2013 14:52:55 +0000 (UTC) Subject: [commit: ghc] wip/T8598: Do not forget CPR information after an IO action (5c690b4) Message-ID: <20131209145255.0EEDD2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8598 Link : http://ghc.haskell.org/trac/ghc/changeset/5c690b4de0aea8e9416403bb615c7519f7e2504e/ghc >--------------------------------------------------------------- commit 5c690b4de0aea8e9416403bb615c7519f7e2504e Author: Joachim Breitner Date: Fri Dec 6 17:58:29 2013 +0000 Do not forget CPR information after an IO action but do forget about certain divergence, if required. Fixes one part of ticket #8598. The added function (deferAfterIO) can maybe be merged with existing code, but given the ongoing work in the nested-cpr branch, I defer that work. >--------------------------------------------------------------- 5c690b4de0aea8e9416403bb615c7519f7e2504e compiler/basicTypes/Demand.lhs | 19 ++++++++++++++++++- compiler/stranal/DmdAnal.lhs | 2 +- 2 files changed, 19 insertions(+), 2 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index cd844a1..ff6c59f 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -35,7 +35,7 @@ module Demand ( evalDmd, cleanEvalDmd, cleanEvalProdDmd, isStrictDmd, splitDmdTy, splitFVs, - deferDmd, deferType, deferAndUse, deferEnv, modifyEnv, + deferDmd, deferType, deferAndUse, deferAfterIO, deferEnv, modifyEnv, splitProdDmd, splitProdDmd_maybe, peelCallDmd, mkCallDmd, dmdTransformSig, dmdTransformDataConSig, dmdTransformDictSelSig, @@ -1086,6 +1086,23 @@ useType (DmdType fv ds res_ty) = DmdType (useEnv fv) ds res_ty useEnv :: DmdEnv -> DmdEnv useEnv fv = mapVarEnv useDmd fv +-- When e is evaluated after executing an IO action, and d is e's demand, then +-- what of this demand should we consider, given that the IO action can cleanly +-- exit? +-- * We have to kill all strictness demands (i.e. lub with a lazy demand) +-- * We can keep demand information (i.e. lub with an absent deman) +-- * We have to kill definite divergence +-- * We can keep CPR information. +-- See Note [IO hack in the demand analyser] +deferAfterIO :: DmdType -> DmdType +deferAfterIO d@(DmdType _ _ res) = + case d `lubDmdType` topDmdType of + DmdType fv ds _ -> DmdType fv ds (defer_res res) + where + defer_res BotCPR = NoCPR + defer_res r = r + + modifyEnv :: Bool -- No-op if False -> (Demand -> Demand) -- The zapper -> DmdEnv -> DmdEnv -- Env1 and Env2 diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index 99eb7ac..5e0453ca8 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -332,7 +332,7 @@ dmdAnalAlt env dmd (con,bndrs,rhs) (rhs_ty, rhs') = dmdAnal env dmd rhs rhs_ty' = addDataConPatDmds con bndrs rhs_ty (alt_ty, bndrs') = annotateBndrs env rhs_ty' bndrs - final_alt_ty | io_hack_reqd = alt_ty `lubDmdType` topDmdType + final_alt_ty | io_hack_reqd = deferAfterIO alt_ty | otherwise = alt_ty -- There's a hack here for I/O operations. Consider From git at git.haskell.org Mon Dec 9 14:52:57 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 9 Dec 2013 14:52:57 +0000 (UTC) Subject: [commit: ghc] wip/T8598: Rename topDmdType to nopDmdType (412c483) Message-ID: <20131209145257.4D56E2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8598 Link : http://ghc.haskell.org/trac/ghc/changeset/412c48383d16bcb5db80094a1df05466c7af2c99/ghc >--------------------------------------------------------------- commit 412c48383d16bcb5db80094a1df05466c7af2c99 Author: Joachim Breitner Date: Mon Dec 9 14:36:25 2013 +0000 Rename topDmdType to nopDmdType because topDmdType is ''not'' the top of the lattice, as it puts an implicit absent demand on free variables, but Abs is the bottom of the Usage lattice. Why nopDmdType? Becuase it is the demand of doing nothing: Everything lazy, everything absent, no definite divergence. >--------------------------------------------------------------- 412c48383d16bcb5db80094a1df05466c7af2c99 compiler/basicTypes/Demand.lhs | 40 ++++++++++++++++++++++------------------ compiler/basicTypes/Id.lhs | 2 +- compiler/basicTypes/IdInfo.lhs | 2 +- compiler/coreSyn/CoreArity.lhs | 2 +- compiler/iface/MkIface.lhs | 2 +- compiler/main/TidyPgm.lhs | 4 ++-- compiler/stranal/DmdAnal.lhs | 10 ++++++---- 7 files changed, 34 insertions(+), 28 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 412c48383d16bcb5db80094a1df05466c7af2c99 From git at git.haskell.org Mon Dec 9 14:52:59 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 9 Dec 2013 14:52:59 +0000 (UTC) Subject: [commit: ghc] wip/T8598's head updated: Rename topDmdType to nopDmdType (412c483) Message-ID: <20131209145302.62A3E2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/T8598' now includes: 8528165 Fix windows x86_64 build. 5c690b4 Do not forget CPR information after an IO action 412c483 Rename topDmdType to nopDmdType From git at git.haskell.org Mon Dec 9 15:40:49 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 9 Dec 2013 15:40:49 +0000 (UTC) Subject: [commit: testsuite] master: Use -ddump-strsigs in tests/stranal/sigs (323cab2) Message-ID: <20131209154050.C75382406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/testsuite On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/323cab22d65ea88410a607ef22db23198c03e305/testsuite >--------------------------------------------------------------- commit 323cab22d65ea88410a607ef22db23198c03e305 Author: Joachim Breitner Date: Mon Dec 9 15:40:20 2013 +0000 Use -ddump-strsigs in tests/stranal/sigs because it is more reliable than the previous GHC plugin (no need to support annotations etc.), plus it works nicely with "make accept". >--------------------------------------------------------------- 323cab22d65ea88410a607ef22db23198c03e305 tests/stranal/sigs/HyperStrUse.hs | 4 -- tests/stranal/sigs/HyperStrUse.stderr | 5 +++ tests/stranal/sigs/StrAnalAnnotation.hs | 59 ------------------------------ tests/stranal/sigs/StrAnalExample.hs | 5 --- tests/stranal/sigs/StrAnalExample.stderr | 5 +++ tests/stranal/sigs/T8569.hs | 4 -- tests/stranal/sigs/T8569.stderr | 5 +++ tests/stranal/sigs/T8598.hs | 3 -- tests/stranal/sigs/T8598.stderr | 5 +++ tests/stranal/sigs/all.T | 18 +++------ 10 files changed, 25 insertions(+), 88 deletions(-) diff --git a/tests/stranal/sigs/HyperStrUse.hs b/tests/stranal/sigs/HyperStrUse.hs index 88ba3e3..14bdea4 100644 --- a/tests/stranal/sigs/HyperStrUse.hs +++ b/tests/stranal/sigs/HyperStrUse.hs @@ -1,9 +1,5 @@ -{-# OPTIONS_GHC -fplugin StrAnalAnnotation #-} module HyperStrUse where -import StrAnalAnnotation (StrAnal(StrAnal)) - f :: (Int, Int) -> Bool -> Int f (x,y) True = error (show x) f (x,y) False = x +1 -{-# ANN f (StrAnal "m") #-} diff --git a/tests/stranal/sigs/HyperStrUse.stderr b/tests/stranal/sigs/HyperStrUse.stderr new file mode 100644 index 0000000..1a0ff33 --- /dev/null +++ b/tests/stranal/sigs/HyperStrUse.stderr @@ -0,0 +1,5 @@ + +==================== Strictness signatures ==================== +HyperStrUse.f: m + + diff --git a/tests/stranal/sigs/StrAnalAnnotation.hs b/tests/stranal/sigs/StrAnalAnnotation.hs deleted file mode 100644 index b5bfa75..0000000 --- a/tests/stranal/sigs/StrAnalAnnotation.hs +++ /dev/null @@ -1,59 +0,0 @@ -{-# LANGUAGE DeriveDataTypeable #-} - - --- | This module is not used in GHC. Rather, it is a module that --- can be used to annotate functions with expected result of the demand --- analyzer, and it will print warnings if they do not match. --- This is primarily used for the GHC testsuite, but you can use it in your own --- test suites as well. -module StrAnalAnnotation (plugin, StrAnal(..)) where - -import GhcPlugins -import Demand (StrictSig, pprIfaceStrictSig) - -import Data.Data -import Control.Monad - --- | Use this to annotate your functions -data StrAnal= StrAnal String deriving (Data, Typeable) - -plugin :: Plugin -plugin = defaultPlugin { - installCoreToDos = install - } - -install :: [CommandLineOption] -> [CoreToDo] -> CoreM [CoreToDo] -install _ todo = do - reinitializeGlobals - return (todo ++ [CoreDoPluginPass "Strictness Analzier result test" pass]) - -pass :: ModGuts -> CoreM ModGuts -pass g = mapM_ (printAnn g) (allIds (mg_binds g)) >> return g - -printAnn :: ModGuts -> Id -> CoreM () -printAnn guts b = do - anns <- annotationsOn guts b :: CoreM [StrAnal] - flags <- getDynFlags - mapM_ (report flags b) anns - -report :: DynFlags -> Id -> StrAnal -> CoreM () -report flags id (StrAnal ann) - | sigStr == ann = return () - | otherwise = putMsg $ - hang (text "Mismatch in expected strictness signature:") 4 $ - vcat [ text "name: " <+> ppr id - , text "expected:" <+> text ann - , text "found: " <+> text sigStr - ] - where sig = idStrictness id - sigStr = showSDoc flags (pprIfaceStrictSig (idStrictness id)) - -allIds :: CoreProgram -> [Id] -allIds = concatMap go - where go (NonRec i _) = [i] - go (Rec bs) = map fst bs - -annotationsOn :: Data a => ModGuts -> CoreBndr -> CoreM [a] -annotationsOn guts bndr = do - anns <- getAnnotations deserializeWithData guts - return $ lookupWithDefaultUFM anns [] (varUnique bndr) diff --git a/tests/stranal/sigs/StrAnalExample.hs b/tests/stranal/sigs/StrAnalExample.hs index af9180b..0ac61b9 100644 --- a/tests/stranal/sigs/StrAnalExample.hs +++ b/tests/stranal/sigs/StrAnalExample.hs @@ -1,10 +1,5 @@ -{-# OPTIONS_GHC -fplugin StrAnalAnnotation #-} - -- Just an example on how to create tests that test the strictness analizer module StrAnalExample where -import StrAnalAnnotation (StrAnal(StrAnal)) - foo x = x -{-# ANN foo (StrAnal "") #-} diff --git a/tests/stranal/sigs/StrAnalExample.stderr b/tests/stranal/sigs/StrAnalExample.stderr new file mode 100644 index 0000000..dbe4770 --- /dev/null +++ b/tests/stranal/sigs/StrAnalExample.stderr @@ -0,0 +1,5 @@ + +==================== Strictness signatures ==================== +StrAnalExample.foo: + + diff --git a/tests/stranal/sigs/T8569.hs b/tests/stranal/sigs/T8569.hs index ee6c413..17f7595 100644 --- a/tests/stranal/sigs/T8569.hs +++ b/tests/stranal/sigs/T8569.hs @@ -1,10 +1,7 @@ -{-# OPTIONS_GHC -fplugin StrAnalAnnotation #-} {-# LANGUAGE GADTs #-} module T8569 where -import StrAnalAnnotation (StrAnal(StrAnal)) - data Rep t where Rint :: Rep Int Rdata :: Rep i -> (t -> i) -> Rep t @@ -12,4 +9,3 @@ data Rep t where addUp :: Rep a -> a -> Int addUp Rint n = n addUp (Rdata i f) x = addUp i (f x) -{-# ANN addUp (StrAnal "") #-} diff --git a/tests/stranal/sigs/T8569.stderr b/tests/stranal/sigs/T8569.stderr new file mode 100644 index 0000000..d33935e --- /dev/null +++ b/tests/stranal/sigs/T8569.stderr @@ -0,0 +1,5 @@ + +==================== Strictness signatures ==================== +T8569.addUp: + + diff --git a/tests/stranal/sigs/T8598.hs b/tests/stranal/sigs/T8598.hs index 55c1a35..1e0ca6f 100644 --- a/tests/stranal/sigs/T8598.hs +++ b/tests/stranal/sigs/T8598.hs @@ -1,11 +1,9 @@ -{-# OPTIONS_GHC -fplugin StrAnalAnnotation #-} {-# LANGUAGE MagicHash , UnboxedTuples #-} module T8598(fun) where import GHC.Float (Double(..)) import GHC.Integer (decodeDoubleInteger, encodeDoubleInteger) -import StrAnalAnnotation (StrAnal(StrAnal)) -- Float.scaleFloat for Doubles, slightly simplified fun :: Double -> Double @@ -15,6 +13,5 @@ fun x | isFix = x (# i, j #) -> D# (encodeDoubleInteger i j) where isFix = isDoubleFinite x == 0 -{-# ANN fun (StrAnal "m") #-} foreign import ccall unsafe "isDoubleFinite" isDoubleFinite :: Double -> Int diff --git a/tests/stranal/sigs/T8598.stderr b/tests/stranal/sigs/T8598.stderr new file mode 100644 index 0000000..8de5d31 --- /dev/null +++ b/tests/stranal/sigs/T8598.stderr @@ -0,0 +1,5 @@ + +==================== Strictness signatures ==================== +T8598.fun: m + + diff --git a/tests/stranal/sigs/all.T b/tests/stranal/sigs/all.T index aee2ab3..247a077 100644 --- a/tests/stranal/sigs/all.T +++ b/tests/stranal/sigs/all.T @@ -1,22 +1,14 @@ # This directory contains tests where we annotate functions with expected # type signatures, and verify that these actually those found by the compiler -def f(name, opts): - if (ghc_with_interpreter == 0): - opts.skip = 1 - -setTestOpts(f) -setTestOpts(when(compiler_lt('ghc', '7.1'), skip)) -setTestOpts(extra_clean(['StrAnalAnnotation.hi','StrAnalAnnotation.o'])) +setTestOpts(extra_hc_opts('-ddump-strsigs')) # We are testing the result of an optimization, so no use # running them in various runtimes setTestOpts(only_ways(['optasm'])) -# Use this as a template -test('StrAnalExample', normal, compile, ['--make -package ghc -v0 ' + config.ghc_th_way_flags]) - -test('T8569', expect_broken(8569), compile, ['--make -package ghc -v0 ' + config.ghc_th_way_flags]) -test('HyperStrUse', normal, compile, ['--make -package ghc -v0 ' + config.ghc_th_way_flags]) -test('T8598', expect_broken(8598), compile, ['--make -package ghc -v0 ' + config.ghc_th_way_flags]) +test('StrAnalExample', normal, compile, ['']) +test('T8569', expect_broken(8569), compile, ['']) +test('HyperStrUse', normal, compile, ['']) +test('T8598', expect_broken(8598), compile, ['']) From git at git.haskell.org Mon Dec 9 15:40:59 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 9 Dec 2013 15:40:59 +0000 (UTC) Subject: [commit: ghc] master: New flag: -ddump-strsigs (3f6da56) Message-ID: <20131209154103.572C72406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3f6da561a9d71030efbab20544c4f77f9da0759d/ghc >--------------------------------------------------------------- commit 3f6da561a9d71030efbab20544c4f77f9da0759d Author: Joachim Breitner Date: Mon Dec 9 15:29:21 2013 +0000 New flag: -ddump-strsigs The existing flag -ddump-stranal dumps the full Core, which is very verbose and not always helpful. This adds a more concise output (one line per top-level bind) that is faster to read, and especially more suitable to be used when writing test cases for the strictness analiser. >--------------------------------------------------------------- 3f6da561a9d71030efbab20544c4f77f9da0759d compiler/main/DynFlags.hs | 2 ++ compiler/stranal/DmdAnal.lhs | 12 ++++++++++++ docs/users_guide/debugging.xml | 10 ++++++++++ docs/users_guide/flags.xml | 6 ++++++ 4 files changed, 30 insertions(+) diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index 05a72d6..70d2a81 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -242,6 +242,7 @@ data DumpFlag | Opt_D_dump_prep | Opt_D_dump_stg | Opt_D_dump_stranal + | Opt_D_dump_strsigs | Opt_D_dump_tc | Opt_D_dump_types | Opt_D_dump_rules @@ -2311,6 +2312,7 @@ dynamic_flags = [ , Flag "ddump-prep" (setDumpFlag Opt_D_dump_prep) , Flag "ddump-stg" (setDumpFlag Opt_D_dump_stg) , Flag "ddump-stranal" (setDumpFlag Opt_D_dump_stranal) + , Flag "ddump-strsigs" (setDumpFlag Opt_D_dump_strsigs) , Flag "ddump-tc" (setDumpFlag Opt_D_dump_tc) , Flag "ddump-types" (setDumpFlag Opt_D_dump_types) , Flag "ddump-rules" (setDumpFlag Opt_D_dump_rules) diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index 99eb7ac..0ceb7c9 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -35,6 +35,7 @@ import Util import Maybes ( isJust, orElse ) import TysWiredIn ( unboxedPairDataCon ) import TysPrim ( realWorldStatePrimTy ) +import ErrUtils ( dumpIfSet_dyn ) \end{code} %************************************************************************ @@ -48,6 +49,8 @@ dmdAnalProgram :: DynFlags -> CoreProgram -> IO CoreProgram dmdAnalProgram dflags binds = do { let { binds_plus_dmds = do_prog binds } ; + dumpIfSet_dyn dflags Opt_D_dump_strsigs "Strictness signatures" $ + dumpStrSig binds_plus_dmds ; return binds_plus_dmds } where @@ -1100,6 +1103,15 @@ set_idDemandInfo env id dmd set_idStrictness :: AnalEnv -> Id -> StrictSig -> Id set_idStrictness env id sig = setIdStrictness id (zapStrictSig (ae_dflags env) sig) + +dumpStrSig :: CoreProgram -> SDoc +dumpStrSig binds = vcat (concatMap goBind binds) + where + goBind (NonRec i _) = [ goId i ] + goBind (Rec bs) = map (goId . fst) bs + goId id | isExportedId id = ppr id <> colon <+> pprIfaceStrictSig (idStrictness id) + | otherwise = empty + \end{code} Note [Initial CPR for strict binders] diff --git a/docs/users_guide/debugging.xml b/docs/users_guide/debugging.xml index 003d2b5..5130345 100644 --- a/docs/users_guide/debugging.xml +++ b/docs/users_guide/debugging.xml @@ -202,6 +202,16 @@ + : + + + + strictness signatures + + + + + : diff --git a/docs/users_guide/flags.xml b/docs/users_guide/flags.xml index 72ef91e..2422b9d 100644 --- a/docs/users_guide/flags.xml +++ b/docs/users_guide/flags.xml @@ -2817,6 +2817,12 @@ - + + Dump strictness signatures + dynamic + - + + Dump typechecker output dynamic From git at git.haskell.org Mon Dec 9 16:09:37 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 9 Dec 2013 16:09:37 +0000 (UTC) Subject: [commit: ghc] wip/T8598: Rename topDmdType to nopDmdType (f64cf13) Message-ID: <20131209160937.7255D2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8598 Link : http://ghc.haskell.org/trac/ghc/changeset/f64cf134336820cc98fa45578400d9c9606fa8dc/ghc >--------------------------------------------------------------- commit f64cf134336820cc98fa45578400d9c9606fa8dc Author: Joachim Breitner Date: Mon Dec 9 14:36:25 2013 +0000 Rename topDmdType to nopDmdType because topDmdType is ''not'' the top of the lattice, as it puts an implicit absent demand on free variables, but Abs is the bottom of the Usage lattice. Why nopDmdType? Becuase it is the demand of doing nothing: Everything lazy, everything absent, no definite divergence. >--------------------------------------------------------------- f64cf134336820cc98fa45578400d9c9606fa8dc compiler/basicTypes/Demand.lhs | 40 ++++++++++++++++++++++------------------ compiler/basicTypes/Id.lhs | 2 +- compiler/basicTypes/IdInfo.lhs | 2 +- compiler/coreSyn/CoreArity.lhs | 2 +- compiler/iface/MkIface.lhs | 2 +- compiler/main/TidyPgm.lhs | 4 ++-- compiler/stranal/DmdAnal.lhs | 10 ++++++---- 7 files changed, 34 insertions(+), 28 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 f64cf134336820cc98fa45578400d9c9606fa8dc From git at git.haskell.org Mon Dec 9 16:09:39 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 9 Dec 2013 16:09:39 +0000 (UTC) Subject: [commit: ghc] wip/T8598: Do not forget CPR information after an IO action (a31cb5b) Message-ID: <20131209160941.6084F2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8598 Link : http://ghc.haskell.org/trac/ghc/changeset/a31cb5b07726f5739f6eac35cbb348fcd2d6b598/ghc >--------------------------------------------------------------- commit a31cb5b07726f5739f6eac35cbb348fcd2d6b598 Author: Joachim Breitner Date: Fri Dec 6 17:58:29 2013 +0000 Do not forget CPR information after an IO action but do forget about certain divergence, if required. Fixes one part of ticket #8598. The added function (deferAfterIO) can maybe be merged with existing code, but given the ongoing work in the nested-cpr branch, I defer that work. >--------------------------------------------------------------- a31cb5b07726f5739f6eac35cbb348fcd2d6b598 compiler/basicTypes/Demand.lhs | 19 ++++++++++++++++++- compiler/stranal/DmdAnal.lhs | 2 +- 2 files changed, 19 insertions(+), 2 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index cd844a1..ff6c59f 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -35,7 +35,7 @@ module Demand ( evalDmd, cleanEvalDmd, cleanEvalProdDmd, isStrictDmd, splitDmdTy, splitFVs, - deferDmd, deferType, deferAndUse, deferEnv, modifyEnv, + deferDmd, deferType, deferAndUse, deferAfterIO, deferEnv, modifyEnv, splitProdDmd, splitProdDmd_maybe, peelCallDmd, mkCallDmd, dmdTransformSig, dmdTransformDataConSig, dmdTransformDictSelSig, @@ -1086,6 +1086,23 @@ useType (DmdType fv ds res_ty) = DmdType (useEnv fv) ds res_ty useEnv :: DmdEnv -> DmdEnv useEnv fv = mapVarEnv useDmd fv +-- When e is evaluated after executing an IO action, and d is e's demand, then +-- what of this demand should we consider, given that the IO action can cleanly +-- exit? +-- * We have to kill all strictness demands (i.e. lub with a lazy demand) +-- * We can keep demand information (i.e. lub with an absent deman) +-- * We have to kill definite divergence +-- * We can keep CPR information. +-- See Note [IO hack in the demand analyser] +deferAfterIO :: DmdType -> DmdType +deferAfterIO d@(DmdType _ _ res) = + case d `lubDmdType` topDmdType of + DmdType fv ds _ -> DmdType fv ds (defer_res res) + where + defer_res BotCPR = NoCPR + defer_res r = r + + modifyEnv :: Bool -- No-op if False -> (Demand -> Demand) -- The zapper -> DmdEnv -> DmdEnv -- Env1 and Env2 diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index 0ceb7c9..cadc04c 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -335,7 +335,7 @@ dmdAnalAlt env dmd (con,bndrs,rhs) (rhs_ty, rhs') = dmdAnal env dmd rhs rhs_ty' = addDataConPatDmds con bndrs rhs_ty (alt_ty, bndrs') = annotateBndrs env rhs_ty' bndrs - final_alt_ty | io_hack_reqd = alt_ty `lubDmdType` topDmdType + final_alt_ty | io_hack_reqd = deferAfterIO alt_ty | otherwise = alt_ty -- There's a hack here for I/O operations. Consider From git at git.haskell.org Mon Dec 9 16:09:41 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 9 Dec 2013 16:09:41 +0000 (UTC) Subject: [commit: ghc] wip/T8598: Replace mkTopDmdType by mkClosedStrictSig (3cdf125) Message-ID: <20131209160941.EBA6A2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8598 Link : http://ghc.haskell.org/trac/ghc/changeset/3cdf12512d51454e6eefd1f6ceb9827b9f9976c2/ghc >--------------------------------------------------------------- commit 3cdf12512d51454e6eefd1f6ceb9827b9f9976c2 Author: Joachim Breitner Date: Mon Dec 9 16:09:03 2013 +0000 Replace mkTopDmdType by mkClosedStrictSig because it is not a top deman (see previous commit), and it is only used in an argument to mkStrictSig. >--------------------------------------------------------------- 3cdf12512d51454e6eefd1f6ceb9827b9f9976c2 compiler/basicTypes/Demand.lhs | 10 +++++----- compiler/basicTypes/MkId.lhs | 8 ++++---- compiler/coreSyn/CoreArity.lhs | 2 +- compiler/coreSyn/MkCore.lhs | 4 ++-- compiler/prelude/primops.txt.pp | 10 +++++----- compiler/specialise/SpecConstr.lhs | 2 +- compiler/stranal/WorkWrap.lhs | 6 +++--- 7 files changed, 21 insertions(+), 21 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 3cdf12512d51454e6eefd1f6ceb9827b9f9976c2 From git at git.haskell.org Mon Dec 9 16:09:43 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 9 Dec 2013 16:09:43 +0000 (UTC) Subject: [commit: ghc] wip/T8598's head updated: Replace mkTopDmdType by mkClosedStrictSig (3cdf125) Message-ID: <20131209160944.03AB42406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/T8598' now includes: 3f6da56 New flag: -ddump-strsigs a31cb5b Do not forget CPR information after an IO action f64cf13 Rename topDmdType to nopDmdType 3cdf125 Replace mkTopDmdType by mkClosedStrictSig From git at git.haskell.org Mon Dec 9 16:28:58 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 9 Dec 2013 16:28:58 +0000 (UTC) Subject: [commit: testsuite] master: Mark testcase for #8598 as not broken (def26d4) Message-ID: <20131209162858.1AC672406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/testsuite On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/def26d4335641b967940c56daac552b07b4efa6e/testsuite >--------------------------------------------------------------- commit def26d4335641b967940c56daac552b07b4efa6e Author: Joachim Breitner Date: Mon Dec 9 15:50:00 2013 +0000 Mark testcase for #8598 as not broken >--------------------------------------------------------------- def26d4335641b967940c56daac552b07b4efa6e tests/stranal/sigs/all.T | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/tests/stranal/sigs/all.T b/tests/stranal/sigs/all.T index 247a077..d77cd9e 100644 --- a/tests/stranal/sigs/all.T +++ b/tests/stranal/sigs/all.T @@ -10,5 +10,5 @@ setTestOpts(only_ways(['optasm'])) test('StrAnalExample', normal, compile, ['']) test('T8569', expect_broken(8569), compile, ['']) test('HyperStrUse', normal, compile, ['']) -test('T8598', expect_broken(8598), compile, ['']) +test('T8598', normal, compile, ['']) From git at git.haskell.org Mon Dec 9 16:29:44 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 9 Dec 2013 16:29:44 +0000 (UTC) Subject: [commit: ghc] master's head updated: Replace mkTopDmdType by mkClosedStrictSig (3cdf125) Message-ID: <20131209162944.0DD382406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'master' now includes: a31cb5b Do not forget CPR information after an IO action f64cf13 Rename topDmdType to nopDmdType 3cdf125 Replace mkTopDmdType by mkClosedStrictSig From git at git.haskell.org Mon Dec 9 16:29:56 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 9 Dec 2013 16:29:56 +0000 (UTC) Subject: [commit: ghc] branch 'wip/T8598' deleted Message-ID: <20131209162957.15D7E2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Deleted branch: wip/T8598 From git at git.haskell.org Mon Dec 9 18:44:25 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 9 Dec 2013 18:44:25 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Merge remote-tracking branch 'origin/wip/T8598' into wip/nested-cpr (4f216b0) Message-ID: <20131209184425.43C212406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/4f216b058cadffee5d314fe61114450463772592/ghc >--------------------------------------------------------------- commit 4f216b058cadffee5d314fe61114450463772592 Merge: 81b3b12 3cdf125 Author: Joachim Breitner Date: Mon Dec 9 16:14:41 2013 +0000 Merge remote-tracking branch 'origin/wip/T8598' into wip/nested-cpr Conflicts: compiler/basicTypes/Demand.lhs compiler/basicTypes/MkId.lhs compiler/stranal/WorkWrap.lhs >--------------------------------------------------------------- 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 4f216b058cadffee5d314fe61114450463772592 From git at git.haskell.org Mon Dec 9 18:44:27 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 9 Dec 2013 18:44:27 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Add documentation to plusUFM_CD (5b1eac3) Message-ID: <20131209184427.69A952406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/5b1eac3f16c05209f499ca30a92c4a00cdf9dcec/ghc >--------------------------------------------------------------- commit 5b1eac3f16c05209f499ca30a92c4a00cdf9dcec Author: Joachim Breitner Date: Mon Dec 9 16:46:55 2013 +0000 Add documentation to plusUFM_CD >--------------------------------------------------------------- 5b1eac3f16c05209f499ca30a92c4a00cdf9dcec compiler/utils/UniqFM.lhs | 11 +++++++++++ 1 file changed, 11 insertions(+) diff --git a/compiler/utils/UniqFM.lhs b/compiler/utils/UniqFM.lhs index e74eefc..01acbf3 100644 --- a/compiler/utils/UniqFM.lhs +++ b/compiler/utils/UniqFM.lhs @@ -135,6 +135,13 @@ plusUFM :: UniqFM elt -> UniqFM elt -> UniqFM elt plusUFM_C :: (elt -> elt -> elt) -> UniqFM elt -> UniqFM elt -> UniqFM elt +-- | plusUFM_CD f m1 d1 m2 d2 +-- merges the maps using `f` as the combinding function and d1 resp. d2 as +-- the default value if there is no entry in m1 reps. m2. The domain is the union +-- of the domains of m1 m2. +-- Representative example: +-- > plusUFM_CD f {A: 1, B: 2} 23 {B: 3, C: 4} 42 +-- > == {A: f 1 42, B: f 2 3, C: f 23 4 } plusUFM_CD :: (elt -> elt -> elt) -> UniqFM elt -> elt -> UniqFM elt -> elt -> UniqFM elt @@ -226,7 +233,11 @@ delFromUFM_Directly (UFM m) u = UFM (M.delete (getKey u) m) -- M.union is left-biased, plusUFM should be right-biased. plusUFM (UFM x) (UFM y) = UFM (M.union y x) + -- Note (M.union y x), with arguments flipped + -- M.union is left-biased, plusUFM should be right-biased. + plusUFM_C f (UFM x) (UFM y) = UFM (M.unionWith f x y) + plusUFM_CD f (UFM xm) dx (UFM ym) dy = UFM $ M.mergeWithKey (\_ x y -> Just (x `f` y)) From git at git.haskell.org Mon Dec 9 18:44:29 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 9 Dec 2013 18:44:29 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Do not export DmdResult constructors in Demand.lhs (db0f30e) Message-ID: <20131209184429.98C082406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/db0f30edaea313a6015ce79608b2b9db34e8ab52/ghc >--------------------------------------------------------------- commit db0f30edaea313a6015ce79608b2b9db34e8ab52 Author: Joachim Breitner Date: Mon Dec 9 16:56:32 2013 +0000 Do not export DmdResult constructors in Demand.lhs >--------------------------------------------------------------- db0f30edaea313a6015ce79608b2b9db34e8ab52 compiler/basicTypes/Demand.lhs | 16 ++++++++-------- compiler/basicTypes/MkId.lhs | 2 +- compiler/stranal/DmdAnal.lhs | 6 +++--- 3 files changed, 12 insertions(+), 12 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index fa1cfdc..61c503c 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -25,7 +25,7 @@ module Demand ( DmdEnv, emptyDmdEnv, peelFV, - DmdResult(..), CPRResult(..), + DmdResult, CPRResult(..), isBotRes, isTopRes, getDmdResult, resTypeArgDmd, topRes, botRes, cprConRes, vanillaCprConRes, appIsBottom, isBottomingSig, pprIfaceStrictSig, @@ -837,20 +837,20 @@ forgetCPR Diverges = Diverges forgetCPR (Converges _) = Converges NoCPR forgetCPR (Dunno _) = Dunno NoCPR -cprConRes :: ConTag -> [DmdResult] -> CPRResult +cprConRes :: ConTag -> [DmdResult] -> DmdResult cprConRes tag arg_ress - | opt_CprOff = NoCPR - | opt_NestedCprOff = cutCPRResult flatCPRDepth $ RetCon tag arg_ress - | otherwise = cutCPRResult maxCPRDepth $ RetCon tag arg_ress + | opt_CprOff = topRes + | opt_NestedCprOff = Converges $ cutCPRResult flatCPRDepth $ RetCon tag arg_ress + | otherwise = Converges $ cutCPRResult maxCPRDepth $ RetCon tag arg_ress getDmdResult :: DmdType -> DmdResult getDmdResult (DmdType _ [] r) = r -- Only for data-typed arguments! getDmdResult _ = topRes -vanillaCprConRes :: ConTag -> Arity -> CPRResult +vanillaCprConRes :: ConTag -> Arity -> DmdResult vanillaCprConRes tag arity - | opt_CprOff = NoCPR - | otherwise = cutCPRResult maxCPRDepth $ RetCon tag (replicate arity topRes) + | opt_CprOff = topRes + | otherwise = Converges $ cutCPRResult maxCPRDepth $ RetCon tag (replicate arity topRes) isTopRes :: DmdResult -> Bool isTopRes (Dunno NoCPR) = True diff --git a/compiler/basicTypes/MkId.lhs b/compiler/basicTypes/MkId.lhs index 4dcd3fe..ddb59a9 100644 --- a/compiler/basicTypes/MkId.lhs +++ b/compiler/basicTypes/MkId.lhs @@ -419,7 +419,7 @@ dataConCPR con , isVanillaDataCon con -- No existentials , wkr_arity > 0 , wkr_arity <= mAX_CPR_SIZE - = Converges (vanillaCprConRes (dataConTag con) (dataConRepArity con)) + = vanillaCprConRes (dataConTag con) (dataConRepArity con) | otherwise = topRes where diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index 2aafa79..57c578c 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -522,10 +522,10 @@ dmdAnalVarApp env dmd fun args , n_val_args == dataConRepArity con -- Saturated , dataConRepArity con > 0 , dataConRepArity con < 10 -- TODO: Sync with mAX_CPR_SIZE in MkId - , let cpr_info = Converges (cprConRes (dataConTag con) arg_rets) - res_ty = foldl bothDmdType (DmdType emptyDmdEnv [] cpr_info) arg_tys + , let dmd_res = cprConRes (dataConTag con) arg_rets + res_ty = foldl bothDmdType (DmdType emptyDmdEnv [] dmd_res) arg_tys = -- pprTrace "dmdAnalVarApp" (vcat [ ppr con, ppr args, ppr n_val_args, ppr cxt_ds - -- , ppr arg_tys, ppr (Converges cpr_info), ppr res_ty]) $ + -- , ppr arg_tys, ppr dmd_res, ppr res_ty]) $ ( res_ty , foldl App (Var fun) args') where From git at git.haskell.org Mon Dec 9 18:44:31 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 9 Dec 2013 18:44:31 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Make types of bothDmdType more precise (8c20ef4) Message-ID: <20131209184431.E5AAF2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/8c20ef4f13b16fef39b997bf5a52cdfb9bbe8390/ghc >--------------------------------------------------------------- commit 8c20ef4f13b16fef39b997bf5a52cdfb9bbe8390 Author: Joachim Breitner Date: Mon Dec 9 18:40:09 2013 +0000 Make types of bothDmdType more precise by only passing the demand on the free variables, and whether the argument (resp. scrunitee) may or will diverge. Also make different postProcess code paths for function arguments (which are post-processed just to be both'ed) and unsaturated functions (which are post-processed for other reasons.) Also rename a few functions related to unsaturated function calls (postProcessDmdType to postProcessUnsat, useType to reuseType,...) Also add a note [Demands from unsaturated function calls] that hopefully comprehensively and comprehensibly explains what is going on here. >--------------------------------------------------------------- 8c20ef4f13b16fef39b997bf5a52cdfb9bbe8390 compiler/basicTypes/Demand.lhs | 214 +++++++++++++++++++++++++++------------- compiler/stranal/DmdAnal.lhs | 14 +-- 2 files changed, 150 insertions(+), 78 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 8c20ef4f13b16fef39b997bf5a52cdfb9bbe8390 From git at git.haskell.org Mon Dec 9 18:44:34 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 9 Dec 2013 18:44:34 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr's head updated: Make types of bothDmdType more precise (8c20ef4) Message-ID: <20131209184434.46F8C2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/nested-cpr' now includes: 586bc85 Mask async exceptions in forkM_ d14e5bf Export getHscEnv from HscMain 95ba5d8 More detailed error message when GND fails 356bc56 Fix note reference [WildCard binders] e122154 Comments only b67f503 Improve ASSERT cd03893 Comments only 4f603db Untab ClosureTypes.h and ClosureFlags.c 9d7cbbc Remove code that generates FunDep error message context 55c703b Move the allocation of CAF blackholes into 'newCAF' (#8590) fe68ad5 Update and deduplicate the comments on CAF management (#8590) 95854ca Use new flushExec implementation on all operating systems (#8562) 47024b6 Made ghc -e have a nonzero exit code upon failure (Trac #7962 ) 415f0d6 Refactored by Simon Marlow's suggestion d9ad369 Fix compiler warnings due to integer size mismatch 9d6f111 Comments, and rename a variable 8b642de Typecheck typed TH splices properly (fix Trac #8577) 0f2a20b Suggest TemplateHaskell after encountering a naked top-level expression 1c69305 Clean up Lexer.srcParseErr 1860dae Suggest TemplateHaskell after encountering a parse error on '$' (#7396) 8157a26 Add `.mailmap` file 980badd Remove the LFBlackHole constructor 8528165 Fix windows x86_64 build. 3f6da56 New flag: -ddump-strsigs a31cb5b Do not forget CPR information after an IO action f64cf13 Rename topDmdType to nopDmdType 3cdf125 Replace mkTopDmdType by mkClosedStrictSig 4f216b0 Merge remote-tracking branch 'origin/wip/T8598' into wip/nested-cpr 5b1eac3 Add documentation to plusUFM_CD db0f30e Do not export DmdResult constructors in Demand.lhs 8c20ef4 Make types of bothDmdType more precise From git at git.haskell.org Mon Dec 9 18:44:44 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 9 Dec 2013 18:44:44 +0000 (UTC) Subject: [commit: testsuite] master: Add nested CPR testcase (9f4c591) Message-ID: <20131209184444.09C512406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/testsuite On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9f4c591f6b82bf6f06e844fa60df8289303e6068/testsuite >--------------------------------------------------------------- commit 9f4c591f6b82bf6f06e844fa60df8289303e6068 Author: Joachim Breitner Date: Mon Dec 9 16:35:28 2013 +0000 Add nested CPR testcase >--------------------------------------------------------------- 9f4c591f6b82bf6f06e844fa60df8289303e6068 tests/stranal/sigs/FacState.hs | 6 ++++++ tests/stranal/sigs/{StrAnalExample.stderr => FacState.stderr} | 2 +- tests/stranal/sigs/all.T | 2 +- 3 files changed, 8 insertions(+), 2 deletions(-) diff --git a/tests/stranal/sigs/FacState.hs b/tests/stranal/sigs/FacState.hs new file mode 100644 index 0000000..470bbd9 --- /dev/null +++ b/tests/stranal/sigs/FacState.hs @@ -0,0 +1,6 @@ +module FacState where + + +fac :: Int -> a -> (a, Int) +fac n s | n < 2 = (s,1) + | otherwise = case fac (n-1) s of (s',n') -> let n'' = n*n' in n'' `seq` (s',n'') diff --git a/tests/stranal/sigs/StrAnalExample.stderr b/tests/stranal/sigs/FacState.stderr similarity index 60% copy from tests/stranal/sigs/StrAnalExample.stderr copy to tests/stranal/sigs/FacState.stderr index dbe4770..133ad6e 100644 --- a/tests/stranal/sigs/StrAnalExample.stderr +++ b/tests/stranal/sigs/FacState.stderr @@ -1,5 +1,5 @@ ==================== Strictness signatures ==================== -StrAnalExample.foo: +FacState.fac: dm1(d,tm1(d)) diff --git a/tests/stranal/sigs/all.T b/tests/stranal/sigs/all.T index d77cd9e..ca47b52 100644 --- a/tests/stranal/sigs/all.T +++ b/tests/stranal/sigs/all.T @@ -11,4 +11,4 @@ test('StrAnalExample', normal, compile, ['']) test('T8569', expect_broken(8569), compile, ['']) test('HyperStrUse', normal, compile, ['']) test('T8598', normal, compile, ['']) - +test('FacState', expect_broken(1600), compile, ['']) From git at git.haskell.org Mon Dec 9 18:44:46 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 9 Dec 2013 18:44:46 +0000 (UTC) Subject: [commit: testsuite] master: Demand Analyser testcase: Unsaturated functions (8c5f13e) Message-ID: <20131209184446.695C82406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/testsuite On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8c5f13eb2949d0cd29efaae2882adfc3b9af212a/testsuite >--------------------------------------------------------------- commit 8c5f13eb2949d0cd29efaae2882adfc3b9af212a Author: Joachim Breitner Date: Mon Dec 9 17:45:48 2013 +0000 Demand Analyser testcase: Unsaturated functions >--------------------------------------------------------------- 8c5f13eb2949d0cd29efaae2882adfc3b9af212a tests/stranal/sigs/UnsatFun.hs | 29 +++++++++++++++++++++++++++++ tests/stranal/sigs/UnsatFun.stderr | 9 +++++++++ tests/stranal/sigs/all.T | 1 + 3 files changed, 39 insertions(+) diff --git a/tests/stranal/sigs/UnsatFun.hs b/tests/stranal/sigs/UnsatFun.hs new file mode 100644 index 0000000..23ba642 --- /dev/null +++ b/tests/stranal/sigs/UnsatFun.hs @@ -0,0 +1,29 @@ +module UnsatFun where + +-- Here we test how a partially applied function (f x) +-- with a bottom result affects the strictness signature +-- when used strictly (g) and lazily (g') +-- +-- In both cases, the parameter x should not be absent + +f :: Int -> Int -> Int +f x y = error (show x) +{-# NOINLINE f #-} + +h :: (Int -> Int) -> Int +h f = f 2 +{-# NOINLINE h #-} + +h2 :: Bool -> (Int -> Int) -> Int +h2 True _ = 0 +h2 False f = f 2 +{-# NOINLINE h2 #-} + +-- Should get a bottom result +g :: Int -> Int +g x = let f' = f x + in h f' + +g2 :: Int -> Int +g2 x = let f' = f x + in h2 True f' diff --git a/tests/stranal/sigs/UnsatFun.stderr b/tests/stranal/sigs/UnsatFun.stderr new file mode 100644 index 0000000..3df7ac8 --- /dev/null +++ b/tests/stranal/sigs/UnsatFun.stderr @@ -0,0 +1,9 @@ + +==================== Strictness signatures ==================== +UnsatFun.h: +UnsatFun.h2: +UnsatFun.f: b +UnsatFun.g2: +UnsatFun.g: b + + diff --git a/tests/stranal/sigs/all.T b/tests/stranal/sigs/all.T index ca47b52..3657432 100644 --- a/tests/stranal/sigs/all.T +++ b/tests/stranal/sigs/all.T @@ -12,3 +12,4 @@ test('T8569', expect_broken(8569), compile, ['']) test('HyperStrUse', normal, compile, ['']) test('T8598', normal, compile, ['']) test('FacState', expect_broken(1600), compile, ['']) +test('UnsatFun', normal, compile, ['']) From git at git.haskell.org Mon Dec 9 18:44:53 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 9 Dec 2013 18:44:53 +0000 (UTC) Subject: [commit: testsuite] wip/nested-cpr: Update outputs per “Improve the handling of used-once stuff” (1cfa8d6) Message-ID: <20131209184454.97FA224069@ghc.haskell.org> Repository : ssh://git at git.haskell.org/testsuite On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/1cfa8d6e5c7ae66a14b30edf9a3549527791c329/testsuite >--------------------------------------------------------------- commit 1cfa8d6e5c7ae66a14b30edf9a3549527791c329 Author: Joachim Breitner Date: Tue Dec 3 15:27:28 2013 +0000 Update outputs per ?Improve the handling of used-once stuff? >--------------------------------------------------------------- 1cfa8d6e5c7ae66a14b30edf9a3549527791c329 tests/deSugar/should_compile/T2431.stderr | 2 +- tests/numeric/should_compile/T7116.stdout | 16 ++++++++------ tests/perf/should_run/all.T | 3 ++- tests/simplCore/should_compile/T3717.stderr | 4 ++-- tests/simplCore/should_compile/T3772.stdout | 7 +++--- tests/simplCore/should_compile/T4908.stderr | 10 +++++---- tests/simplCore/should_compile/T4930.stderr | 10 +++++---- tests/simplCore/should_compile/T5366.stdout | 3 +-- tests/simplCore/should_compile/T7360.stderr | 13 +++++++---- tests/simplCore/should_compile/T7865.stdout | 4 ++-- tests/simplCore/should_compile/spec-inline.stderr | 24 ++++++++++----------- tests/stranal/sigs/UnsatFun.stderr | 2 +- 12 files changed, 56 insertions(+), 42 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 1cfa8d6e5c7ae66a14b30edf9a3549527791c329 From git at git.haskell.org Mon Dec 9 18:44:50 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 9 Dec 2013 18:44:50 +0000 (UTC) Subject: [commit: testsuite] wip/nested-cpr: Test output update: Nested CPR signatures (63ae604) Message-ID: <20131209184454.5D8D52406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/testsuite On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/63ae6044cb5692b581cf1a42f934c70139013fc7/testsuite >--------------------------------------------------------------- commit 63ae6044cb5692b581cf1a42f934c70139013fc7 Author: Joachim Breitner Date: Tue Dec 3 17:08:50 2013 +0000 Test output update: Nested CPR signatures >--------------------------------------------------------------- 63ae6044cb5692b581cf1a42f934c70139013fc7 tests/numeric/should_compile/T7116.stdout | 8 ++++---- tests/simplCore/should_compile/T3717.stderr | 10 +++++----- tests/simplCore/should_compile/T4201.stdout | 2 +- tests/simplCore/should_compile/T4908.stderr | 6 +++--- tests/simplCore/should_compile/T4918.stdout | 4 ++-- tests/simplCore/should_compile/T4930.stderr | 2 +- tests/simplCore/should_compile/T7360.stderr | 6 +++--- tests/simplCore/should_compile/spec-inline.stderr | 8 ++++---- tests/stranal/sigs/HyperStrUse.stderr | 2 +- tests/stranal/sigs/T8598.stderr | 2 +- tests/stranal/sigs/all.T | 2 +- 11 files changed, 26 insertions(+), 26 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 63ae6044cb5692b581cf1a42f934c70139013fc7 From git at git.haskell.org Mon Dec 9 18:44:55 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 9 Dec 2013 18:44:55 +0000 (UTC) Subject: [commit: testsuite] wip/nested-cpr's head updated: Test output update: Nested CPR signatures (63ae604) Message-ID: <20131209184455.5AF022406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/testsuite Branch 'wip/nested-cpr' now includes: 20d7273 Update output: More elaborate GND error messages 69f6072 Add new ghc-e/should_fail test suite 0d939eb Different quotes in error messages following lexer clean-up 3e66489 Test Trac #8577 27c42f4 More different quotes in error messages following lexer clean-up 7e5c115 Add testcase for #8598 323cab2 Use -ddump-strsigs in tests/stranal/sigs def26d4 Mark testcase for #8598 as not broken 9f4c591 Add nested CPR testcase 8c5f13e Demand Analyser testcase: Unsaturated functions 1cfa8d6 Update outputs per ?Improve the handling of used-once stuff? 63ae604 Test output update: Nested CPR signatures From git at git.haskell.org Mon Dec 9 20:06:25 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 9 Dec 2013 20:06:25 +0000 (UTC) Subject: [commit: testsuite] master: Sort the output of -dump-strsigs (3144b8f) Message-ID: <20131209200625.736F02406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/testsuite On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3144b8f1e902b1baebd98c7d0aceb5340ce22c9f/testsuite >--------------------------------------------------------------- commit 3144b8f1e902b1baebd98c7d0aceb5340ce22c9f Author: Joachim Breitner Date: Mon Dec 9 20:06:21 2013 +0000 Sort the output of -dump-strsigs >--------------------------------------------------------------- 3144b8f1e902b1baebd98c7d0aceb5340ce22c9f tests/stranal/sigs/UnsatFun.stderr | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/tests/stranal/sigs/UnsatFun.stderr b/tests/stranal/sigs/UnsatFun.stderr index 3df7ac8..646a987 100644 --- a/tests/stranal/sigs/UnsatFun.stderr +++ b/tests/stranal/sigs/UnsatFun.stderr @@ -1,9 +1,9 @@ ==================== Strictness signatures ==================== -UnsatFun.h: -UnsatFun.h2: UnsatFun.f: b -UnsatFun.g2: UnsatFun.g: b +UnsatFun.g2: +UnsatFun.h: +UnsatFun.h2: From git at git.haskell.org Mon Dec 9 20:06:35 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 9 Dec 2013 20:06:35 +0000 (UTC) Subject: [commit: ghc] master: Sort the output of -dump-strsigs (5e0fe05) Message-ID: <20131209200635.A9DEA2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5e0fe058aeaddcfeb437670e470e024f7d90ce7c/ghc >--------------------------------------------------------------- commit 5e0fe058aeaddcfeb437670e470e024f7d90ce7c Author: Joachim Breitner Date: Mon Dec 9 20:05:44 2013 +0000 Sort the output of -dump-strsigs >--------------------------------------------------------------- 5e0fe058aeaddcfeb437670e470e024f7d90ce7c compiler/stranal/DmdAnal.lhs | 13 ++++++++----- 1 file changed, 8 insertions(+), 5 deletions(-) diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index 2b4a6b1..bf88383 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -36,6 +36,8 @@ import Maybes ( isJust, orElse ) import TysWiredIn ( unboxedPairDataCon ) import TysPrim ( realWorldStatePrimTy ) import ErrUtils ( dumpIfSet_dyn ) +import Name ( getName, stableNameCmp ) +import Data.Function ( on ) \end{code} %************************************************************************ @@ -1107,12 +1109,13 @@ set_idStrictness env id sig = setIdStrictness id (zapStrictSig (ae_dflags env) sig) dumpStrSig :: CoreProgram -> SDoc -dumpStrSig binds = vcat (concatMap goBind binds) +dumpStrSig binds = vcat (map printId ids) where - goBind (NonRec i _) = [ goId i ] - goBind (Rec bs) = map (goId . fst) bs - goId id | isExportedId id = ppr id <> colon <+> pprIfaceStrictSig (idStrictness id) - | otherwise = empty + ids = sortBy (stableNameCmp `on` getName) (concatMap getIds binds) + getIds (NonRec i _) = [ i ] + getIds (Rec bs) = map fst bs + printId id | isExportedId id = ppr id <> colon <+> pprIfaceStrictSig (idStrictness id) + | otherwise = empty \end{code} From git at git.haskell.org Tue Dec 10 09:09:35 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 10 Dec 2013 09:09:35 +0000 (UTC) Subject: [commit: ghc] master: Add more .mailmap entries (289ecda) Message-ID: <20131210090935.DF9262406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/289ecda3d4bd3073b37cfdcccce02ad53962ea0d/ghc >--------------------------------------------------------------- commit 289ecda3d4bd3073b37cfdcccce02ad53962ea0d Author: Herbert Valerio Riedel Date: Tue Dec 10 09:31:40 2013 +0100 Add more .mailmap entries Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- 289ecda3d4bd3073b37cfdcccce02ad53962ea0d .mailmap | 60 ++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 60 insertions(+) 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 289ecda3d4bd3073b37cfdcccce02ad53962ea0d From git at git.haskell.org Tue Dec 10 10:09:26 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 10 Dec 2013 10:09:26 +0000 (UTC) Subject: [commit: ghc] wip/T8545: Add check for left-over testsuite/.git folder to sync-all (1be87e5) Message-ID: <20131210100926.14B192406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T8545 Link : http://ghc.haskell.org/trac/ghc/changeset/1be87e5ecca4adc79e0de3bab7130950c83dbb63/ghc >--------------------------------------------------------------- commit 1be87e5ecca4adc79e0de3bab7130950c83dbb63 Author: Herbert Valerio Riedel Date: Tue Dec 10 11:06:03 2013 +0100 Add check for left-over testsuite/.git folder to sync-all This way, the first time sync-all is called after updating to a post-testsuite-merge (see #8545) state of ghc.git, the sync-all script aborts with an error message if a testsuite/.git folder is detected and thus forces the user to take action. Signed-off-by: Herbert Valerio Riedel >--------------------------------------------------------------- 1be87e5ecca4adc79e0de3bab7130950c83dbb63 sync-all | 16 ++++++++++++++++ 1 file changed, 16 insertions(+) diff --git a/sync-all b/sync-all index 3fe0e8c..f88ad2b 100755 --- a/sync-all +++ b/sync-all @@ -933,6 +933,22 @@ BEGIN { checkCurrentBranchIsMaster(); } $initial_working_directory = getcwd(); + + #message "== Checking for left-over testsuite/.git folder"; + if (-d "testsuite/.git") { + print < Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/31da0b116db24d5db5346320382021c3d03af4d3/ghc >--------------------------------------------------------------- commit 31da0b116db24d5db5346320382021c3d03af4d3 Merge: 4f216b0 289ecda Author: Joachim Breitner Date: Tue Dec 10 10:43:12 2013 +0000 Merge remote-tracking branch 'origin/master' into HEAD >--------------------------------------------------------------- 31da0b116db24d5db5346320382021c3d03af4d3 .mailmap | 60 ++++++++++++++++++++++++++++++++++++++++++ compiler/stranal/DmdAnal.lhs | 13 +++++---- 2 files changed, 68 insertions(+), 5 deletions(-) From git at git.haskell.org Tue Dec 10 11:18:55 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 10 Dec 2013 11:18:55 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Make types of bothDmdType more precise (0c44351) Message-ID: <20131210111855.5244A2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/0c44351d905ddaf5d5d96819fc3c8a15cbf478bf/ghc >--------------------------------------------------------------- commit 0c44351d905ddaf5d5d96819fc3c8a15cbf478bf Author: Joachim Breitner Date: Mon Dec 9 18:40:09 2013 +0000 Make types of bothDmdType more precise by only passing the demand on the free variables, and whether the argument (resp. scrunitee) may or will diverge. Also make different postProcess code paths for function arguments (which are post-processed just to be both'ed) and unsaturated functions (which are post-processed for other reasons.) Also rename a few functions related to unsaturated function calls (postProcessDmdType to postProcessUnsat, useType to reuseType,...) Also add a note [Demands from unsaturated function calls] that hopefully comprehensively and comprehensibly explains what is going on here. >--------------------------------------------------------------- 0c44351d905ddaf5d5d96819fc3c8a15cbf478bf compiler/basicTypes/Demand.lhs | 214 +++++++++++++++++++++++++++------------- compiler/stranal/DmdAnal.lhs | 14 +-- 2 files changed, 150 insertions(+), 78 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 0c44351d905ddaf5d5d96819fc3c8a15cbf478bf From git at git.haskell.org Tue Dec 10 11:18:57 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 10 Dec 2013 11:18:57 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Add documentation to plusUFM_CD (9805e2c) Message-ID: <20131210111857.78C3F2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/9805e2c5fd9b40bd364db7601e6e0a47dc05d818/ghc >--------------------------------------------------------------- commit 9805e2c5fd9b40bd364db7601e6e0a47dc05d818 Author: Joachim Breitner Date: Mon Dec 9 16:46:55 2013 +0000 Add documentation to plusUFM_CD >--------------------------------------------------------------- 9805e2c5fd9b40bd364db7601e6e0a47dc05d818 compiler/utils/UniqFM.lhs | 11 +++++++++++ 1 file changed, 11 insertions(+) diff --git a/compiler/utils/UniqFM.lhs b/compiler/utils/UniqFM.lhs index e74eefc..01acbf3 100644 --- a/compiler/utils/UniqFM.lhs +++ b/compiler/utils/UniqFM.lhs @@ -135,6 +135,13 @@ plusUFM :: UniqFM elt -> UniqFM elt -> UniqFM elt plusUFM_C :: (elt -> elt -> elt) -> UniqFM elt -> UniqFM elt -> UniqFM elt +-- | plusUFM_CD f m1 d1 m2 d2 +-- merges the maps using `f` as the combinding function and d1 resp. d2 as +-- the default value if there is no entry in m1 reps. m2. The domain is the union +-- of the domains of m1 m2. +-- Representative example: +-- > plusUFM_CD f {A: 1, B: 2} 23 {B: 3, C: 4} 42 +-- > == {A: f 1 42, B: f 2 3, C: f 23 4 } plusUFM_CD :: (elt -> elt -> elt) -> UniqFM elt -> elt -> UniqFM elt -> elt -> UniqFM elt @@ -226,7 +233,11 @@ delFromUFM_Directly (UFM m) u = UFM (M.delete (getKey u) m) -- M.union is left-biased, plusUFM should be right-biased. plusUFM (UFM x) (UFM y) = UFM (M.union y x) + -- Note (M.union y x), with arguments flipped + -- M.union is left-biased, plusUFM should be right-biased. + plusUFM_C f (UFM x) (UFM y) = UFM (M.unionWith f x y) + plusUFM_CD f (UFM xm) dx (UFM ym) dy = UFM $ M.mergeWithKey (\_ x y -> Just (x `f` y)) From git at git.haskell.org Tue Dec 10 11:18:59 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 10 Dec 2013 11:18:59 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: in Demand.lhs, remember what is a sum type (1167ff4) Message-ID: <20131210111859.E9BE22406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/1167ff44f3f7c8bd088b68966320457bd009cf2b/ghc >--------------------------------------------------------------- commit 1167ff44f3f7c8bd088b68966320457bd009cf2b Author: Joachim Breitner Date: Tue Dec 10 09:15:09 2013 +0000 in Demand.lhs, remember what is a sum type because we want to zap CPR information for sum types not only on the outermost level, but also nested. See Note [CPR for sum types] This comes up in sublist in Listplikefns in nofib?s boyer2. >--------------------------------------------------------------- 1167ff44f3f7c8bd088b68966320457bd009cf2b compiler/basicTypes/DataCon.lhs | 4 +++ compiler/basicTypes/Demand.lhs | 75 ++++++++++++++++++++++++--------------- compiler/basicTypes/MkId.lhs | 2 +- compiler/stranal/DmdAnal.lhs | 37 +++++++++++-------- 4 files changed, 75 insertions(+), 43 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 1167ff44f3f7c8bd088b68966320457bd009cf2b From git at git.haskell.org Tue Dec 10 11:19:02 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 10 Dec 2013 11:19:02 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Do not export DmdResult constructors in Demand.lhs (ed35eb8) Message-ID: <20131210111902.8F5CD2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/ed35eb8d519901bf6186f74ce7f0db87e508a97c/ghc >--------------------------------------------------------------- commit ed35eb8d519901bf6186f74ce7f0db87e508a97c Author: Joachim Breitner Date: Mon Dec 9 16:56:32 2013 +0000 Do not export DmdResult constructors in Demand.lhs >--------------------------------------------------------------- ed35eb8d519901bf6186f74ce7f0db87e508a97c compiler/basicTypes/Demand.lhs | 16 ++++++++-------- compiler/basicTypes/MkId.lhs | 2 +- compiler/stranal/DmdAnal.lhs | 6 +++--- 3 files changed, 12 insertions(+), 12 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index fa1cfdc..61c503c 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -25,7 +25,7 @@ module Demand ( DmdEnv, emptyDmdEnv, peelFV, - DmdResult(..), CPRResult(..), + DmdResult, CPRResult(..), isBotRes, isTopRes, getDmdResult, resTypeArgDmd, topRes, botRes, cprConRes, vanillaCprConRes, appIsBottom, isBottomingSig, pprIfaceStrictSig, @@ -837,20 +837,20 @@ forgetCPR Diverges = Diverges forgetCPR (Converges _) = Converges NoCPR forgetCPR (Dunno _) = Dunno NoCPR -cprConRes :: ConTag -> [DmdResult] -> CPRResult +cprConRes :: ConTag -> [DmdResult] -> DmdResult cprConRes tag arg_ress - | opt_CprOff = NoCPR - | opt_NestedCprOff = cutCPRResult flatCPRDepth $ RetCon tag arg_ress - | otherwise = cutCPRResult maxCPRDepth $ RetCon tag arg_ress + | opt_CprOff = topRes + | opt_NestedCprOff = Converges $ cutCPRResult flatCPRDepth $ RetCon tag arg_ress + | otherwise = Converges $ cutCPRResult maxCPRDepth $ RetCon tag arg_ress getDmdResult :: DmdType -> DmdResult getDmdResult (DmdType _ [] r) = r -- Only for data-typed arguments! getDmdResult _ = topRes -vanillaCprConRes :: ConTag -> Arity -> CPRResult +vanillaCprConRes :: ConTag -> Arity -> DmdResult vanillaCprConRes tag arity - | opt_CprOff = NoCPR - | otherwise = cutCPRResult maxCPRDepth $ RetCon tag (replicate arity topRes) + | opt_CprOff = topRes + | otherwise = Converges $ cutCPRResult maxCPRDepth $ RetCon tag (replicate arity topRes) isTopRes :: DmdResult -> Bool isTopRes (Dunno NoCPR) = True diff --git a/compiler/basicTypes/MkId.lhs b/compiler/basicTypes/MkId.lhs index 4dcd3fe..ddb59a9 100644 --- a/compiler/basicTypes/MkId.lhs +++ b/compiler/basicTypes/MkId.lhs @@ -419,7 +419,7 @@ dataConCPR con , isVanillaDataCon con -- No existentials , wkr_arity > 0 , wkr_arity <= mAX_CPR_SIZE - = Converges (vanillaCprConRes (dataConTag con) (dataConRepArity con)) + = vanillaCprConRes (dataConTag con) (dataConRepArity con) | otherwise = topRes where diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index 712274a..3724f26 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -524,10 +524,10 @@ dmdAnalVarApp env dmd fun args , n_val_args == dataConRepArity con -- Saturated , dataConRepArity con > 0 , dataConRepArity con < 10 -- TODO: Sync with mAX_CPR_SIZE in MkId - , let cpr_info = Converges (cprConRes (dataConTag con) arg_rets) - res_ty = foldl bothDmdType (DmdType emptyDmdEnv [] cpr_info) arg_tys + , let dmd_res = cprConRes (dataConTag con) arg_rets + res_ty = foldl bothDmdType (DmdType emptyDmdEnv [] dmd_res) arg_tys = -- pprTrace "dmdAnalVarApp" (vcat [ ppr con, ppr args, ppr n_val_args, ppr cxt_ds - -- , ppr arg_tys, ppr (Converges cpr_info), ppr res_ty]) $ + -- , ppr arg_tys, ppr dmd_res, ppr res_ty]) $ ( res_ty , foldl App (Var fun) args') where From git at git.haskell.org Tue Dec 10 11:19:04 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 10 Dec 2013 11:19:04 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Temporarily disable nested CPR inside sum types (142eb5a) Message-ID: <20131210111904.E27732406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/142eb5ae1fda84d16b180bf40bbe94d3cc54376c/ghc >--------------------------------------------------------------- commit 142eb5ae1fda84d16b180bf40bbe94d3cc54376c Author: Joachim Breitner Date: Tue Dec 10 10:12:46 2013 +0000 Temporarily disable nested CPR inside sum types >--------------------------------------------------------------- 142eb5ae1fda84d16b180bf40bbe94d3cc54376c compiler/basicTypes/Demand.lhs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 16165a2..dc88692 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -861,7 +861,7 @@ cprConRes isProd tag arg_ress | opt_NestedCprOff = Converges $ cutCPRResult flatCPRDepth $ retCon arg_ress | otherwise = Converges $ cutCPRResult maxCPRDepth $ retCon arg_ress where retCon | isProd = RetProd - | otherwise = RetSum tag + | otherwise = RetSum tag . map (const topRes) getDmdResult :: DmdType -> DmdResult getDmdResult (DmdType _ [] r) = r -- Only for data-typed arguments! From git at git.haskell.org Tue Dec 10 11:19:07 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 10 Dec 2013 11:19:07 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Allow the CPR w/w to take unboxed tuples apart (b2bdc27) Message-ID: <20131210111907.3A9DD2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/b2bdc27bfd21e522b79a32b7c8599c3fe0201ceb/ghc >--------------------------------------------------------------- commit b2bdc27bfd21e522b79a32b7c8599c3fe0201ceb Author: Joachim Breitner Date: Tue Dec 10 11:16:15 2013 +0000 Allow the CPR w/w to take unboxed tuples apart >--------------------------------------------------------------- b2bdc27bfd21e522b79a32b7c8599c3fe0201ceb compiler/stranal/WwLib.lhs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/stranal/WwLib.lhs b/compiler/stranal/WwLib.lhs index ce4112c..5168d8f 100644 --- a/compiler/stranal/WwLib.lhs +++ b/compiler/stranal/WwLib.lhs @@ -502,7 +502,7 @@ deepSplitCprType_maybe :: ConTag -> Type -> Maybe (DataCon, [Type], [Type], Coer deepSplitCprType_maybe con_tag ty | let (co, ty1) = topNormaliseNewType_maybe ty `orElse` (mkReflCo Representational ty, ty) , Just (tc, tc_args) <- splitTyConApp_maybe ty1 - , isDataTyCon tc + , isDataTyCon tc || isUnboxedTupleTyCon tc , let cons = tyConDataCons tc con = ASSERT( cons `lengthAtLeast` con_tag ) cons !! (con_tag - fIRST_TAG) = Just (con, tc_args, dataConInstArgTys con tc_args, co) From git at git.haskell.org Tue Dec 10 11:19:09 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 10 Dec 2013 11:19:09 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr's head updated: Allow the CPR w/w to take unboxed tuples apart (b2bdc27) Message-ID: <20131210111909.931702406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/nested-cpr' now includes: 5e0fe05 Sort the output of -dump-strsigs 289ecda Add more .mailmap entries 31da0b1 Merge remote-tracking branch 'origin/master' into HEAD 9805e2c Add documentation to plusUFM_CD ed35eb8 Do not export DmdResult constructors in Demand.lhs 0c44351 Make types of bothDmdType more precise 1167ff4 in Demand.lhs, remember what is a sum type 142eb5a Temporarily disable nested CPR inside sum types b2bdc27 Allow the CPR w/w to take unboxed tuples apart From git at git.haskell.org Tue Dec 10 13:55:51 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 10 Dec 2013 13:55:51 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Add a warning to dmdTransformDataConSig (which I believe is dead code) (222e1b4) Message-ID: <20131210135551.F3C7C2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/222e1b405cd90a071d79b25b2b25103746302993/ghc >--------------------------------------------------------------- commit 222e1b405cd90a071d79b25b2b25103746302993 Author: Joachim Breitner Date: Tue Dec 10 13:56:08 2013 +0000 Add a warning to dmdTransformDataConSig (which I believe is dead code) >--------------------------------------------------------------- 222e1b405cd90a071d79b25b2b25103746302993 compiler/basicTypes/Demand.lhs | 1 + 1 file changed, 1 insertion(+) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index dc88692..8c7b009 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -1522,6 +1522,7 @@ dmdTransformDataConSig arity (StrictSig (DmdType _ _ con_res)) (CD { sd = str, ud = abs }) | Just str_dmds <- go_str arity str , Just abs_dmds <- go_abs arity abs + , WARN( True, text "dmdTransformDataConSig indeed still in use" ) True = DmdType emptyDmdEnv (mkJointDmds str_dmds abs_dmds) con_res -- Must remember whether it's a product, hence con_res, not TopRes From git at git.haskell.org Tue Dec 10 17:50:19 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 10 Dec 2013 17:50:19 +0000 (UTC) Subject: [commit: ghc] master: Better debug printing (0849d02) Message-ID: <20131210175019.8F6B42406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0849d0243192ac10798b2095a25e18b7f611988c/ghc >--------------------------------------------------------------- commit 0849d0243192ac10798b2095a25e18b7f611988c Author: Simon Peyton Jones Date: Tue Dec 10 17:49:48 2013 +0000 Better debug printing >--------------------------------------------------------------- 0849d0243192ac10798b2095a25e18b7f611988c compiler/typecheck/TcRnTypes.lhs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/typecheck/TcRnTypes.lhs b/compiler/typecheck/TcRnTypes.lhs index e71d73a..b7c9790 100644 --- a/compiler/typecheck/TcRnTypes.lhs +++ b/compiler/typecheck/TcRnTypes.lhs @@ -1294,8 +1294,8 @@ instance Outputable Implication where , ic_binds = binds, ic_info = info }) = ptext (sLit "Implic") <+> braces (sep [ ptext (sLit "Untouchables =") <+> ppr untch - , ptext (sLit "Skolems =") <+> ppr skols - , ptext (sLit "Flatten-skolems =") <+> ppr fsks + , ptext (sLit "Skolems =") <+> pprTvBndrs skols + , ptext (sLit "Flatten-skolems =") <+> pprTvBndrs fsks , ptext (sLit "Given =") <+> pprEvVars given , ptext (sLit "Wanted =") <+> ppr wanted , ptext (sLit "Binds =") <+> ppr binds From git at git.haskell.org Tue Dec 10 17:50:21 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 10 Dec 2013 17:50:21 +0000 (UTC) Subject: [commit: ghc] master: Spelling in comment (f114826) Message-ID: <20131210175021.DF97A2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f114826575c29bc578df64b8ba754609d9986fb6/ghc >--------------------------------------------------------------- commit f114826575c29bc578df64b8ba754609d9986fb6 Author: Simon Peyton Jones Date: Tue Dec 10 17:49:58 2013 +0000 Spelling in comment >--------------------------------------------------------------- f114826575c29bc578df64b8ba754609d9986fb6 compiler/typecheck/TcEvidence.lhs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/typecheck/TcEvidence.lhs b/compiler/typecheck/TcEvidence.lhs index da48849..3e230d3 100644 --- a/compiler/typecheck/TcEvidence.lhs +++ b/compiler/typecheck/TcEvidence.lhs @@ -567,7 +567,7 @@ data EvTerm | EvCoercion TcCoercion -- (Boxed) coercion bindings -- See Note [Coercion evidence terms] - | EvCast EvTerm TcCoercion -- d |> co, the coerction being at role representational + | EvCast EvTerm TcCoercion -- d |> co, the coercion being at role representational | EvDFunApp DFunId -- Dictionary instance application [Type] [EvTerm] From git at git.haskell.org Tue Dec 10 17:50:24 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 10 Dec 2013 17:50:24 +0000 (UTC) Subject: [commit: ghc] master: Do not generate given kind-equalities (fix Trac #8566) (7558231) Message-ID: <20131210175024.5F6492406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/755823126f4f58b74f2bb783dc683197273f3474/ghc >--------------------------------------------------------------- commit 755823126f4f58b74f2bb783dc683197273f3474 Author: Simon Peyton Jones Date: Tue Dec 10 17:49:18 2013 +0000 Do not generate given kind-equalities (fix Trac #8566) This is a long-standing bug. We were generating a Given equality between kind variables, and (at least until we support kind coercions) we can't do that. The fix is to drop such Given equalities entirely. That may mean we can't prove some things, but that's fair enough -- the current proof language can't express such proofs. See Note [Do not create Given kind equalities] in TcSMonad >--------------------------------------------------------------- 755823126f4f58b74f2bb783dc683197273f3474 compiler/typecheck/TcCanonical.lhs | 34 ++++++++--------- compiler/typecheck/TcInteract.lhs | 11 ++++-- compiler/typecheck/TcSMonad.lhs | 72 ++++++++++++++++++++++++++---------- 3 files changed, 77 insertions(+), 40 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 755823126f4f58b74f2bb783dc683197273f3474 From git at git.haskell.org Tue Dec 10 17:54:26 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 10 Dec 2013 17:54:26 +0000 (UTC) Subject: [commit: testsuite] master: Test Trac #8566 (a6e35a0) Message-ID: <20131210175426.B86BE2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/testsuite On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a6e35a07d6d48ce782c5473c03cc09da996e1986/testsuite >--------------------------------------------------------------- commit a6e35a07d6d48ce782c5473c03cc09da996e1986 Author: Simon Peyton Jones Date: Tue Dec 10 17:53:46 2013 +0000 Test Trac #8566 >--------------------------------------------------------------- a6e35a07d6d48ce782c5473c03cc09da996e1986 tests/polykinds/T8566.hs | 31 +++++++++++++++++++++++++++++++ tests/polykinds/T8566.stderr | 18 ++++++++++++++++++ tests/polykinds/all.T | 1 + 3 files changed, 50 insertions(+) diff --git a/tests/polykinds/T8566.hs b/tests/polykinds/T8566.hs new file mode 100644 index 0000000..ee5892c --- /dev/null +++ b/tests/polykinds/T8566.hs @@ -0,0 +1,31 @@ +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE PolyKinds #-} +{-# LANGUAGE GADTs #-} +{-# LANGUAGE FlexibleInstances #-} +{-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE TypeOperators #-} +{-# LANGUAGE UndecidableInstances #-} +{-# LANGUAGE MultiParamTypeClasses #-} + +module T8566 where + +data U (s :: *) = forall v. AA v [U s] +-- AA :: forall (s:*) (v:*). v -> [U s] -> U s + +data I (u :: U *) (r :: [*]) :: * where + A :: I (AA t as) r -- Existential k + +-- A :: forall (u:U *) (r:[*]) Universal +-- (k:BOX) (t:k) (as:[U *]). Existential +-- (u ~ AA * k t as) => +-- I u r + +-- fs unused, but needs to be present for the bug +class C (u :: U *) (r :: [*]) (fs :: [*]) where + c :: I u r -> I u r + +-- c :: forall (u :: U *) (r :: [*]) (fs :: [*]). C u r fs => I u r -> I u r + +instance (C (AA (t (I a ps)) as) ps fs) => C (AA t (a ': as)) ps fs where +-- instance C (AA t (a ': as)) ps fs where + c A = c undefined diff --git a/tests/polykinds/T8566.stderr b/tests/polykinds/T8566.stderr new file mode 100644 index 0000000..639f72b --- /dev/null +++ b/tests/polykinds/T8566.stderr @@ -0,0 +1,18 @@ + +T8566.hs:31:9: + Could not deduce (C ('AA (t (I a ps)) as) ps fs0) + arising from a use of ?c? + from the context (C ('AA (t (I a ps)) as) ps fs) + bound by the instance declaration at T8566.hs:29:10-67 + or from ('AA t (a : as) ~ 'AA t1 as1) + bound by a pattern with constructor + A :: forall (r :: [*]) (t :: k) (as :: [U *]). I ('AA t as) r, + in an equation for ?c? + at T8566.hs:31:5 + The type variable ?fs0? is ambiguous + Relevant bindings include + c :: I ('AA t (a : as)) ps -> I ('AA t (a : as)) ps + (bound at T8566.hs:31:3) + In the expression: c undefined + In an equation for ?c?: c A = c undefined + In the instance declaration for ?C ('AA t (a : as)) ps fs? diff --git a/tests/polykinds/all.T b/tests/polykinds/all.T index 44edefb..2d53e04 100644 --- a/tests/polykinds/all.T +++ b/tests/polykinds/all.T @@ -94,3 +94,4 @@ test('T8359', normal, compile, ['']) test('T8391', normal, compile, ['']) test('T8449', normal, run_command, ['$MAKE -s --no-print-directory T8449']) test('T8534', normal, compile, ['']) +test('T8566', normal, compile_fail,['']) From git at git.haskell.org Wed Dec 11 18:34:16 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 11 Dec 2013 18:34:16 +0000 (UTC) Subject: [commit: ghc] branch 'wip/better-ho-cardinality' created Message-ID: <20131211183416.6AC652406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/better-ho-cardinality Referencing: 79a1ef786623de3eb9b5791ce9d1e18cfd433103 From git at git.haskell.org Wed Dec 11 18:34:20 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 11 Dec 2013 18:34:20 +0000 (UTC) Subject: [commit: ghc] wip/better-ho-cardinality: Do not split void functions (20f8ee7) Message-ID: <20131211183421.00D212406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/better-ho-cardinality Link : http://ghc.haskell.org/trac/ghc/changeset/20f8ee758a359231ebb467bcee115671d082cb53/ghc >--------------------------------------------------------------- commit 20f8ee758a359231ebb467bcee115671d082cb53 Author: Simon Peyton Jones Date: Wed Dec 11 18:30:54 2013 +0000 Do not split void functions This is authored by SPJ, and split out out "Improve the handling of used-once stuff" by Joachim. >--------------------------------------------------------------- 20f8ee758a359231ebb467bcee115671d082cb53 compiler/stranal/WorkWrap.lhs | 19 ++++++++++++++++++- 1 file changed, 18 insertions(+), 1 deletion(-) diff --git a/compiler/stranal/WorkWrap.lhs b/compiler/stranal/WorkWrap.lhs index 6857961..c7b8201 100644 --- a/compiler/stranal/WorkWrap.lhs +++ b/compiler/stranal/WorkWrap.lhs @@ -257,7 +257,7 @@ tryWW dflags is_rec fn_id rhs -- Furthermore, don't even expose strictness info = return [ (fn_id, rhs) ] - | is_fun && (any worthSplittingArgDmd wrap_dmds || returnsCPR res_info) + | is_fun && (worth_splitting_args wrap_dmds rhs || returnsCPR res_info) = checkSize dflags new_fn_id rhs $ splitFun dflags new_fn_id fn_info wrap_dmds res_info rhs @@ -275,6 +275,12 @@ tryWW dflags is_rec fn_id rhs fn_dmd = demandInfo fn_info inline_act = inlinePragmaActivation (inlinePragInfo fn_info) + worth_splitting_args [d] (Lam b _) + | isAbsDmd d && isVoidTy (idType b) + = False -- Note [Do not split void functions] + worth_splitting_args wrap_dmds _ + = any worthSplittingArgDmd wrap_dmds + -- In practice it always will have a strictness -- signature, even if it's a uninformative one strict_sig = strictnessInfo fn_info @@ -395,6 +401,17 @@ noOneShotInfo :: [Bool] noOneShotInfo = repeat False \end{code} +Note [Do not split void functions] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Consider this rather common form of binding: + $j = \x:Void# -> ...no use of x... + +Since x is not used it'll be marked as absent. But there is no point +in w/w-ing because we'll simply add (\y:Void#), see WwLib.mkWorerArgs. + +If x has a more interesting type (eg Int, or Int#), there *is* a point +in w/w so that we don't pass the argument at all. + Note [Thunk splitting] ~~~~~~~~~~~~~~~~~~~~~~ Suppose x is used strictly (never mind whether it has the CPR From git at git.haskell.org Wed Dec 11 18:34:23 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 11 Dec 2013 18:34:23 +0000 (UTC) Subject: [commit: ghc] wip/better-ho-cardinality: Guarding against silly shifts (20c4854) Message-ID: <20131211183423.2D9302406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/better-ho-cardinality Link : http://ghc.haskell.org/trac/ghc/changeset/20c48544321f21b153fe4c198f7376d04975e58d/ghc >--------------------------------------------------------------- commit 20c48544321f21b153fe4c198f7376d04975e58d Author: Simon Peyton Jones Date: Wed Dec 11 18:19:34 2013 +0000 Guarding against silly shifts This patch was authored by SPJ and extracted from "Improve the handling of used-once stuff" by Joachim. >--------------------------------------------------------------- 20c48544321f21b153fe4c198f7376d04975e58d compiler/prelude/PrelRules.lhs | 80 ++++++++++++++++++++++++++++++++++------ 1 file changed, 68 insertions(+), 12 deletions(-) diff --git a/compiler/prelude/PrelRules.lhs b/compiler/prelude/PrelRules.lhs index b6ded2e..11367ed 100644 --- a/compiler/prelude/PrelRules.lhs +++ b/compiler/prelude/PrelRules.lhs @@ -141,10 +141,8 @@ primOpRules nm OrOp = mkPrimOpRule nm 2 [ binaryLit (wordOp2 (.|.)) primOpRules nm XorOp = mkPrimOpRule nm 2 [ binaryLit (wordOp2 xor) , identityDynFlags zerow , equalArgs >> retLit zerow ] -primOpRules nm SllOp = mkPrimOpRule nm 2 [ binaryLit (wordShiftOp2 Bits.shiftL) - , rightIdentityDynFlags zeroi ] -primOpRules nm SrlOp = mkPrimOpRule nm 2 [ binaryLit (wordShiftOp2 shiftRightLogical) - , rightIdentityDynFlags zeroi ] +primOpRules nm SllOp = mkPrimOpRule nm 2 [ wordShiftRule Bits.shiftL ] +primOpRules nm SrlOp = mkPrimOpRule nm 2 [ wordShiftRule shiftRightLogical ] -- coercions primOpRules nm Word2IntOp = mkPrimOpRule nm 1 [ liftLitDynFlags word2IntLit @@ -373,14 +371,25 @@ wordOp2 op dflags (MachWord w1) (MachWord w2) = wordResult dflags (fromInteger w1 `op` fromInteger w2) wordOp2 _ _ _ _ = Nothing -- Could find LitLit -wordShiftOp2 :: (Integer -> Int -> Integer) - -> DynFlags -> Literal -> Literal - -> Maybe CoreExpr --- Shifts take an Int; hence second arg of op is Int -wordShiftOp2 op dflags (MachWord x) (MachInt n) - = wordResult dflags (x `op` fromInteger n) - -- Do the shift at type Integer -wordShiftOp2 _ _ _ _ = Nothing +wordShiftRule :: (Integer -> Int -> Integer) -> RuleM CoreExpr + -- Shifts take an Int; hence second arg of op is Int +-- See Note [Guarding against silly shifts] +wordShiftRule shift_op + = do { dflags <- getDynFlags + ; [e1, Lit (MachInt shift_len)] <- getArgs + ; case e1 of + _ | shift_len == 0 + -> return e1 + | shift_len < 0 || wordSizeInBits dflags < shift_len + -> return (mkRuntimeErrorApp rUNTIME_ERROR_ID wordPrimTy + ("Bad shift length" ++ show shift_len)) + Lit (MachWord x) + -> liftMaybe $ wordResult dflags (x `shift_op` fromInteger shift_len) + -- Do the shift at type Integer, but shift length is Int + _ -> mzero } + +wordSizeInBits :: DynFlags -> Integer +wordSizeInBits dflags = toInteger (platformWordSize (targetPlatform dflags) `shiftL` 3) -------------------------- floatOp2 :: (Rational -> Rational -> Rational) @@ -522,6 +531,53 @@ idempotent = do [e1, e2] <- getArgs return e1 \end{code} +Note [Guarding against silly shifts] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Consider this code: + + import Data.Bits( (.|.), shiftL ) + chunkToBitmap :: [Bool] -> Word32 + chunkToBitmap chunk = foldr (.|.) 0 [ 1 `shiftL` n | (True,n) <- zip chunk [0..] ] + +This optimises to: +Shift.$wgo = \ (w_sCS :: GHC.Prim.Int#) (w1_sCT :: [GHC.Types.Bool]) -> + case w1_sCT of _ { + [] -> __word 0; + : x_aAW xs_aAX -> + case x_aAW of _ { + GHC.Types.False -> + case w_sCS of wild2_Xh { + __DEFAULT -> Shift.$wgo (GHC.Prim.+# wild2_Xh 1) xs_aAX; + 9223372036854775807 -> __word 0 }; + GHC.Types.True -> + case GHC.Prim.>=# w_sCS 64 of _ { + GHC.Types.False -> + case w_sCS of wild3_Xh { + __DEFAULT -> + case Shift.$wgo (GHC.Prim.+# wild3_Xh 1) xs_aAX of ww_sCW { __DEFAULT -> + GHC.Prim.or# (GHC.Prim.narrow32Word# + (GHC.Prim.uncheckedShiftL# (__word 1) wild3_Xh)) + ww_sCW + }; + 9223372036854775807 -> + GHC.Prim.narrow32Word# +!!!!--> (GHC.Prim.uncheckedShiftL# (__word 1) 9223372036854775807) + }; + GHC.Types.True -> + case w_sCS of wild3_Xh { + __DEFAULT -> Shift.$wgo (GHC.Prim.+# wild3_Xh 1) xs_aAX; + 9223372036854775807 -> __word 0 + } } } } + +Note the massive shift on line "!!!!". It can't happen, because we've checked +that w < 64, but the optimiser didn't spot that. We DO NO want to constant-fold this! +Moreover, if the programmer writes (n `uncheckedShiftL` 9223372036854775807), we +can't constant fold it, but if it gets to the assember we get + Error: operand type mismatch for `shl' + +So the best thing to do is to rewrite the shift with a call to error, +when the second arg is stupid. + %************************************************************************ %* * \subsection{Vaguely generic functions} From git at git.haskell.org Wed Dec 11 18:34:18 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 11 Dec 2013 18:34:18 +0000 (UTC) Subject: [commit: ghc] wip/better-ho-cardinality: Some refactoring of Demand and DmdAnal (62a8f74) Message-ID: <20131211183418.CAD9B2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/better-ho-cardinality Link : http://ghc.haskell.org/trac/ghc/changeset/62a8f746c25820070a9d808389cacf6fb9004e27/ghc >--------------------------------------------------------------- commit 62a8f746c25820070a9d808389cacf6fb9004e27 Author: Simon Peyton Jones Date: Wed Dec 11 18:17:04 2013 +0000 Some refactoring of Demand and DmdAnal This was authored by SPJ and extracted from the "Improve the handling of used-once stuff" patch by Joachim. >--------------------------------------------------------------- 62a8f746c25820070a9d808389cacf6fb9004e27 compiler/basicTypes/Demand.lhs | 223 +++++++++++++++++++--------------------- compiler/coreSyn/CoreUtils.lhs | 7 ++ compiler/stranal/DmdAnal.lhs | 31 +++--- compiler/stranal/WorkWrap.lhs | 11 +- 4 files changed, 136 insertions(+), 136 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 62a8f746c25820070a9d808389cacf6fb9004e27 From git at git.haskell.org Wed Dec 11 18:34:27 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 11 Dec 2013 18:34:27 +0000 (UTC) Subject: [commit: ghc] wip/better-ho-cardinality: Assign strictness signatures to primitive operations (32d3b73) Message-ID: <20131211183428.86F732406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/better-ho-cardinality Link : http://ghc.haskell.org/trac/ghc/changeset/32d3b73423923adc40ac7cc867d9930b1d474240/ghc >--------------------------------------------------------------- commit 32d3b73423923adc40ac7cc867d9930b1d474240 Author: Simon Peyton Jones Date: Wed Dec 11 18:18:53 2013 +0000 Assign strictness signatures to primitive operations This patch was authored by SPJ, and extracted from "Improve the handling of used-once stuff" by Joachim. >--------------------------------------------------------------- 32d3b73423923adc40ac7cc867d9930b1d474240 compiler/basicTypes/Demand.lhs | 7 ++++++- compiler/prelude/primops.txt.pp | 10 ++++++++-- 2 files changed, 14 insertions(+), 3 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 8249748..9c87bb7 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -14,7 +14,7 @@ module Demand ( mkProdDmd, mkOnceUsedDmd, mkManyUsedDmd, mkHeadStrict, oneifyDmd, getUsage, toCleanDmd, absDmd, topDmd, botDmd, seqDmd, - lubDmd, bothDmd, + lubDmd, bothDmd, apply1Dmd, apply2Dmd, isTopDmd, isBotDmd, isAbsDmd, isSeqDmd, peelUseCall, cleanUseDmd_maybe, strictenDmd, bothCleanDmd, @@ -465,6 +465,11 @@ mkJointDmds ss as = zipWithEqual "mkJointDmds" mkJointDmd ss as absDmd :: JointDmd absDmd = mkJointDmd Lazy Abs +apply1Dmd, apply2Dmd :: Demand +-- C1(U), C1(C1(U)) respectively +apply1Dmd = JD { strd = Lazy, absd = Use Many (UCall One Used) } +apply2Dmd = JD { strd = Lazy, absd = Use Many (UCall One (UCall One Used)) } + topDmd :: JointDmd topDmd = mkJointDmd Lazy useTop diff --git a/compiler/prelude/primops.txt.pp b/compiler/prelude/primops.txt.pp index 37591af..34a5ef3 100644 --- a/compiler/prelude/primops.txt.pp +++ b/compiler/prelude/primops.txt.pp @@ -1618,8 +1618,8 @@ primop CatchOp "catch#" GenPrimOp with -- Catch is actually strict in its first argument -- but we don't want to tell the strictness - -- analyser about that! - -- might use caught action multiply + -- analyser about that, so that exceptions stay inside it. + strictness = { \ _arity -> mkStrictSig (mkTopDmdType [apply1Dmd,apply2Dmd,topDmd] topRes) } out_of_line = True has_side_effects = True @@ -1651,6 +1651,7 @@ primop MaskAsyncExceptionsOp "maskAsyncExceptions#" GenPrimOp (State# RealWorld -> (# State# RealWorld, a #)) -> (State# RealWorld -> (# State# RealWorld, a #)) with + strictness = { \ _arity -> mkStrictSig (mkTopDmdType [apply1Dmd,topDmd] topRes) } out_of_line = True has_side_effects = True @@ -1658,6 +1659,7 @@ primop MaskUninterruptibleOp "maskUninterruptible#" GenPrimOp (State# RealWorld -> (# State# RealWorld, a #)) -> (State# RealWorld -> (# State# RealWorld, a #)) with + strictness = { \ _arity -> mkStrictSig (mkTopDmdType [apply1Dmd,topDmd] topRes) } out_of_line = True has_side_effects = True @@ -1665,6 +1667,7 @@ primop UnmaskAsyncExceptionsOp "unmaskAsyncExceptions#" GenPrimOp (State# RealWorld -> (# State# RealWorld, a #)) -> (State# RealWorld -> (# State# RealWorld, a #)) with + strictness = { \ _arity -> mkStrictSig (mkTopDmdType [apply1Dmd,topDmd] topRes) } out_of_line = True has_side_effects = True @@ -1684,6 +1687,7 @@ primop AtomicallyOp "atomically#" GenPrimOp (State# RealWorld -> (# State# RealWorld, a #) ) -> State# RealWorld -> (# State# RealWorld, a #) with + strictness = { \ _arity -> mkStrictSig (mkTopDmdType [apply1Dmd,topDmd] topRes) } out_of_line = True has_side_effects = True @@ -1709,6 +1713,7 @@ primop CatchRetryOp "catchRetry#" GenPrimOp -> (State# RealWorld -> (# State# RealWorld, a #) ) -> (State# RealWorld -> (# State# RealWorld, a #) ) with + strictness = { \ _arity -> mkStrictSig (mkTopDmdType [apply1Dmd,apply1Dmd,topDmd] topRes) } out_of_line = True has_side_effects = True @@ -1717,6 +1722,7 @@ primop CatchSTMOp "catchSTM#" GenPrimOp -> (b -> State# RealWorld -> (# State# RealWorld, a #) ) -> (State# RealWorld -> (# State# RealWorld, a #) ) with + strictness = { \ _arity -> mkStrictSig (mkTopDmdType [apply1Dmd,apply2Dmd,topDmd] topRes) } out_of_line = True has_side_effects = True From git at git.haskell.org Wed Dec 11 18:34:29 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 11 Dec 2013 18:34:29 +0000 (UTC) Subject: [commit: ghc] wip/better-ho-cardinality: Improve the handling of used-once stuff (79a1ef7) Message-ID: <20131211183429.EA2D12406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/better-ho-cardinality Link : http://ghc.haskell.org/trac/ghc/changeset/79a1ef786623de3eb9b5791ce9d1e18cfd433103/ghc >--------------------------------------------------------------- commit 79a1ef786623de3eb9b5791ce9d1e18cfd433103 Author: Simon Peyton Jones Date: Fri Nov 22 17:13:05 2013 +0000 Improve the handling of used-once stuff Joachim and I are committing this onto a branch so that we can share it, but we expect to do a bit more work before merging it onto head. Nofib staus: - Most programs, no change - A few improve - A couple get worse (cacheprof, tak, rfib) Investigating the "get worse" set is what's holding up putting this on head. The major issue is this. Consider map (f g) ys where f's demand signature looks like f :: -> -> . So 'f' is not saturated. What demand do we place on g? Answer C(C1(U)) That is, the inner C1 should stay, even though f is not saturated. I found that this made a significant difference in the demand signatures inferred in GHC.IO, which uses lots of higher-order exception handlers. I also had to add used-once demand signatures for some of the 'catch' primops, so that we know their handlers are only called once. >--------------------------------------------------------------- 79a1ef786623de3eb9b5791ce9d1e18cfd433103 compiler/basicTypes/BasicTypes.lhs | 55 ++++++++++++++++++++++++++++ compiler/basicTypes/Demand.lhs | 21 +++++------ compiler/basicTypes/Id.lhs | 64 ++++++++++++++++++++++++--------- compiler/basicTypes/IdInfo.lhs | 70 +++++++++--------------------------- compiler/basicTypes/MkId.lhs | 3 +- compiler/coreSyn/CoreArity.lhs | 45 ++++++++++------------- compiler/coreSyn/PprCore.lhs | 33 ++++++++++------- compiler/simplCore/OccurAnal.lhs | 63 ++++++++++++++++---------------- compiler/simplCore/SetLevels.lhs | 4 ++- compiler/specialise/SpecConstr.lhs | 2 +- compiler/stranal/WorkWrap.lhs | 9 ++--- compiler/stranal/WwLib.lhs | 64 +++++++++++++++++---------------- 12 files changed, 241 insertions(+), 192 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 79a1ef786623de3eb9b5791ce9d1e18cfd433103 From git at git.haskell.org Wed Dec 11 18:34:25 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 11 Dec 2013 18:34:25 +0000 (UTC) Subject: [commit: ghc] wip/better-ho-cardinality: Return exprArity, not manifestArity (753b254) Message-ID: <20131211183425.78CDE2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/better-ho-cardinality Link : http://ghc.haskell.org/trac/ghc/changeset/753b25499fa0060ff403c3bb592b343ff98abe81/ghc >--------------------------------------------------------------- commit 753b25499fa0060ff403c3bb592b343ff98abe81 Author: Simon Peyton Jones Date: Wed Dec 11 18:20:21 2013 +0000 Return exprArity, not manifestArity This patch was authored by SPJ, and extracted from "Improve the handling of used-once stuff" by Joachim. >--------------------------------------------------------------- 753b25499fa0060ff403c3bb592b343ff98abe81 compiler/simplCore/SimplUtils.lhs | 19 ++++++++++++++++--- 1 file changed, 16 insertions(+), 3 deletions(-) diff --git a/compiler/simplCore/SimplUtils.lhs b/compiler/simplCore/SimplUtils.lhs index 6c7dcc2..36f292d 100644 --- a/compiler/simplCore/SimplUtils.lhs +++ b/compiler/simplCore/SimplUtils.lhs @@ -1195,8 +1195,11 @@ tryEtaExpandRhs env bndr rhs = do { dflags <- getDynFlags ; (new_arity, new_rhs) <- try_expand dflags - ; WARN( new_arity < old_arity || new_arity < _dmd_arity, - (ptext (sLit "Arity decrease:") <+> (ppr bndr <+> ppr old_arity + ; WARN( new_arity < old_arity, + (ptext (sLit "Arity decrease:") <+> (ppr bndr + <+> ppr old_arity <+> ppr new_arity) $$ ppr new_rhs) ) + WARN( new_arity < _dmd_arity, + (ptext (sLit "Arity less than dmd sig arity:") <+> (ppr bndr <+> ppr new_arity <+> ppr _dmd_arity) $$ ppr new_rhs) ) -- Note [Arity decrease] return (new_arity, new_rhs) } @@ -1211,13 +1214,23 @@ tryEtaExpandRhs env bndr rhs = do { tick (EtaExpansion bndr) ; return (new_arity, etaExpand new_arity rhs) } | otherwise - = return (manifest_arity, rhs) + = return (exprArity rhs, rhs) -- See Note [Return exprArity, not manifestArity] manifest_arity = manifestArity rhs old_arity = idArity bndr _dmd_arity = length $ fst $ splitStrictSig $ idStrictness bndr \end{code} +Note [Return exprArity, not manifestArity] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Consider + f = \xy. blah + g = f 2 +The f will get arity 2, and we want g to get arity 1, even though +exprEtaExpandArity (and hence findArity) may not eta-expand it. +Hence tryEtaExpand should return (exprArity (f 2)), not its +manifest arity (which is zero). + Note [Eta-expanding at let bindings] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ We now eta expand at let-bindings, which is where the payoff comes. From git at git.haskell.org Wed Dec 11 18:52:07 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 11 Dec 2013 18:52:07 +0000 (UTC) Subject: [commit: ghc] wip/better-ho-cardinality: Some refactoring of Demand and DmdAnal (910b489) Message-ID: <20131211185207.B4DFB2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/better-ho-cardinality Link : http://ghc.haskell.org/trac/ghc/changeset/910b48912f19988764f5875749872d3106e13617/ghc >--------------------------------------------------------------- commit 910b48912f19988764f5875749872d3106e13617 Author: Simon Peyton Jones Date: Wed Dec 11 18:17:04 2013 +0000 Some refactoring of Demand and DmdAnal This was authored by SPJ and extracted from the "Improve the handling of used-once stuff" patch by Joachim. >--------------------------------------------------------------- 910b48912f19988764f5875749872d3106e13617 compiler/basicTypes/Demand.lhs | 225 +++++++++++++++++++--------------------- compiler/coreSyn/CoreUtils.lhs | 7 ++ compiler/stranal/DmdAnal.lhs | 31 +++--- compiler/stranal/WorkWrap.lhs | 10 +- 4 files changed, 136 insertions(+), 137 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 910b48912f19988764f5875749872d3106e13617 From git at git.haskell.org Wed Dec 11 18:52:10 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 11 Dec 2013 18:52:10 +0000 (UTC) Subject: [commit: ghc] wip/better-ho-cardinality: Do not split void functions (7583c20) Message-ID: <20131211185210.32F962406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/better-ho-cardinality Link : http://ghc.haskell.org/trac/ghc/changeset/7583c20521b40f4a4d9ab354e4bc88d3f4040ebe/ghc >--------------------------------------------------------------- commit 7583c20521b40f4a4d9ab354e4bc88d3f4040ebe Author: Simon Peyton Jones Date: Wed Dec 11 18:30:54 2013 +0000 Do not split void functions This is authored by SPJ, and split out out "Improve the handling of used-once stuff" by Joachim. >--------------------------------------------------------------- 7583c20521b40f4a4d9ab354e4bc88d3f4040ebe compiler/stranal/WorkWrap.lhs | 20 +++++++++++++++++++- 1 file changed, 19 insertions(+), 1 deletion(-) diff --git a/compiler/stranal/WorkWrap.lhs b/compiler/stranal/WorkWrap.lhs index b66a449..14a01d5 100644 --- a/compiler/stranal/WorkWrap.lhs +++ b/compiler/stranal/WorkWrap.lhs @@ -17,6 +17,7 @@ import CoreSyn import CoreUnfold ( certainlyWillInline, mkInlineUnfolding, mkWwInlineRule ) import CoreUtils ( exprType, exprIsHNF ) import CoreArity ( exprArity ) +import Type ( isVoidTy ) import Var import Id import IdInfo @@ -256,7 +257,7 @@ tryWW dflags is_rec fn_id rhs -- Furthermore, don't even expose strictness info = return [ (fn_id, rhs) ] - | is_fun && (any worthSplittingArgDmd wrap_dmds || returnsCPR res_info) + | is_fun && (worth_splitting_args wrap_dmds rhs || returnsCPR res_info) = checkSize dflags new_fn_id rhs $ splitFun dflags new_fn_id fn_info wrap_dmds res_info rhs @@ -274,6 +275,12 @@ tryWW dflags is_rec fn_id rhs fn_dmd = demandInfo fn_info inline_act = inlinePragmaActivation (inlinePragInfo fn_info) + worth_splitting_args [d] (Lam b _) + | isAbsDmd d && isVoidTy (idType b) + = False -- Note [Do not split void functions] + worth_splitting_args wrap_dmds _ + = any worthSplittingArgDmd wrap_dmds + -- In practice it always will have a strictness -- signature, even if it's a uninformative one strict_sig = strictnessInfo fn_info @@ -394,6 +401,17 @@ noOneShotInfo :: [Bool] noOneShotInfo = repeat False \end{code} +Note [Do not split void functions] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Consider this rather common form of binding: + $j = \x:Void# -> ...no use of x... + +Since x is not used it'll be marked as absent. But there is no point +in w/w-ing because we'll simply add (\y:Void#), see WwLib.mkWorerArgs. + +If x has a more interesting type (eg Int, or Int#), there *is* a point +in w/w so that we don't pass the argument at all. + Note [Thunk splitting] ~~~~~~~~~~~~~~~~~~~~~~ Suppose x is used strictly (never mind whether it has the CPR From git at git.haskell.org Wed Dec 11 18:52:12 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 11 Dec 2013 18:52:12 +0000 (UTC) Subject: [commit: ghc] wip/better-ho-cardinality: Assign strictness signatures to primitive operations (c7b9505) Message-ID: <20131211185212.CD8762406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/better-ho-cardinality Link : http://ghc.haskell.org/trac/ghc/changeset/c7b9505b863da78a8b128af9a8d99dbd4c1f0754/ghc >--------------------------------------------------------------- commit c7b9505b863da78a8b128af9a8d99dbd4c1f0754 Author: Simon Peyton Jones Date: Wed Dec 11 18:18:53 2013 +0000 Assign strictness signatures to primitive operations This patch was authored by SPJ, and extracted from "Improve the handling of used-once stuff" by Joachim. >--------------------------------------------------------------- c7b9505b863da78a8b128af9a8d99dbd4c1f0754 compiler/basicTypes/Demand.lhs | 7 ++++++- compiler/prelude/primops.txt.pp | 10 ++++++++-- 2 files changed, 14 insertions(+), 3 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index fa706de..ba635fc 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -14,7 +14,7 @@ module Demand ( mkProdDmd, mkOnceUsedDmd, mkManyUsedDmd, mkHeadStrict, oneifyDmd, getUsage, toCleanDmd, absDmd, topDmd, botDmd, seqDmd, - lubDmd, bothDmd, + lubDmd, bothDmd, apply1Dmd, apply2Dmd, isTopDmd, isBotDmd, isAbsDmd, isSeqDmd, peelUseCall, cleanUseDmd_maybe, strictenDmd, bothCleanDmd, @@ -467,6 +467,11 @@ mkJointDmds ss as = zipWithEqual "mkJointDmds" mkJointDmd ss as absDmd :: JointDmd absDmd = mkJointDmd Lazy Abs +apply1Dmd, apply2Dmd :: Demand +-- C1(U), C1(C1(U)) respectively +apply1Dmd = JD { strd = Lazy, absd = Use Many (UCall One Used) } +apply2Dmd = JD { strd = Lazy, absd = Use Many (UCall One (UCall One Used)) } + topDmd :: JointDmd topDmd = mkJointDmd Lazy useTop diff --git a/compiler/prelude/primops.txt.pp b/compiler/prelude/primops.txt.pp index 7457583..b3cf2f4 100644 --- a/compiler/prelude/primops.txt.pp +++ b/compiler/prelude/primops.txt.pp @@ -1618,8 +1618,8 @@ primop CatchOp "catch#" GenPrimOp with -- Catch is actually strict in its first argument -- but we don't want to tell the strictness - -- analyser about that! - -- might use caught action multiply + -- analyser about that, so that exceptions stay inside it. + strictness = { \ _arity -> mkClosedStrictSig [apply1Dmd,apply2Dmd,topDmd] topRes } out_of_line = True has_side_effects = True @@ -1651,6 +1651,7 @@ primop MaskAsyncExceptionsOp "maskAsyncExceptions#" GenPrimOp (State# RealWorld -> (# State# RealWorld, a #)) -> (State# RealWorld -> (# State# RealWorld, a #)) with + strictness = { \ _arity -> mkClosedStrictSig [apply1Dmd,topDmd] topRes } out_of_line = True has_side_effects = True @@ -1658,6 +1659,7 @@ primop MaskUninterruptibleOp "maskUninterruptible#" GenPrimOp (State# RealWorld -> (# State# RealWorld, a #)) -> (State# RealWorld -> (# State# RealWorld, a #)) with + strictness = { \ _arity -> mkClosedStrictSig [apply1Dmd,topDmd] topRes } out_of_line = True has_side_effects = True @@ -1665,6 +1667,7 @@ primop UnmaskAsyncExceptionsOp "unmaskAsyncExceptions#" GenPrimOp (State# RealWorld -> (# State# RealWorld, a #)) -> (State# RealWorld -> (# State# RealWorld, a #)) with + strictness = { \ _arity -> mkClosedStrictSig [apply1Dmd,topDmd] topRes } out_of_line = True has_side_effects = True @@ -1684,6 +1687,7 @@ primop AtomicallyOp "atomically#" GenPrimOp (State# RealWorld -> (# State# RealWorld, a #) ) -> State# RealWorld -> (# State# RealWorld, a #) with + strictness = { \ _arity -> mkClosedStrictSig [apply1Dmd,topDmd] topRes } out_of_line = True has_side_effects = True @@ -1709,6 +1713,7 @@ primop CatchRetryOp "catchRetry#" GenPrimOp -> (State# RealWorld -> (# State# RealWorld, a #) ) -> (State# RealWorld -> (# State# RealWorld, a #) ) with + strictness = { \ _arity -> mkClosedStrictSig [apply1Dmd,apply1Dmd,topDmd] topRes } out_of_line = True has_side_effects = True @@ -1717,6 +1722,7 @@ primop CatchSTMOp "catchSTM#" GenPrimOp -> (b -> State# RealWorld -> (# State# RealWorld, a #) ) -> (State# RealWorld -> (# State# RealWorld, a #) ) with + strictness = { \ _arity -> mkClosedStrictSig [apply1Dmd,apply2Dmd,topDmd] topRes } out_of_line = True has_side_effects = True From git at git.haskell.org Wed Dec 11 18:52:14 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 11 Dec 2013 18:52:14 +0000 (UTC) Subject: [commit: ghc] wip/better-ho-cardinality: Guarding against silly shifts (5a92f04) Message-ID: <20131211185215.040B72406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/better-ho-cardinality Link : http://ghc.haskell.org/trac/ghc/changeset/5a92f04e81dcccb39f4ab766f9fa5950a86d622a/ghc >--------------------------------------------------------------- commit 5a92f04e81dcccb39f4ab766f9fa5950a86d622a Author: Simon Peyton Jones Date: Wed Dec 11 18:19:34 2013 +0000 Guarding against silly shifts This patch was authored by SPJ and extracted from "Improve the handling of used-once stuff" by Joachim. >--------------------------------------------------------------- 5a92f04e81dcccb39f4ab766f9fa5950a86d622a compiler/prelude/PrelRules.lhs | 80 ++++++++++++++++++++++++++++++++++------ 1 file changed, 68 insertions(+), 12 deletions(-) diff --git a/compiler/prelude/PrelRules.lhs b/compiler/prelude/PrelRules.lhs index b6ded2e..11367ed 100644 --- a/compiler/prelude/PrelRules.lhs +++ b/compiler/prelude/PrelRules.lhs @@ -141,10 +141,8 @@ primOpRules nm OrOp = mkPrimOpRule nm 2 [ binaryLit (wordOp2 (.|.)) primOpRules nm XorOp = mkPrimOpRule nm 2 [ binaryLit (wordOp2 xor) , identityDynFlags zerow , equalArgs >> retLit zerow ] -primOpRules nm SllOp = mkPrimOpRule nm 2 [ binaryLit (wordShiftOp2 Bits.shiftL) - , rightIdentityDynFlags zeroi ] -primOpRules nm SrlOp = mkPrimOpRule nm 2 [ binaryLit (wordShiftOp2 shiftRightLogical) - , rightIdentityDynFlags zeroi ] +primOpRules nm SllOp = mkPrimOpRule nm 2 [ wordShiftRule Bits.shiftL ] +primOpRules nm SrlOp = mkPrimOpRule nm 2 [ wordShiftRule shiftRightLogical ] -- coercions primOpRules nm Word2IntOp = mkPrimOpRule nm 1 [ liftLitDynFlags word2IntLit @@ -373,14 +371,25 @@ wordOp2 op dflags (MachWord w1) (MachWord w2) = wordResult dflags (fromInteger w1 `op` fromInteger w2) wordOp2 _ _ _ _ = Nothing -- Could find LitLit -wordShiftOp2 :: (Integer -> Int -> Integer) - -> DynFlags -> Literal -> Literal - -> Maybe CoreExpr --- Shifts take an Int; hence second arg of op is Int -wordShiftOp2 op dflags (MachWord x) (MachInt n) - = wordResult dflags (x `op` fromInteger n) - -- Do the shift at type Integer -wordShiftOp2 _ _ _ _ = Nothing +wordShiftRule :: (Integer -> Int -> Integer) -> RuleM CoreExpr + -- Shifts take an Int; hence second arg of op is Int +-- See Note [Guarding against silly shifts] +wordShiftRule shift_op + = do { dflags <- getDynFlags + ; [e1, Lit (MachInt shift_len)] <- getArgs + ; case e1 of + _ | shift_len == 0 + -> return e1 + | shift_len < 0 || wordSizeInBits dflags < shift_len + -> return (mkRuntimeErrorApp rUNTIME_ERROR_ID wordPrimTy + ("Bad shift length" ++ show shift_len)) + Lit (MachWord x) + -> liftMaybe $ wordResult dflags (x `shift_op` fromInteger shift_len) + -- Do the shift at type Integer, but shift length is Int + _ -> mzero } + +wordSizeInBits :: DynFlags -> Integer +wordSizeInBits dflags = toInteger (platformWordSize (targetPlatform dflags) `shiftL` 3) -------------------------- floatOp2 :: (Rational -> Rational -> Rational) @@ -522,6 +531,53 @@ idempotent = do [e1, e2] <- getArgs return e1 \end{code} +Note [Guarding against silly shifts] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Consider this code: + + import Data.Bits( (.|.), shiftL ) + chunkToBitmap :: [Bool] -> Word32 + chunkToBitmap chunk = foldr (.|.) 0 [ 1 `shiftL` n | (True,n) <- zip chunk [0..] ] + +This optimises to: +Shift.$wgo = \ (w_sCS :: GHC.Prim.Int#) (w1_sCT :: [GHC.Types.Bool]) -> + case w1_sCT of _ { + [] -> __word 0; + : x_aAW xs_aAX -> + case x_aAW of _ { + GHC.Types.False -> + case w_sCS of wild2_Xh { + __DEFAULT -> Shift.$wgo (GHC.Prim.+# wild2_Xh 1) xs_aAX; + 9223372036854775807 -> __word 0 }; + GHC.Types.True -> + case GHC.Prim.>=# w_sCS 64 of _ { + GHC.Types.False -> + case w_sCS of wild3_Xh { + __DEFAULT -> + case Shift.$wgo (GHC.Prim.+# wild3_Xh 1) xs_aAX of ww_sCW { __DEFAULT -> + GHC.Prim.or# (GHC.Prim.narrow32Word# + (GHC.Prim.uncheckedShiftL# (__word 1) wild3_Xh)) + ww_sCW + }; + 9223372036854775807 -> + GHC.Prim.narrow32Word# +!!!!--> (GHC.Prim.uncheckedShiftL# (__word 1) 9223372036854775807) + }; + GHC.Types.True -> + case w_sCS of wild3_Xh { + __DEFAULT -> Shift.$wgo (GHC.Prim.+# wild3_Xh 1) xs_aAX; + 9223372036854775807 -> __word 0 + } } } } + +Note the massive shift on line "!!!!". It can't happen, because we've checked +that w < 64, but the optimiser didn't spot that. We DO NO want to constant-fold this! +Moreover, if the programmer writes (n `uncheckedShiftL` 9223372036854775807), we +can't constant fold it, but if it gets to the assember we get + Error: operand type mismatch for `shl' + +So the best thing to do is to rewrite the shift with a call to error, +when the second arg is stupid. + %************************************************************************ %* * \subsection{Vaguely generic functions} From git at git.haskell.org Wed Dec 11 18:52:17 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 11 Dec 2013 18:52:17 +0000 (UTC) Subject: [commit: ghc] wip/better-ho-cardinality: Return exprArity, not manifestArity (a9de79f) Message-ID: <20131211185217.999422406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/better-ho-cardinality Link : http://ghc.haskell.org/trac/ghc/changeset/a9de79f9d0de24757882c62da99cacb17b9e0ca9/ghc >--------------------------------------------------------------- commit a9de79f9d0de24757882c62da99cacb17b9e0ca9 Author: Simon Peyton Jones Date: Wed Dec 11 18:20:21 2013 +0000 Return exprArity, not manifestArity This patch was authored by SPJ, and extracted from "Improve the handling of used-once stuff" by Joachim. >--------------------------------------------------------------- a9de79f9d0de24757882c62da99cacb17b9e0ca9 compiler/simplCore/SimplUtils.lhs | 19 ++++++++++++++++--- 1 file changed, 16 insertions(+), 3 deletions(-) diff --git a/compiler/simplCore/SimplUtils.lhs b/compiler/simplCore/SimplUtils.lhs index 6c7dcc2..36f292d 100644 --- a/compiler/simplCore/SimplUtils.lhs +++ b/compiler/simplCore/SimplUtils.lhs @@ -1195,8 +1195,11 @@ tryEtaExpandRhs env bndr rhs = do { dflags <- getDynFlags ; (new_arity, new_rhs) <- try_expand dflags - ; WARN( new_arity < old_arity || new_arity < _dmd_arity, - (ptext (sLit "Arity decrease:") <+> (ppr bndr <+> ppr old_arity + ; WARN( new_arity < old_arity, + (ptext (sLit "Arity decrease:") <+> (ppr bndr + <+> ppr old_arity <+> ppr new_arity) $$ ppr new_rhs) ) + WARN( new_arity < _dmd_arity, + (ptext (sLit "Arity less than dmd sig arity:") <+> (ppr bndr <+> ppr new_arity <+> ppr _dmd_arity) $$ ppr new_rhs) ) -- Note [Arity decrease] return (new_arity, new_rhs) } @@ -1211,13 +1214,23 @@ tryEtaExpandRhs env bndr rhs = do { tick (EtaExpansion bndr) ; return (new_arity, etaExpand new_arity rhs) } | otherwise - = return (manifest_arity, rhs) + = return (exprArity rhs, rhs) -- See Note [Return exprArity, not manifestArity] manifest_arity = manifestArity rhs old_arity = idArity bndr _dmd_arity = length $ fst $ splitStrictSig $ idStrictness bndr \end{code} +Note [Return exprArity, not manifestArity] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Consider + f = \xy. blah + g = f 2 +The f will get arity 2, and we want g to get arity 1, even though +exprEtaExpandArity (and hence findArity) may not eta-expand it. +Hence tryEtaExpand should return (exprArity (f 2)), not its +manifest arity (which is zero). + Note [Eta-expanding at let bindings] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ We now eta expand at let-bindings, which is where the payoff comes. From git at git.haskell.org Wed Dec 11 18:52:19 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 11 Dec 2013 18:52:19 +0000 (UTC) Subject: [commit: ghc] wip/better-ho-cardinality: Improve the handling of used-once stuff (fe6512d) Message-ID: <20131211185220.821632406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/better-ho-cardinality Link : http://ghc.haskell.org/trac/ghc/changeset/fe6512dd5f48ba1d2deee7c2abb42d8b2b917b5c/ghc >--------------------------------------------------------------- commit fe6512dd5f48ba1d2deee7c2abb42d8b2b917b5c Author: Simon Peyton Jones Date: Fri Nov 22 17:13:05 2013 +0000 Improve the handling of used-once stuff Joachim and I are committing this onto a branch so that we can share it, but we expect to do a bit more work before merging it onto head. Nofib staus: - Most programs, no change - A few improve - A couple get worse (cacheprof, tak, rfib) Investigating the "get worse" set is what's holding up putting this on head. The major issue is this. Consider map (f g) ys where f's demand signature looks like f :: -> -> . So 'f' is not saturated. What demand do we place on g? Answer C(C1(U)) That is, the inner C1 should stay, even though f is not saturated. I found that this made a significant difference in the demand signatures inferred in GHC.IO, which uses lots of higher-order exception handlers. I also had to add used-once demand signatures for some of the 'catch' primops, so that we know their handlers are only called once. >--------------------------------------------------------------- fe6512dd5f48ba1d2deee7c2abb42d8b2b917b5c compiler/basicTypes/BasicTypes.lhs | 55 ++++++++++++++++++++++++++++ compiler/basicTypes/Demand.lhs | 21 +++++------ compiler/basicTypes/Id.lhs | 64 ++++++++++++++++++++++++--------- compiler/basicTypes/IdInfo.lhs | 70 +++++++++--------------------------- compiler/basicTypes/MkId.lhs | 3 +- compiler/coreSyn/CoreArity.lhs | 45 ++++++++++------------- compiler/coreSyn/PprCore.lhs | 33 ++++++++++------- compiler/simplCore/OccurAnal.lhs | 63 ++++++++++++++++---------------- compiler/simplCore/SetLevels.lhs | 4 ++- compiler/specialise/SpecConstr.lhs | 2 +- compiler/stranal/WorkWrap.lhs | 9 ++--- compiler/stranal/WwLib.lhs | 64 +++++++++++++++++---------------- 12 files changed, 241 insertions(+), 192 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 fe6512dd5f48ba1d2deee7c2abb42d8b2b917b5c From git at git.haskell.org Wed Dec 11 18:52:23 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 11 Dec 2013 18:52:23 +0000 (UTC) Subject: [commit: ghc] wip/better-ho-cardinality's head updated: Improve the handling of used-once stuff (fe6512d) Message-ID: <20131211185223.811472406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/better-ho-cardinality' now includes: 803afa3 In toHsType, filter out kind variables 5f3aa06 Typos in comments in TcEvidence df37261 Typos in comments 6279a01 ghc.mk: one module name per line 9fbb8c7 Rejigger flushExec implementation (#8562, #8561) a247887 Comment only 1812f44 Comment only 3ac1539 Add role-checking ASSERT to mkCast f432229 Remove unused liftTcCoSubstWith 9d643cf Roleify TcCoercion aef9044 Beginnings of removing EvCoercible 808ded9 Get rid of EvCoercible 9bc5b53 Coercible for impredicative types 3fcde74 Comments only 1df2116 EvCast needs to take a representational coercion 4d1ea48 Implement shortcuts for slow calls (#6084) e9b0d36 Fix up shortcut for slow calls 9021737 Comments on slow-call-shortcutting 77e33bc -ddump-cmm: don't dump the proc point stage if we didn't do anything 6f7fa4e Refactor handleRunStatus some more, add comments and tidy up formatting a8ac471 Fix the deugger (fixing Trac #8557) f3a8416 More faff to get GHCi's top-level environment right 59e17d6 Fail (rather than addErr) if you use a bogus field in a pattern 9641641 Remove whitespace between macro identifiers and `(` 23efdd6 Update Notes for Coercible ceb600d Minor fix to example GHC plugin in the documentation 2e3c6a5 Update "stolen syntax" section (#8575) 9c3c152 Call busy_wait_nop() in the spin-wait loop in shutdown_gc_threads() de9f17e Update "stolen syntax" section (#8575) 4bbffb4 Fix documentation of FlexibleContexts (#8574) adb9964 Fix loopification with profiling and enable it by default (#8275) 6d24076 Document solution to #8275 6178f6e Don't explicitly refer to nodeReg in ldvEnterClosure ac31b79 Move the LDV code below the self-loop label (#8275) 574ccfa Respect the ordering of -package directives fac831f Revert "Respect the ordering of -package directives" 5e86ea5 TcDeriv: s/isomorphism/coercible bd7a125 With GND, report Coercible errors earliy 1791ea0 Print nicer error message for Coercible errors 06facab Refactor deferTcSForAllEq: Do not bind, but return EvTerm 249d47a Bind monadic stuff in getCoercibleInst locally, not via parameters e1e9faf Handle Coercible (forall a. t) (forall a. t2) in TcInteract b859c18 More links to [Coercible Instances] 3fecf81 Remove dead code orphaned by implementing GND with `coerce`. 4067340 Rejig rejigConRes & friends, doing role checks in a second pass. b84fff3 Fix location of spliced-in role annotations. 90588c1 Move FunDeps to typecheck cb17c1f Note [HyperStr and Use demands] 0fe399c Some popular typos in comments 51bebb7 Refactor: Origin of inferred Thetas 4025d66 Elaborate "deriving" error messages 586bc85 Mask async exceptions in forkM_ d14e5bf Export getHscEnv from HscMain 95ba5d8 More detailed error message when GND fails 356bc56 Fix note reference [WildCard binders] e122154 Comments only b67f503 Improve ASSERT cd03893 Comments only 4f603db Untab ClosureTypes.h and ClosureFlags.c 9d7cbbc Remove code that generates FunDep error message context 55c703b Move the allocation of CAF blackholes into 'newCAF' (#8590) fe68ad5 Update and deduplicate the comments on CAF management (#8590) 95854ca Use new flushExec implementation on all operating systems (#8562) 47024b6 Made ghc -e have a nonzero exit code upon failure (Trac #7962 ) 415f0d6 Refactored by Simon Marlow's suggestion d9ad369 Fix compiler warnings due to integer size mismatch 9d6f111 Comments, and rename a variable 8b642de Typecheck typed TH splices properly (fix Trac #8577) 0f2a20b Suggest TemplateHaskell after encountering a naked top-level expression 1c69305 Clean up Lexer.srcParseErr 1860dae Suggest TemplateHaskell after encountering a parse error on '$' (#7396) 8157a26 Add `.mailmap` file 980badd Remove the LFBlackHole constructor 8528165 Fix windows x86_64 build. 3f6da56 New flag: -ddump-strsigs a31cb5b Do not forget CPR information after an IO action f64cf13 Rename topDmdType to nopDmdType 3cdf125 Replace mkTopDmdType by mkClosedStrictSig 5e0fe05 Sort the output of -dump-strsigs 289ecda Add more .mailmap entries 7558231 Do not generate given kind-equalities (fix Trac #8566) 0849d02 Better debug printing f114826 Spelling in comment 910b489 Some refactoring of Demand and DmdAnal 7583c20 Do not split void functions c7b9505 Assign strictness signatures to primitive operations 5a92f04 Guarding against silly shifts a9de79f Return exprArity, not manifestArity fe6512d Improve the handling of used-once stuff From git at git.haskell.org Thu Dec 12 12:15:14 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 12 Dec 2013 12:15:14 +0000 (UTC) Subject: [commit: testsuite] branch 'wip/better-ho-cardinality' created Message-ID: <20131212121514.1A0002406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/testsuite New branch : wip/better-ho-cardinality Referencing: b0ef3980d8a8c8b1777d8dbdbdc0aa9b76586774 From git at git.haskell.org Thu Dec 12 12:15:16 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 12 Dec 2013 12:15:16 +0000 (UTC) Subject: [commit: testsuite] wip/better-ho-cardinality: Adjust output to new oneshotness (8f2121b) Message-ID: <20131212121516.409F22406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/testsuite On branch : wip/better-ho-cardinality Link : http://ghc.haskell.org/trac/ghc/changeset/8f2121b513475479e4a8ab15ea23aef03749963d/testsuite >--------------------------------------------------------------- commit 8f2121b513475479e4a8ab15ea23aef03749963d Author: Joachim Breitner Date: Thu Dec 12 11:59:33 2013 +0000 Adjust output to new oneshotness >--------------------------------------------------------------- 8f2121b513475479e4a8ab15ea23aef03749963d tests/deSugar/should_compile/T2431.stderr | 2 +- tests/numeric/should_compile/T7116.stdout | 16 ++++++++------ tests/simplCore/should_compile/T3717.stderr | 4 ++-- tests/simplCore/should_compile/T3772.stdout | 7 +++--- tests/simplCore/should_compile/T4908.stderr | 10 +++++---- tests/simplCore/should_compile/T4930.stderr | 10 +++++---- tests/simplCore/should_compile/T5366.stdout | 3 +-- tests/simplCore/should_compile/T7360.stderr | 13 +++++++---- tests/simplCore/should_compile/T7865.stdout | 4 ++-- tests/simplCore/should_compile/spec-inline.stderr | 24 ++++++++++----------- tests/stranal/sigs/UnsatFun.stderr | 2 +- 11 files changed, 54 insertions(+), 41 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 8f2121b513475479e4a8ab15ea23aef03749963d From git at git.haskell.org Thu Dec 12 12:15:18 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 12 Dec 2013 12:15:18 +0000 (UTC) Subject: [commit: testsuite] wip/better-ho-cardinality: lazy-bs-alloc improved from oneshotness stuff (b0ef398) Message-ID: <20131212121518.673E52406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/testsuite On branch : wip/better-ho-cardinality Link : http://ghc.haskell.org/trac/ghc/changeset/b0ef3980d8a8c8b1777d8dbdbdc0aa9b76586774/testsuite >--------------------------------------------------------------- commit b0ef3980d8a8c8b1777d8dbdbdc0aa9b76586774 Author: Joachim Breitner Date: Thu Dec 12 12:01:04 2013 +0000 lazy-bs-alloc improved from oneshotness stuff >--------------------------------------------------------------- b0ef3980d8a8c8b1777d8dbdbdc0aa9b76586774 tests/perf/should_run/all.T | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/tests/perf/should_run/all.T b/tests/perf/should_run/all.T index 01d358b..a780a26 100644 --- a/tests/perf/should_run/all.T +++ b/tests/perf/should_run/all.T @@ -35,9 +35,10 @@ test('lazy-bs-alloc', [stats_num_field('peak_megabytes_allocated', (2, 1)), # expected value: 2 (amd64/Linux) stats_num_field('bytes allocated', - [(wordsize(64), 429744, 1), + [(wordsize(64), 425400, 1), # 489776 (amd64/Linux) # 2013-02-07: 429744 (amd64/Linux) + # 2013-12-12: 425400 (amd64/Linux) (wordsize(32), 417738, 1)]), # 2013-02-10: 421296 (x86/Windows) # 2013-02-10: 414180 (x86/OSX) From git at git.haskell.org Thu Dec 12 12:15:36 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 12 Dec 2013 12:15:36 +0000 (UTC) Subject: [commit: ghc] wip/better-ho-cardinality: Some refactoring of Demand and DmdAnal (838da6f) Message-ID: <20131212121536.EB30F2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/better-ho-cardinality Link : http://ghc.haskell.org/trac/ghc/changeset/838da6fc74266cf6e561d6ba0cb1c8bd052b4efc/ghc >--------------------------------------------------------------- commit 838da6fc74266cf6e561d6ba0cb1c8bd052b4efc Author: Simon Peyton Jones Date: Wed Dec 11 18:17:04 2013 +0000 Some refactoring of Demand and DmdAnal This was authored by SPJ and extracted from the "Improve the handling of used-once stuff" patch by Joachim. >--------------------------------------------------------------- 838da6fc74266cf6e561d6ba0cb1c8bd052b4efc compiler/basicTypes/Demand.lhs | 225 +++++++++++++++++++--------------------- compiler/coreSyn/CoreUtils.lhs | 11 +- compiler/stranal/DmdAnal.lhs | 31 +++--- compiler/stranal/WorkWrap.lhs | 10 +- 4 files changed, 133 insertions(+), 144 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 838da6fc74266cf6e561d6ba0cb1c8bd052b4efc From git at git.haskell.org Thu Dec 12 12:15:39 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 12 Dec 2013 12:15:39 +0000 (UTC) Subject: [commit: ghc] wip/better-ho-cardinality: Improve the handling of used-once stuff (80989de) Message-ID: <20131212121539.3BB062406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/better-ho-cardinality Link : http://ghc.haskell.org/trac/ghc/changeset/80989de947dc7edb55999456d1c1e8c337efc951/ghc >--------------------------------------------------------------- commit 80989de947dc7edb55999456d1c1e8c337efc951 Author: Simon Peyton Jones Date: Fri Nov 22 17:13:05 2013 +0000 Improve the handling of used-once stuff Joachim and I are committing this onto a branch so that we can share it, but we expect to do a bit more work before merging it onto head. Nofib staus: - Most programs, no change - A few improve - A couple get worse (cacheprof, tak, rfib) Investigating the "get worse" set is what's holding up putting this on head. The major issue is this. Consider map (f g) ys where f's demand signature looks like f :: -> -> . So 'f' is not saturated. What demand do we place on g? Answer C(C1(U)) That is, the inner C1 should stay, even though f is not saturated. I found that this made a significant difference in the demand signatures inferred in GHC.IO, which uses lots of higher-order exception handlers. I also had to add used-once demand signatures for some of the 'catch' primops, so that we know their handlers are only called once. >--------------------------------------------------------------- 80989de947dc7edb55999456d1c1e8c337efc951 compiler/basicTypes/BasicTypes.lhs | 55 ++++++++++++++++++++++++++++ compiler/basicTypes/Demand.lhs | 21 +++++------ compiler/basicTypes/Id.lhs | 64 ++++++++++++++++++++++++--------- compiler/basicTypes/IdInfo.lhs | 70 +++++++++--------------------------- compiler/basicTypes/MkId.lhs | 3 +- compiler/coreSyn/CoreArity.lhs | 45 ++++++++++------------- compiler/coreSyn/PprCore.lhs | 33 ++++++++++------- compiler/simplCore/OccurAnal.lhs | 63 ++++++++++++++++---------------- compiler/simplCore/SetLevels.lhs | 4 ++- compiler/specialise/SpecConstr.lhs | 2 +- compiler/stranal/WorkWrap.lhs | 9 ++--- compiler/stranal/WwLib.lhs | 64 +++++++++++++++++---------------- 12 files changed, 241 insertions(+), 192 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 80989de947dc7edb55999456d1c1e8c337efc951 From git at git.haskell.org Thu Dec 12 12:15:41 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 12 Dec 2013 12:15:41 +0000 (UTC) Subject: [commit: ghc] wip/better-ho-cardinality: Do not split void functions (ba78bf1) Message-ID: <20131212121541.793902406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/better-ho-cardinality Link : http://ghc.haskell.org/trac/ghc/changeset/ba78bf1772c9d695a0ded932eeceed10622d91a4/ghc >--------------------------------------------------------------- commit ba78bf1772c9d695a0ded932eeceed10622d91a4 Author: Simon Peyton Jones Date: Wed Dec 11 18:30:54 2013 +0000 Do not split void functions This is authored by SPJ, and split out out "Improve the handling of used-once stuff" by Joachim. >--------------------------------------------------------------- ba78bf1772c9d695a0ded932eeceed10622d91a4 compiler/stranal/WorkWrap.lhs | 20 +++++++++++++++++++- 1 file changed, 19 insertions(+), 1 deletion(-) diff --git a/compiler/stranal/WorkWrap.lhs b/compiler/stranal/WorkWrap.lhs index b66a449..14a01d5 100644 --- a/compiler/stranal/WorkWrap.lhs +++ b/compiler/stranal/WorkWrap.lhs @@ -17,6 +17,7 @@ import CoreSyn import CoreUnfold ( certainlyWillInline, mkInlineUnfolding, mkWwInlineRule ) import CoreUtils ( exprType, exprIsHNF ) import CoreArity ( exprArity ) +import Type ( isVoidTy ) import Var import Id import IdInfo @@ -256,7 +257,7 @@ tryWW dflags is_rec fn_id rhs -- Furthermore, don't even expose strictness info = return [ (fn_id, rhs) ] - | is_fun && (any worthSplittingArgDmd wrap_dmds || returnsCPR res_info) + | is_fun && (worth_splitting_args wrap_dmds rhs || returnsCPR res_info) = checkSize dflags new_fn_id rhs $ splitFun dflags new_fn_id fn_info wrap_dmds res_info rhs @@ -274,6 +275,12 @@ tryWW dflags is_rec fn_id rhs fn_dmd = demandInfo fn_info inline_act = inlinePragmaActivation (inlinePragInfo fn_info) + worth_splitting_args [d] (Lam b _) + | isAbsDmd d && isVoidTy (idType b) + = False -- Note [Do not split void functions] + worth_splitting_args wrap_dmds _ + = any worthSplittingArgDmd wrap_dmds + -- In practice it always will have a strictness -- signature, even if it's a uninformative one strict_sig = strictnessInfo fn_info @@ -394,6 +401,17 @@ noOneShotInfo :: [Bool] noOneShotInfo = repeat False \end{code} +Note [Do not split void functions] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Consider this rather common form of binding: + $j = \x:Void# -> ...no use of x... + +Since x is not used it'll be marked as absent. But there is no point +in w/w-ing because we'll simply add (\y:Void#), see WwLib.mkWorerArgs. + +If x has a more interesting type (eg Int, or Int#), there *is* a point +in w/w so that we don't pass the argument at all. + Note [Thunk splitting] ~~~~~~~~~~~~~~~~~~~~~~ Suppose x is used strictly (never mind whether it has the CPR From git at git.haskell.org Thu Dec 12 12:15:43 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 12 Dec 2013 12:15:43 +0000 (UTC) Subject: [commit: ghc] wip/better-ho-cardinality: Return exprArity, not manifestArity (b24e0c4) Message-ID: <20131212121544.0542E2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/better-ho-cardinality Link : http://ghc.haskell.org/trac/ghc/changeset/b24e0c4b3f19f87b80b7e23f722bef63018dc7f6/ghc >--------------------------------------------------------------- commit b24e0c4b3f19f87b80b7e23f722bef63018dc7f6 Author: Simon Peyton Jones Date: Wed Dec 11 18:20:21 2013 +0000 Return exprArity, not manifestArity This patch was authored by SPJ, and extracted from "Improve the handling of used-once stuff" by Joachim. >--------------------------------------------------------------- b24e0c4b3f19f87b80b7e23f722bef63018dc7f6 compiler/simplCore/SimplUtils.lhs | 19 ++++++++++++++++--- 1 file changed, 16 insertions(+), 3 deletions(-) diff --git a/compiler/simplCore/SimplUtils.lhs b/compiler/simplCore/SimplUtils.lhs index 6c7dcc2..36f292d 100644 --- a/compiler/simplCore/SimplUtils.lhs +++ b/compiler/simplCore/SimplUtils.lhs @@ -1195,8 +1195,11 @@ tryEtaExpandRhs env bndr rhs = do { dflags <- getDynFlags ; (new_arity, new_rhs) <- try_expand dflags - ; WARN( new_arity < old_arity || new_arity < _dmd_arity, - (ptext (sLit "Arity decrease:") <+> (ppr bndr <+> ppr old_arity + ; WARN( new_arity < old_arity, + (ptext (sLit "Arity decrease:") <+> (ppr bndr + <+> ppr old_arity <+> ppr new_arity) $$ ppr new_rhs) ) + WARN( new_arity < _dmd_arity, + (ptext (sLit "Arity less than dmd sig arity:") <+> (ppr bndr <+> ppr new_arity <+> ppr _dmd_arity) $$ ppr new_rhs) ) -- Note [Arity decrease] return (new_arity, new_rhs) } @@ -1211,13 +1214,23 @@ tryEtaExpandRhs env bndr rhs = do { tick (EtaExpansion bndr) ; return (new_arity, etaExpand new_arity rhs) } | otherwise - = return (manifest_arity, rhs) + = return (exprArity rhs, rhs) -- See Note [Return exprArity, not manifestArity] manifest_arity = manifestArity rhs old_arity = idArity bndr _dmd_arity = length $ fst $ splitStrictSig $ idStrictness bndr \end{code} +Note [Return exprArity, not manifestArity] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Consider + f = \xy. blah + g = f 2 +The f will get arity 2, and we want g to get arity 1, even though +exprEtaExpandArity (and hence findArity) may not eta-expand it. +Hence tryEtaExpand should return (exprArity (f 2)), not its +manifest arity (which is zero). + Note [Eta-expanding at let bindings] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ We now eta expand at let-bindings, which is where the payoff comes. From git at git.haskell.org Thu Dec 12 12:15:46 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 12 Dec 2013 12:15:46 +0000 (UTC) Subject: [commit: ghc] wip/better-ho-cardinality: Assign strictness signatures to primitive operations (0558911) Message-ID: <20131212121546.0522B2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/better-ho-cardinality Link : http://ghc.haskell.org/trac/ghc/changeset/0558911f91ce3433cc3d1d21a43067fa67e2bd79/ghc >--------------------------------------------------------------- commit 0558911f91ce3433cc3d1d21a43067fa67e2bd79 Author: Simon Peyton Jones Date: Wed Dec 11 18:18:53 2013 +0000 Assign strictness signatures to primitive operations This patch was authored by SPJ, and extracted from "Improve the handling of used-once stuff" by Joachim. >--------------------------------------------------------------- 0558911f91ce3433cc3d1d21a43067fa67e2bd79 compiler/basicTypes/Demand.lhs | 7 ++++++- compiler/prelude/primops.txt.pp | 10 ++++++++-- 2 files changed, 14 insertions(+), 3 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index fa706de..ba635fc 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -14,7 +14,7 @@ module Demand ( mkProdDmd, mkOnceUsedDmd, mkManyUsedDmd, mkHeadStrict, oneifyDmd, getUsage, toCleanDmd, absDmd, topDmd, botDmd, seqDmd, - lubDmd, bothDmd, + lubDmd, bothDmd, apply1Dmd, apply2Dmd, isTopDmd, isBotDmd, isAbsDmd, isSeqDmd, peelUseCall, cleanUseDmd_maybe, strictenDmd, bothCleanDmd, @@ -467,6 +467,11 @@ mkJointDmds ss as = zipWithEqual "mkJointDmds" mkJointDmd ss as absDmd :: JointDmd absDmd = mkJointDmd Lazy Abs +apply1Dmd, apply2Dmd :: Demand +-- C1(U), C1(C1(U)) respectively +apply1Dmd = JD { strd = Lazy, absd = Use Many (UCall One Used) } +apply2Dmd = JD { strd = Lazy, absd = Use Many (UCall One (UCall One Used)) } + topDmd :: JointDmd topDmd = mkJointDmd Lazy useTop diff --git a/compiler/prelude/primops.txt.pp b/compiler/prelude/primops.txt.pp index 7457583..b3cf2f4 100644 --- a/compiler/prelude/primops.txt.pp +++ b/compiler/prelude/primops.txt.pp @@ -1618,8 +1618,8 @@ primop CatchOp "catch#" GenPrimOp with -- Catch is actually strict in its first argument -- but we don't want to tell the strictness - -- analyser about that! - -- might use caught action multiply + -- analyser about that, so that exceptions stay inside it. + strictness = { \ _arity -> mkClosedStrictSig [apply1Dmd,apply2Dmd,topDmd] topRes } out_of_line = True has_side_effects = True @@ -1651,6 +1651,7 @@ primop MaskAsyncExceptionsOp "maskAsyncExceptions#" GenPrimOp (State# RealWorld -> (# State# RealWorld, a #)) -> (State# RealWorld -> (# State# RealWorld, a #)) with + strictness = { \ _arity -> mkClosedStrictSig [apply1Dmd,topDmd] topRes } out_of_line = True has_side_effects = True @@ -1658,6 +1659,7 @@ primop MaskUninterruptibleOp "maskUninterruptible#" GenPrimOp (State# RealWorld -> (# State# RealWorld, a #)) -> (State# RealWorld -> (# State# RealWorld, a #)) with + strictness = { \ _arity -> mkClosedStrictSig [apply1Dmd,topDmd] topRes } out_of_line = True has_side_effects = True @@ -1665,6 +1667,7 @@ primop UnmaskAsyncExceptionsOp "unmaskAsyncExceptions#" GenPrimOp (State# RealWorld -> (# State# RealWorld, a #)) -> (State# RealWorld -> (# State# RealWorld, a #)) with + strictness = { \ _arity -> mkClosedStrictSig [apply1Dmd,topDmd] topRes } out_of_line = True has_side_effects = True @@ -1684,6 +1687,7 @@ primop AtomicallyOp "atomically#" GenPrimOp (State# RealWorld -> (# State# RealWorld, a #) ) -> State# RealWorld -> (# State# RealWorld, a #) with + strictness = { \ _arity -> mkClosedStrictSig [apply1Dmd,topDmd] topRes } out_of_line = True has_side_effects = True @@ -1709,6 +1713,7 @@ primop CatchRetryOp "catchRetry#" GenPrimOp -> (State# RealWorld -> (# State# RealWorld, a #) ) -> (State# RealWorld -> (# State# RealWorld, a #) ) with + strictness = { \ _arity -> mkClosedStrictSig [apply1Dmd,apply1Dmd,topDmd] topRes } out_of_line = True has_side_effects = True @@ -1717,6 +1722,7 @@ primop CatchSTMOp "catchSTM#" GenPrimOp -> (b -> State# RealWorld -> (# State# RealWorld, a #) ) -> (State# RealWorld -> (# State# RealWorld, a #) ) with + strictness = { \ _arity -> mkClosedStrictSig [apply1Dmd,apply2Dmd,topDmd] topRes } out_of_line = True has_side_effects = True From git at git.haskell.org Thu Dec 12 12:15:48 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 12 Dec 2013 12:15:48 +0000 (UTC) Subject: [commit: ghc] wip/better-ho-cardinality: Guarding against silly shifts (869f69f) Message-ID: <20131212121548.422482406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/better-ho-cardinality Link : http://ghc.haskell.org/trac/ghc/changeset/869f69fd4a78371c221e6d9abd69a71440a4679a/ghc >--------------------------------------------------------------- commit 869f69fd4a78371c221e6d9abd69a71440a4679a Author: Simon Peyton Jones Date: Wed Dec 11 18:19:34 2013 +0000 Guarding against silly shifts This patch was authored by SPJ and extracted from "Improve the handling of used-once stuff" by Joachim. >--------------------------------------------------------------- 869f69fd4a78371c221e6d9abd69a71440a4679a compiler/prelude/PrelRules.lhs | 80 ++++++++++++++++++++++++++++++++++------ 1 file changed, 68 insertions(+), 12 deletions(-) diff --git a/compiler/prelude/PrelRules.lhs b/compiler/prelude/PrelRules.lhs index b6ded2e..11367ed 100644 --- a/compiler/prelude/PrelRules.lhs +++ b/compiler/prelude/PrelRules.lhs @@ -141,10 +141,8 @@ primOpRules nm OrOp = mkPrimOpRule nm 2 [ binaryLit (wordOp2 (.|.)) primOpRules nm XorOp = mkPrimOpRule nm 2 [ binaryLit (wordOp2 xor) , identityDynFlags zerow , equalArgs >> retLit zerow ] -primOpRules nm SllOp = mkPrimOpRule nm 2 [ binaryLit (wordShiftOp2 Bits.shiftL) - , rightIdentityDynFlags zeroi ] -primOpRules nm SrlOp = mkPrimOpRule nm 2 [ binaryLit (wordShiftOp2 shiftRightLogical) - , rightIdentityDynFlags zeroi ] +primOpRules nm SllOp = mkPrimOpRule nm 2 [ wordShiftRule Bits.shiftL ] +primOpRules nm SrlOp = mkPrimOpRule nm 2 [ wordShiftRule shiftRightLogical ] -- coercions primOpRules nm Word2IntOp = mkPrimOpRule nm 1 [ liftLitDynFlags word2IntLit @@ -373,14 +371,25 @@ wordOp2 op dflags (MachWord w1) (MachWord w2) = wordResult dflags (fromInteger w1 `op` fromInteger w2) wordOp2 _ _ _ _ = Nothing -- Could find LitLit -wordShiftOp2 :: (Integer -> Int -> Integer) - -> DynFlags -> Literal -> Literal - -> Maybe CoreExpr --- Shifts take an Int; hence second arg of op is Int -wordShiftOp2 op dflags (MachWord x) (MachInt n) - = wordResult dflags (x `op` fromInteger n) - -- Do the shift at type Integer -wordShiftOp2 _ _ _ _ = Nothing +wordShiftRule :: (Integer -> Int -> Integer) -> RuleM CoreExpr + -- Shifts take an Int; hence second arg of op is Int +-- See Note [Guarding against silly shifts] +wordShiftRule shift_op + = do { dflags <- getDynFlags + ; [e1, Lit (MachInt shift_len)] <- getArgs + ; case e1 of + _ | shift_len == 0 + -> return e1 + | shift_len < 0 || wordSizeInBits dflags < shift_len + -> return (mkRuntimeErrorApp rUNTIME_ERROR_ID wordPrimTy + ("Bad shift length" ++ show shift_len)) + Lit (MachWord x) + -> liftMaybe $ wordResult dflags (x `shift_op` fromInteger shift_len) + -- Do the shift at type Integer, but shift length is Int + _ -> mzero } + +wordSizeInBits :: DynFlags -> Integer +wordSizeInBits dflags = toInteger (platformWordSize (targetPlatform dflags) `shiftL` 3) -------------------------- floatOp2 :: (Rational -> Rational -> Rational) @@ -522,6 +531,53 @@ idempotent = do [e1, e2] <- getArgs return e1 \end{code} +Note [Guarding against silly shifts] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Consider this code: + + import Data.Bits( (.|.), shiftL ) + chunkToBitmap :: [Bool] -> Word32 + chunkToBitmap chunk = foldr (.|.) 0 [ 1 `shiftL` n | (True,n) <- zip chunk [0..] ] + +This optimises to: +Shift.$wgo = \ (w_sCS :: GHC.Prim.Int#) (w1_sCT :: [GHC.Types.Bool]) -> + case w1_sCT of _ { + [] -> __word 0; + : x_aAW xs_aAX -> + case x_aAW of _ { + GHC.Types.False -> + case w_sCS of wild2_Xh { + __DEFAULT -> Shift.$wgo (GHC.Prim.+# wild2_Xh 1) xs_aAX; + 9223372036854775807 -> __word 0 }; + GHC.Types.True -> + case GHC.Prim.>=# w_sCS 64 of _ { + GHC.Types.False -> + case w_sCS of wild3_Xh { + __DEFAULT -> + case Shift.$wgo (GHC.Prim.+# wild3_Xh 1) xs_aAX of ww_sCW { __DEFAULT -> + GHC.Prim.or# (GHC.Prim.narrow32Word# + (GHC.Prim.uncheckedShiftL# (__word 1) wild3_Xh)) + ww_sCW + }; + 9223372036854775807 -> + GHC.Prim.narrow32Word# +!!!!--> (GHC.Prim.uncheckedShiftL# (__word 1) 9223372036854775807) + }; + GHC.Types.True -> + case w_sCS of wild3_Xh { + __DEFAULT -> Shift.$wgo (GHC.Prim.+# wild3_Xh 1) xs_aAX; + 9223372036854775807 -> __word 0 + } } } } + +Note the massive shift on line "!!!!". It can't happen, because we've checked +that w < 64, but the optimiser didn't spot that. We DO NO want to constant-fold this! +Moreover, if the programmer writes (n `uncheckedShiftL` 9223372036854775807), we +can't constant fold it, but if it gets to the assember we get + Error: operand type mismatch for `shl' + +So the best thing to do is to rewrite the shift with a call to error, +when the second arg is stupid. + %************************************************************************ %* * \subsection{Vaguely generic functions} From git at git.haskell.org Thu Dec 12 15:01:49 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 12 Dec 2013 15:01:49 +0000 (UTC) Subject: [commit: testsuite] branch 'wip/better-ho-cardinality' deleted Message-ID: <20131212150149.6FEEE2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/testsuite Deleted branch: wip/better-ho-cardinality From git at git.haskell.org Thu Dec 12 15:03:48 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 12 Dec 2013 15:03:48 +0000 (UTC) Subject: [commit: testsuite] master: Adjust output to new oneshotness (b2cfd0e) Message-ID: <20131212150348.8F0C52406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/testsuite On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b2cfd0ebdca9efc8297b8afc491c7ccf71f1a3ea/testsuite >--------------------------------------------------------------- commit b2cfd0ebdca9efc8297b8afc491c7ccf71f1a3ea Author: Joachim Breitner Date: Thu Dec 12 11:59:33 2013 +0000 Adjust output to new oneshotness >--------------------------------------------------------------- b2cfd0ebdca9efc8297b8afc491c7ccf71f1a3ea tests/deSugar/should_compile/T2431.stderr | 2 +- tests/numeric/should_compile/T7116.stdout | 16 ++++++++------ tests/simplCore/should_compile/T3717.stderr | 4 ++-- tests/simplCore/should_compile/T3772.stdout | 7 +++--- tests/simplCore/should_compile/T4908.stderr | 10 +++++---- tests/simplCore/should_compile/T4930.stderr | 10 +++++---- tests/simplCore/should_compile/T5366.stdout | 3 +-- tests/simplCore/should_compile/T7360.stderr | 13 +++++++---- tests/simplCore/should_compile/T7865.stdout | 4 ++-- tests/simplCore/should_compile/spec-inline.stderr | 24 ++++++++++----------- tests/stranal/sigs/UnsatFun.stderr | 2 +- 11 files changed, 54 insertions(+), 41 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 b2cfd0ebdca9efc8297b8afc491c7ccf71f1a3ea From git at git.haskell.org Thu Dec 12 15:03:50 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 12 Dec 2013 15:03:50 +0000 (UTC) Subject: [commit: testsuite] master: lazy-bs-alloc improved from oneshotness stuff (5144942) Message-ID: <20131212150350.6DBCE2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/testsuite On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/514494212979ad4abf3e3b4e3256550e9c924175/testsuite >--------------------------------------------------------------- commit 514494212979ad4abf3e3b4e3256550e9c924175 Author: Joachim Breitner Date: Thu Dec 12 12:01:04 2013 +0000 lazy-bs-alloc improved from oneshotness stuff >--------------------------------------------------------------- 514494212979ad4abf3e3b4e3256550e9c924175 tests/perf/should_run/all.T | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/tests/perf/should_run/all.T b/tests/perf/should_run/all.T index 01d358b..a780a26 100644 --- a/tests/perf/should_run/all.T +++ b/tests/perf/should_run/all.T @@ -35,9 +35,10 @@ test('lazy-bs-alloc', [stats_num_field('peak_megabytes_allocated', (2, 1)), # expected value: 2 (amd64/Linux) stats_num_field('bytes allocated', - [(wordsize(64), 429744, 1), + [(wordsize(64), 425400, 1), # 489776 (amd64/Linux) # 2013-02-07: 429744 (amd64/Linux) + # 2013-12-12: 425400 (amd64/Linux) (wordsize(32), 417738, 1)]), # 2013-02-10: 421296 (x86/Windows) # 2013-02-10: 414180 (x86/OSX) From git at git.haskell.org Thu Dec 12 15:03:52 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 12 Dec 2013 15:03:52 +0000 (UTC) Subject: [commit: testsuite] master: Update compiler performance values (8d6c941) Message-ID: <20131212150352.730A02406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/testsuite On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8d6c94122aa63e1c74f44f4b5b5895785f8847b3/testsuite >--------------------------------------------------------------- commit 8d6c94122aa63e1c74f44f4b5b5895785f8847b3 Author: Joachim Breitner Date: Thu Dec 12 14:22:35 2013 +0000 Update compiler performance values >--------------------------------------------------------------- 8d6c94122aa63e1c74f44f4b5b5895785f8847b3 tests/perf/compiler/all.T | 10 +++++++--- tests/perf/haddock/all.T | 8 +++++--- 2 files changed, 12 insertions(+), 6 deletions(-) diff --git a/tests/perf/compiler/all.T b/tests/perf/compiler/all.T index abc9758..ea5807e 100644 --- a/tests/perf/compiler/all.T +++ b/tests/perf/compiler/all.T @@ -129,13 +129,15 @@ test('T3294', # previous: 815479800 (x86/Linux) # (^ increase due to new codegen, see #7198) # 2012-10-08: 1373514844 (x86/Linux) - (wordsize(64), 2901451552, 5)]), + (wordsize(64), 3083825616, 5)]), # old: 1357587088 (amd64/Linux) # 29/08/2012: 2961778696 (amd64/Linux) # (^ increase due to new codegen, see #7198) # 18/09/2012: 2717327208 (amd64/Linux) # 08/06/2013: 2901451552 (amd64/Linux) # (^ reason unknown) + # 12/12/2013: 3083825616 (amd64/Linux) + # (^ reason unknown) conf_3294 ], compile, @@ -217,7 +219,7 @@ test('T3064', compiler_stats_num_field('max_bytes_used', [(wordsize(32), 5511604, 20), # expected value: 2247016 (x86/Linux) (28/6/2011): - (wordsize(64), 16266992, 20)]), + (wordsize(64), 19821544, 20)]), # (amd64/Linux, intree) (28/06/2011): 4032024 # (amd64/Linux, intree) (07/02/2013): 9819288 # (amd64/Linux) (14/02/2013): 8687360 @@ -227,6 +229,7 @@ test('T3064', # (amd64/Linux) (11/09/2013): 12000480, increase from AMP warnings # 933cdf15a2d85229d3df04b437da31fdfbf4961f # (amd64/Linux) (22/11/2013): 16266992, GND via Coercible and counters for constraints solving + # (amd64/Linux) (12/12/2013): 19821544, better One shot analysis only_ways(['normal']) ], compile, @@ -262,8 +265,9 @@ test('T5631', [compiler_stats_num_field('bytes allocated', [(wordsize(32), 392904228, 10), # expected value: 392904228 (x86/Linux) - (wordsize(64), 774595008, 5)]), + (wordsize(64), 735486328, 5)]), # expected value: 774595008 (amd64/Linux): + # expected value: 735486328 (amd64/Linux) 2012/12/12: only_ways(['normal']) ], compile, diff --git a/tests/perf/haddock/all.T b/tests/perf/haddock/all.T index 21cd6a8..c50f670 100644 --- a/tests/perf/haddock/all.T +++ b/tests/perf/haddock/all.T @@ -75,7 +75,7 @@ test('haddock.Cabal', # 2012-08-14: 47461532 (x86/OSX) # 2013-02-10: 46563344 (x86/OSX) ,stats_num_field('bytes allocated', - [(wordsize(64), 3908586784, 2) + [(wordsize(64), 3828567272, 2) # 2012-08-14: 3255435248 (amd64/Linux) # 2012-08-29: 3324606664 (amd64/Linux, new codegen) # 2012-10-08: 3373401360 (amd64/Linux) @@ -83,7 +83,8 @@ test('haddock.Cabal', # 2013-03-28: 3517301864 (amd64/Linux) fixed #7796 # 2013-04-26: 3658801800 (amd64/Linux) Cabal updated # 2013-08-26: 3808466816 (amd64/Linux) Cabal updated - # 2013-21-11: 3908586784 (amd64/Linux) Cabal updated + # 2013-11-21: 3908586784 (amd64/Linux) Cabal updated + # 2013-12-12: 3828567272 (amd64/Linux) ,(platform('i386-unknown-mingw32'), 1906532680, 1) # 2012-10-30: 1733638168 (x86/Windows) # 2013-02-10: 1906532680 (x86/Windows) @@ -96,13 +97,14 @@ test('haddock.Cabal', test('haddock.compiler', [unless(in_tree_compiler(), skip) ,stats_num_field('peak_megabytes_allocated', - [(wordsize(64), 1408, 10) + [(wordsize(64), 1551, 10) # 2012-08-14: 1203 (amd64/Linux) # 2012-08-21: 1199 (amd64/Linux) # 2012-09-20: 1228 (amd64/Linux) # 2012-10-08: 1240 (amd64/Linux) # 2013-08-26: 1250 (amd64/Linux) Cabal updated # 2013-10-18: 1408 (amd64/Linux) + # 2013-12-12: 1551 (amd64/Linux) ,(platform('i386-unknown-mingw32'), 653, 1) # 2012-10-30: 606 (x86/Windows) # 2013-02-10: 653 (x86/Windows) From git at git.haskell.org Thu Dec 12 15:04:44 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 12 Dec 2013 15:04:44 +0000 (UTC) Subject: [commit: ghc] branch 'wip/exprArity' created Message-ID: <20131212150444.78D882406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/exprArity Referencing: b24e0c4b3f19f87b80b7e23f722bef63018dc7f6 From git at git.haskell.org Thu Dec 12 15:04:46 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 12 Dec 2013 15:04:46 +0000 (UTC) Subject: [commit: ghc] branch 'wip/better-ho-cardinality' deleted Message-ID: <20131212150446.76DCD2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Deleted branch: wip/better-ho-cardinality From git at git.haskell.org Thu Dec 12 15:04:48 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 12 Dec 2013 15:04:48 +0000 (UTC) Subject: [commit: ghc] master's head updated: Improve the handling of used-once stuff (80989de) Message-ID: <20131212150448.D67522406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'master' now includes: 838da6f Some refactoring of Demand and DmdAnal ba78bf1 Do not split void functions 0558911 Assign strictness signatures to primitive operations 869f69f Guarding against silly shifts 80989de Improve the handling of used-once stuff From git at git.haskell.org Thu Dec 12 17:56:28 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 12 Dec 2013 17:56:28 +0000 (UTC) Subject: [commit: testsuite] wip/nested-cpr: Update CPR output (different pretty printing for product types) (9e773d9) Message-ID: <20131212175628.D97B12406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/testsuite On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/9e773d9f419847178ca2c4908ba8c6dbdbec6234/testsuite >--------------------------------------------------------------- commit 9e773d9f419847178ca2c4908ba8c6dbdbec6234 Author: Joachim Breitner Date: Tue Dec 10 11:55:56 2013 +0000 Update CPR output (different pretty printing for product types) >--------------------------------------------------------------- 9e773d9f419847178ca2c4908ba8c6dbdbec6234 tests/numeric/should_compile/T7116.stdout | 8 ++++---- tests/simplCore/should_compile/T3717.stderr | 2 +- tests/simplCore/should_compile/T4201.stdout | 2 +- tests/simplCore/should_compile/T4930.stderr | 2 +- tests/simplCore/should_compile/T7360.stderr | 4 ++-- tests/simplCore/should_compile/spec-inline.stderr | 8 ++++---- tests/stranal/sigs/FacState.stderr | 2 +- tests/stranal/sigs/HyperStrUse.stderr | 2 +- tests/stranal/sigs/T8598.stderr | 2 +- 9 files changed, 16 insertions(+), 16 deletions(-) diff --git a/tests/numeric/should_compile/T7116.stdout b/tests/numeric/should_compile/T7116.stdout index 79b4bf3..936ff9e 100644 --- a/tests/numeric/should_compile/T7116.stdout +++ b/tests/numeric/should_compile/T7116.stdout @@ -6,7 +6,7 @@ T7116.dl :: GHC.Types.Double -> GHC.Types.Double [GblId, Arity=1, Caf=NoCafRefs, - Str=DmdType tm1(d), + Str=DmdType tm(d), Unf=Unf{Src=InlineStable, TopLvl=True, Arity=1, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(unsat_ok=True,boring_ok=False) @@ -24,7 +24,7 @@ T7116.dr :: GHC.Types.Double -> GHC.Types.Double [GblId, Arity=1, Caf=NoCafRefs, - Str=DmdType tm1(d), + Str=DmdType tm(d), Unf=Unf{Src=InlineStable, TopLvl=True, Arity=1, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(unsat_ok=True,boring_ok=False) @@ -38,7 +38,7 @@ T7116.fl :: GHC.Types.Float -> GHC.Types.Float [GblId, Arity=1, Caf=NoCafRefs, - Str=DmdType tm1(d), + Str=DmdType tm(d), Unf=Unf{Src=InlineStable, TopLvl=True, Arity=1, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(unsat_ok=True,boring_ok=False) @@ -56,7 +56,7 @@ T7116.fr :: GHC.Types.Float -> GHC.Types.Float [GblId, Arity=1, Caf=NoCafRefs, - Str=DmdType tm1(d), + Str=DmdType tm(d), Unf=Unf{Src=InlineStable, TopLvl=True, Arity=1, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(unsat_ok=True,boring_ok=False) diff --git a/tests/simplCore/should_compile/T3717.stderr b/tests/simplCore/should_compile/T3717.stderr index 753d081..50f9ed6 100644 --- a/tests/simplCore/should_compile/T3717.stderr +++ b/tests/simplCore/should_compile/T3717.stderr @@ -17,7 +17,7 @@ T3717.foo [InlPrag=INLINE[0]] :: GHC.Types.Int -> GHC.Types.Int [GblId, Arity=1, Caf=NoCafRefs, - Str=DmdType dm1(d), + Str=DmdType dm(d), Unf=Unf{Src=InlineStable, TopLvl=True, Arity=1, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(unsat_ok=True,boring_ok=False) diff --git a/tests/simplCore/should_compile/T4201.stdout b/tests/simplCore/should_compile/T4201.stdout index 622276d..201cfe7 100644 --- a/tests/simplCore/should_compile/T4201.stdout +++ b/tests/simplCore/should_compile/T4201.stdout @@ -1,3 +1,3 @@ - {- Arity: 1, HasNoCafRefs, Strictness: tm1(), + {- Arity: 1, HasNoCafRefs, Strictness: tm(), Unfolding: InlineRule (0, True, True) Eta.bof `cast` (Sym (Eta.NTCo:Foo[0]) ->_R _R) -} diff --git a/tests/simplCore/should_compile/T4930.stderr b/tests/simplCore/should_compile/T4930.stderr index e9f2965..e38bdec 100644 --- a/tests/simplCore/should_compile/T4930.stderr +++ b/tests/simplCore/should_compile/T4930.stderr @@ -13,7 +13,7 @@ T4930.foo1 = GHC.Err.error @ GHC.Types.Int lvl T4930.foo :: GHC.Types.Int -> GHC.Types.Int [GblId, Arity=1, - Str=DmdType dm1(d), + Str=DmdType dm(d), Unf=Unf{Src=InlineStable, TopLvl=True, Arity=1, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(unsat_ok=True,boring_ok=False) diff --git a/tests/simplCore/should_compile/T7360.stderr b/tests/simplCore/should_compile/T7360.stderr index 4828efc..4e4e387 100644 --- a/tests/simplCore/should_compile/T7360.stderr +++ b/tests/simplCore/should_compile/T7360.stderr @@ -37,7 +37,7 @@ T7360.fun4 = T7360.fun1 T7360.Foo1 T7360.fun3 :: GHC.Types.Int [GblId, Caf=NoCafRefs, - Str=DmdType tm1(d), + Str=DmdType tm(d), Unf=Unf{Src=, TopLvl=True, Arity=0, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}] @@ -46,7 +46,7 @@ T7360.fun3 = GHC.Types.I# 0 T7360.fun2 :: forall a. [a] -> ((), GHC.Types.Int) [GblId, Arity=1, - Str=DmdType tm1(d,dm1(d)), + Str=DmdType tm(d,dm(d)), Unf=Unf{Src=InlineStable, TopLvl=True, Arity=1, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(unsat_ok=True,boring_ok=False) diff --git a/tests/simplCore/should_compile/spec-inline.stderr b/tests/simplCore/should_compile/spec-inline.stderr index c0a7b58..4b46257 100644 --- a/tests/simplCore/should_compile/spec-inline.stderr +++ b/tests/simplCore/should_compile/spec-inline.stderr @@ -98,7 +98,7 @@ Roman.foo_go [InlPrag=INLINE[0]] -> Data.Maybe.Maybe GHC.Types.Int -> GHC.Types.Int [GblId, Arity=2, - Str=DmdType dm1(d), + Str=DmdType dm(d), Unf=Unf{Src=InlineStable, TopLvl=True, Arity=2, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(unsat_ok=True,boring_ok=False) @@ -113,7 +113,7 @@ Roman.foo_go = Roman.foo2 :: GHC.Types.Int [GblId, Caf=NoCafRefs, - Str=DmdType tm1(d), + Str=DmdType tm(d), Unf=Unf{Src=, TopLvl=True, Arity=0, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}] @@ -122,7 +122,7 @@ Roman.foo2 = GHC.Types.I# 6 Roman.foo1 :: Data.Maybe.Maybe GHC.Types.Int [GblId, Caf=NoCafRefs, - Str=DmdType tm2(tm1(d)), + Str=DmdType tm2(d), Unf=Unf{Src=, TopLvl=True, Arity=0, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}] @@ -132,7 +132,7 @@ Roman.foo :: GHC.Types.Int -> GHC.Types.Int [GblId, Arity=1, Caf=NoCafRefs, - Str=DmdType dm1(d), + Str=DmdType dm(d), Unf=Unf{Src=InlineStable, TopLvl=True, Arity=1, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(unsat_ok=True,boring_ok=False) diff --git a/tests/stranal/sigs/FacState.stderr b/tests/stranal/sigs/FacState.stderr index 133ad6e..18a551d 100644 --- a/tests/stranal/sigs/FacState.stderr +++ b/tests/stranal/sigs/FacState.stderr @@ -1,5 +1,5 @@ ==================== Strictness signatures ==================== -FacState.fac: dm1(d,tm1(d)) +FacState.fac: dm(d,tm(d)) diff --git a/tests/stranal/sigs/HyperStrUse.stderr b/tests/stranal/sigs/HyperStrUse.stderr index f102bb5..c6f02b1 100644 --- a/tests/stranal/sigs/HyperStrUse.stderr +++ b/tests/stranal/sigs/HyperStrUse.stderr @@ -1,5 +1,5 @@ ==================== Strictness signatures ==================== -HyperStrUse.f: dm1(d) +HyperStrUse.f: dm(d) diff --git a/tests/stranal/sigs/T8598.stderr b/tests/stranal/sigs/T8598.stderr index ec63d52..a59be7b 100644 --- a/tests/stranal/sigs/T8598.stderr +++ b/tests/stranal/sigs/T8598.stderr @@ -1,5 +1,5 @@ ==================== Strictness signatures ==================== -T8598.fun: dm1(d) +T8598.fun: dm(d) From git at git.haskell.org Thu Dec 12 17:56:30 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 12 Dec 2013 17:56:30 +0000 (UTC) Subject: [commit: testsuite] wip/nested-cpr: Test output update: Nested CPR signatures (2615aae) Message-ID: <20131212175631.61C612406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/testsuite On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/2615aaee9d660ba57290bbcacddaff101c93e991/testsuite >--------------------------------------------------------------- commit 2615aaee9d660ba57290bbcacddaff101c93e991 Author: Joachim Breitner Date: Tue Dec 3 17:08:50 2013 +0000 Test output update: Nested CPR signatures >--------------------------------------------------------------- 2615aaee9d660ba57290bbcacddaff101c93e991 tests/numeric/should_compile/T7116.stdout | 8 ++++---- tests/simplCore/should_compile/T3717.stderr | 10 +++++----- tests/simplCore/should_compile/T4201.stdout | 2 +- tests/simplCore/should_compile/T4908.stderr | 6 +++--- tests/simplCore/should_compile/T4918.stdout | 4 ++-- tests/simplCore/should_compile/T4930.stderr | 2 +- tests/simplCore/should_compile/T7360.stderr | 6 +++--- tests/simplCore/should_compile/spec-inline.stderr | 8 ++++---- tests/stranal/sigs/HyperStrUse.stderr | 2 +- tests/stranal/sigs/T8598.stderr | 2 +- tests/stranal/sigs/all.T | 2 +- 11 files changed, 26 insertions(+), 26 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 2615aaee9d660ba57290bbcacddaff101c93e991 From git at git.haskell.org Thu Dec 12 17:56:33 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 12 Dec 2013 17:56:33 +0000 (UTC) Subject: [commit: testsuite] wip/nested-cpr: Nested CPR example: Extended Euclidean algorithm (7a8bace) Message-ID: <20131212175633.50E102406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/testsuite On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/7a8bacec3a42b3b3f46911d8c22c1768a4fb0844/testsuite >--------------------------------------------------------------- commit 7a8bacec3a42b3b3f46911d8c22c1768a4fb0844 Author: Joachim Breitner Date: Tue Dec 10 11:51:55 2013 +0000 Nested CPR example: Extended Euclidean algorithm >--------------------------------------------------------------- 7a8bacec3a42b3b3f46911d8c22c1768a4fb0844 tests/stranal/sigs/ExtendedEu.hs | 10 ++++++++++ tests/stranal/sigs/{FacState.stderr => ExtendedEu.stderr} | 2 +- tests/stranal/sigs/all.T | 1 + 3 files changed, 12 insertions(+), 1 deletion(-) diff --git a/tests/stranal/sigs/ExtendedEu.hs b/tests/stranal/sigs/ExtendedEu.hs new file mode 100644 index 0000000..115a976 --- /dev/null +++ b/tests/stranal/sigs/ExtendedEu.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE BangPatterns #-} + +module ExtendedEu where + +extendedEu :: Int -> Int -> (Int, Int) +extendedEu a 0 = (1, 0) +extendedEu a b = let b' = s - q * t + in b' `seq` (t, b') + where (q, r) = quotRem a b + (s, t) = extendedEu b r diff --git a/tests/stranal/sigs/FacState.stderr b/tests/stranal/sigs/ExtendedEu.stderr similarity index 51% copy from tests/stranal/sigs/FacState.stderr copy to tests/stranal/sigs/ExtendedEu.stderr index 18a551d..f45ba12 100644 --- a/tests/stranal/sigs/FacState.stderr +++ b/tests/stranal/sigs/ExtendedEu.stderr @@ -1,5 +1,5 @@ ==================== Strictness signatures ==================== -FacState.fac: dm(d,tm(d)) +ExtendedEu.extendedEu: dm(tm(d),tm(d)) diff --git a/tests/stranal/sigs/all.T b/tests/stranal/sigs/all.T index 3681fb7..84273a6 100644 --- a/tests/stranal/sigs/all.T +++ b/tests/stranal/sigs/all.T @@ -13,3 +13,4 @@ test('HyperStrUse', normal, compile, ['']) test('T8598', normal, compile, ['']) test('FacState', normal, compile, ['']) test('UnsatFun', normal, compile, ['']) +test('ExtendedEu', normal, compile, ['']) From git at git.haskell.org Thu Dec 12 17:56:35 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 12 Dec 2013 17:56:35 +0000 (UTC) Subject: [commit: testsuite] wip/nested-cpr's head updated: Nested CPR example: Extended Euclidean algorithm (7a8bace) Message-ID: <20131212175635.523542406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/testsuite Branch 'wip/nested-cpr' now includes: 3144b8f Sort the output of -dump-strsigs a6e35a0 Test Trac #8566 b2cfd0e Adjust output to new oneshotness 5144942 lazy-bs-alloc improved from oneshotness stuff 8d6c941 Update compiler performance values 2615aae Test output update: Nested CPR signatures 9e773d9 Update CPR output (different pretty printing for product types) 7a8bace Nested CPR example: Extended Euclidean algorithm From git at git.haskell.org Thu Dec 12 17:56:52 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 12 Dec 2013 17:56:52 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Move peelFV from DmdAnal to Demand (6b6a30d) Message-ID: <20131212175653.4B1A72406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/6b6a30d6b65e8cc563b3cad5f53cf6af75caee4c/ghc >--------------------------------------------------------------- commit 6b6a30d6b65e8cc563b3cad5f53cf6af75caee4c Author: Joachim Breitner Date: Wed Dec 4 16:09:34 2013 +0000 Move peelFV from DmdAnal to Demand >--------------------------------------------------------------- 6b6a30d6b65e8cc563b3cad5f53cf6af75caee4c compiler/basicTypes/Demand.lhs | 19 ++++++++++++++++++- compiler/stranal/DmdAnal.lhs | 31 ++++++++++--------------------- 2 files changed, 28 insertions(+), 22 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 33d4bb6..50b6f94 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -20,8 +20,10 @@ module Demand ( DmdType(..), dmdTypeDepth, lubDmdType, bothDmdEnv, bothDmdType, nopDmdType, botDmdType, mkDmdType, + addDemand, DmdEnv, emptyDmdEnv, + peelFV, DmdResult, CPRResult, isBotRes, isTopRes, resTypeArgDmd, @@ -55,12 +57,13 @@ module Demand ( import StaticFlags import DynFlags import Outputable +import Var ( Var ) import VarEnv import UniqFM import Util import BasicTypes import Binary -import Maybes ( isJust, expectJust ) +import Maybes ( isJust, expectJust, orElse ) import Type ( Type ) import TyCon ( isNewTyCon, isClassTyCon ) @@ -1151,6 +1154,20 @@ peelManyCalls arg_ds (CD { sd = str, ud = abs }) go_abs [] _ = One -- one UCall Many in the demand go_abs (_:as) (UCall One d') = go_abs as d' go_abs _ _ = Many + + +peelFV :: DmdType -> Var -> (DmdType, Demand) +peelFV (DmdType fv ds res) id = -- pprTrace "rfv" (ppr id <+> ppr dmd $$ ppr fv) + (DmdType fv' ds res, dmd) + where + fv' = fv `delVarEnv` id + dmd = lookupVarEnv fv id `orElse` deflt + -- See note [Default demand for variables] + deflt | isBotRes res = botDmd + | otherwise = absDmd + +addDemand :: Demand -> DmdType -> DmdType +addDemand dmd (DmdType fv ds res) = DmdType fv (dmd:ds) res \end{code} Note [Always analyse in virgin pass] diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index 27d9112..8a2cf4c 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -32,7 +32,7 @@ import Type ( eqType ) -- import Pair -- import Coercion ( coercionKind ) import Util -import Maybes ( isJust, orElse ) +import Maybes ( isJust ) import TysWiredIn ( unboxedPairDataCon ) import TysPrim ( realWorldStatePrimTy ) import ErrUtils ( dumpIfSet_dyn ) @@ -726,16 +726,6 @@ addLazyFVs dmd_ty lazy_fvs -- which floats out of the defn for h. Without the modifyEnv, that -- L demand doesn't get both'd with the Bot coming up from the inner -- call to f. So we just get an L demand for x for g. - -peelFV :: DmdEnv -> Var -> DmdResult -> (DmdEnv, Demand) -peelFV fv id res = -- pprTrace "rfv" (ppr id <+> ppr dmd $$ ppr fv) - (fv', dmd) - where - fv' = fv `delVarEnv` id - dmd = lookupVarEnv fv id `orElse` deflt - -- See note [Default demand for variables] - deflt | isBotRes res = botDmd - | otherwise = absDmd \end{code} Note [Default demand for variables] @@ -761,11 +751,11 @@ annotateBndr :: AnalEnv -> DmdType -> Var -> (DmdType, Var) -- The returned var is annotated with demand info -- according to the result demand of the provided demand type -- No effect on the argument demands -annotateBndr env dmd_ty@(DmdType fv ds res) var +annotateBndr env dmd_ty var | isTyVar var = (dmd_ty, var) - | otherwise = (DmdType fv' ds res, set_idDemandInfo env var dmd') + | otherwise = (dmd_ty', set_idDemandInfo env var dmd') where - (fv', dmd) = peelFV fv var res + (dmd_ty', dmd) = peelFV dmd_ty var dmd' | gopt Opt_DictsStrict (ae_dflags env) -- We never want to strictify a recursive let. At the moment @@ -786,13 +776,13 @@ annotateLamBndrs env args_of_dfun ty bndrs = mapAccumR annotate ty bndrs annotateLamIdBndr :: AnalEnv -> DFunFlag -- is this lambda at the top of the RHS of a dfun? - -> DmdType -- Demand type of body + -> DmdType -- Demand type of body -> Count -- One-shot-ness of the lambda - -> Id -- Lambda binder - -> (DmdType, -- Demand type of lambda + -> Id -- Lambda binder + -> (DmdType, -- Demand type of lambda Id) -- and binder annotated with demand -annotateLamIdBndr env arg_of_dfun _dmd_ty@(DmdType fv ds res) one_shot id +annotateLamIdBndr env arg_of_dfun dmd_ty one_shot id -- For lambdas we add the demand to the argument demands -- Only called for Ids = ASSERT( isId id ) @@ -806,9 +796,8 @@ annotateLamIdBndr env arg_of_dfun _dmd_ty@(DmdType fv ds res) one_shot id where (unf_ty, _) = dmdAnalStar env dmd unf - main_ty = DmdType fv' (dmd:ds) res - - (fv', dmd) = peelFV fv id res + main_ty = addDemand dmd dmd_ty' + (dmd_ty', dmd) = peelFV dmd_ty id dmd' | gopt Opt_DictsStrict (ae_dflags env), -- see Note [do not strictify the argument dictionaries of a dfun] From git at git.haskell.org Thu Dec 12 17:56:54 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 12 Dec 2013 17:56:54 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Add Note [non-algebraic or open body type warning] (6de91c9) Message-ID: <20131212175655.1B88F2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/6de91c96648e7f4196196223261c3ba7013e357a/ghc >--------------------------------------------------------------- commit 6de91c96648e7f4196196223261c3ba7013e357a Author: Joachim Breitner Date: Wed Dec 4 17:12:07 2013 +0000 Add Note [non-algebraic or open body type warning] >--------------------------------------------------------------- 6de91c96648e7f4196196223261c3ba7013e357a compiler/stranal/WwLib.lhs | 20 ++++++++++++++++++++ 1 file changed, 20 insertions(+) diff --git a/compiler/stranal/WwLib.lhs b/compiler/stranal/WwLib.lhs index fc94c9b..4acf255 100644 --- a/compiler/stranal/WwLib.lhs +++ b/compiler/stranal/WwLib.lhs @@ -540,6 +540,7 @@ mkWWcpr body_ty res Just con_tag | Just stuff <- deepSplitCprType_maybe con_tag body_ty -> mkWWcpr_help stuff | otherwise + -- See Note [non-algebraic or open body type warning] -> WARN( True, text "mkWWcpr: non-algebraic or open body type" <+> ppr body_ty ) return (id, id, body_ty) @@ -590,6 +591,25 @@ mkUnpackCase scrut co uniq boxing_con unpk_args body bndr = mk_ww_local uniq (exprType casted_scrut) \end{code} +Note [non-algebraic or open body type warning] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + +There are a few cases where the W/W transformation is told that something +returns a constructor, but the type at hand doesn't really match this. One +real-world example involves unsafeCoerce: + foo = IO a + foo = unsafeCoere c_exit + foreign import ccall "c_exit" c_exit :: IO () +Here CPR will tell you that `foo` returns a () constructor for sure, but trying +to create a worker/wrapper for type `a` obviously fails. +(This was a real example until ee8e792 in libraries/base.) + +It does not seem feasilbe to avoid all such cases already in the analyser (and +after all, the analysis is not really wrong), so we simply do nothing here in +mkWWcpr. But we still want to emit warning with -DDEBUG, to hopefully catch +other cases where something went avoidably wrong. + + Note [Profiling and unpacking] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ If the original function looked like From git at git.haskell.org Thu Dec 12 17:56:57 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 12 Dec 2013 17:56:57 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Clarify the default demand on demand environments (2b6a6a4) Message-ID: <20131212175657.83F322406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/2b6a6a469fa60b23783c2b1f8e6158ec0a437634/ghc >--------------------------------------------------------------- commit 2b6a6a469fa60b23783c2b1f8e6158ec0a437634 Author: Joachim Breitner Date: Wed Dec 4 17:59:09 2013 +0000 Clarify the default demand on demand environments by adding Notes and using easier to understand combinators. >--------------------------------------------------------------- 2b6a6a469fa60b23783c2b1f8e6158ec0a437634 compiler/basicTypes/Demand.lhs | 83 ++++++++++++++++++---------------------- compiler/basicTypes/VarEnv.lhs | 4 +- compiler/stranal/DmdAnal.lhs | 10 ----- compiler/utils/UniqFM.lhs | 21 ++++++++++ 4 files changed, 62 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 2b6a6a469fa60b23783c2b1f8e6158ec0a437634 From git at git.haskell.org Thu Dec 12 17:57:00 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 12 Dec 2013 17:57:00 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Remove dmdAnalArg and replace by easier to understand code (07b097a) Message-ID: <20131212175700.6FE082406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/07b097a903f5a2cc30d54f17bb9d69010984cc73/ghc >--------------------------------------------------------------- commit 07b097a903f5a2cc30d54f17bb9d69010984cc73 Author: Joachim Breitner Date: Wed Dec 4 17:38:25 2013 +0000 Remove dmdAnalArg and replace by easier to understand code >--------------------------------------------------------------- 07b097a903f5a2cc30d54f17bb9d69010984cc73 compiler/stranal/DmdAnal.lhs | 16 ++++++++-------- 1 file changed, 8 insertions(+), 8 deletions(-) diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index 3b805d9..a377bf5 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -103,13 +103,12 @@ c) The application rule wouldn't be right either evaluation of f in a C(L) demand! \begin{code} -dmdAnalArg :: AnalEnv - -> Demand -- This one takes a *Demand* - -> CoreExpr -> (DmdType, CoreExpr) --- Used for function arguments -dmdAnalArg env dmd e - | exprIsTrivial e = dmdAnalStar env dmd e - | otherwise = dmdAnalStar env (oneifyDmd dmd) e +-- If e is complicated enough to become a thunk, its contents will be evaluated +-- at most once, so oneify it. +dmdTransformThunkDmd :: CoreExpr -> Demand -> Demand +dmdTransformThunkDmd e + | exprIsTrivial e = id + | otherwise = oneifyDmd -- Do not process absent demands -- Otherwise act like in a normal demand analysis @@ -177,7 +176,7 @@ dmdAnal env dmd (App fun arg) -- Non-type arguments call_dmd = mkCallDmd dmd (fun_ty, fun') = dmdAnal env call_dmd fun (arg_dmd, res_ty) = splitDmdTy fun_ty - (arg_ty, arg') = dmdAnalArg env arg_dmd arg + (arg_ty, arg') = dmdAnalStar env (dmdTransformThunkDmd arg arg_dmd) arg in -- pprTrace "dmdAnal:app" (vcat -- [ text "dmd =" <+> ppr dmd @@ -510,6 +509,7 @@ dmdTransform env var dmd | otherwise -- Local non-letrec-bound thing = unitVarDmd var (mkOnceUsedDmd dmd) + \end{code} %************************************************************************ From git at git.haskell.org Thu Dec 12 17:57:02 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 12 Dec 2013 17:57:02 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Split DmdResult into DmdResult and CPRResult (43fa766) Message-ID: <20131212175702.E4D8A2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/43fa76622c65018896f74b56762a7e1090cc626f/ghc >--------------------------------------------------------------- commit 43fa76622c65018896f74b56762a7e1090cc626f Author: Joachim Breitner Date: Thu Dec 12 15:39:30 2013 +0000 Split DmdResult into DmdResult and CPRResult this is a small-step-refactoring patch and not very interesting on its own. >--------------------------------------------------------------- 43fa76622c65018896f74b56762a7e1090cc626f compiler/basicTypes/Demand.lhs | 174 ++++++++++++++++++++++++++-------------- compiler/basicTypes/MkId.lhs | 4 +- compiler/stranal/DmdAnal.lhs | 16 ++-- 3 files changed, 122 insertions(+), 72 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 43fa76622c65018896f74b56762a7e1090cc626f From git at git.haskell.org Thu Dec 12 17:57:05 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 12 Dec 2013 17:57:05 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Do not export DmdResult constructors in Demand.lhs (9fcf856) Message-ID: <20131212175705.6C4172406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/9fcf85608bd6c62a28404d9152be9d277b25a248/ghc >--------------------------------------------------------------- commit 9fcf85608bd6c62a28404d9152be9d277b25a248 Author: Joachim Breitner Date: Mon Dec 9 16:56:32 2013 +0000 Do not export DmdResult constructors in Demand.lhs >--------------------------------------------------------------- 9fcf85608bd6c62a28404d9152be9d277b25a248 compiler/basicTypes/Demand.lhs | 20 ++++++++++---------- compiler/basicTypes/MkId.lhs | 4 ++-- 2 files changed, 12 insertions(+), 12 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 38ff2d2..fefbb8c 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -25,7 +25,7 @@ module Demand ( DmdEnv, emptyDmdEnv, peelFV, - DmdResult(..), CPRResult(..), + DmdResult, CPRResult, isBotRes, isTopRes, resTypeArgDmd, topRes, botRes, cprProdRes, vanillaCprProdRes, cprSumRes, appIsBottom, isBottomingSig, pprIfaceStrictSig, @@ -768,19 +768,19 @@ topRes, botRes :: DmdResult topRes = Dunno NoCPR botRes = Diverges -cprSumRes :: ConTag -> CPRResult -cprSumRes tag | opt_CprOff = NoCPR - | otherwise = RetSum tag +cprSumRes :: ConTag -> DmdResult +cprSumRes tag | opt_CprOff = topRes + | otherwise = Dunno $ RetSum tag -cprProdRes :: [DmdType] -> CPRResult +cprProdRes :: [DmdType] -> DmdResult cprProdRes _arg_tys - | opt_CprOff = NoCPR - | otherwise = RetProd + | opt_CprOff = topRes + | otherwise = Dunno $ RetProd -vanillaCprProdRes :: Arity -> CPRResult +vanillaCprProdRes :: Arity -> DmdResult vanillaCprProdRes _arity - | opt_CprOff = NoCPR - | otherwise = RetProd + | opt_CprOff = topRes + | otherwise = Dunno $ RetProd isTopRes :: DmdResult -> Bool isTopRes (Dunno NoCPR) = True diff --git a/compiler/basicTypes/MkId.lhs b/compiler/basicTypes/MkId.lhs index 6120b56..604163f 100644 --- a/compiler/basicTypes/MkId.lhs +++ b/compiler/basicTypes/MkId.lhs @@ -434,8 +434,8 @@ dataConCPR con , isVanillaDataCon con -- No existentials , wkr_arity > 0 , wkr_arity <= mAX_CPR_SIZE - = if is_prod then Dunno (vanillaCprProdRes (dataConRepArity con)) - else Dunno (cprSumRes (dataConTag con)) + = if is_prod then vanillaCprProdRes (dataConRepArity con) + else cprSumRes (dataConTag con) | otherwise = topRes where From git at git.haskell.org Thu Dec 12 17:57:07 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 12 Dec 2013 17:57:07 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Rename postProcessDmdType to postProcessUnsat and use* to reuse* (715ed45) Message-ID: <20131212175707.955102406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/715ed45699f11182ccba9b466f8209a3ef6a7f81/ghc >--------------------------------------------------------------- commit 715ed45699f11182ccba9b466f8209a3ef6a7f81 Author: Joachim Breitner Date: Thu Dec 12 16:12:00 2013 +0000 Rename postProcessDmdType to postProcessUnsat and use* to reuse* >--------------------------------------------------------------- 715ed45699f11182ccba9b466f8209a3ef6a7f81 compiler/basicTypes/Demand.lhs | 81 ++++++++++++++++++++++------------------ compiler/stranal/DmdAnal.lhs | 4 +- 2 files changed, 46 insertions(+), 39 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index fefbb8c..ba4f789 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -38,13 +38,13 @@ module Demand ( evalDmd, cleanEvalDmd, cleanEvalProdDmd, isStrictDmd, splitDmdTy, splitFVs, deferAfterIO, - postProcessDmdType, postProcessDmdTypeM, + postProcessUnsat, postProcessDmdTypeM, splitProdDmd, splitProdDmd_maybe, peelCallDmd, mkCallDmd, dmdTransformSig, dmdTransformDataConSig, dmdTransformDictSelSig, argOneShots, argsOneShots, - isSingleUsed, useEnv, zapDemand, zapStrictSig, + isSingleUsed, reuseEnv, zapDemand, zapStrictSig, worthSplittingArgDmd, worthSplittingThunkDmd, @@ -400,23 +400,25 @@ Compare with: (C) making Used win for both, but UProd win for lub \begin{code} -markAsUsedDmd :: MaybeUsed -> MaybeUsed -markAsUsedDmd Abs = Abs -markAsUsedDmd (Use _ a) = Use Many (markUsed a) +-- If a demand is used multiple times (i.e. reused), than any use-once +-- mentioned there, that is not protected by a UCall, can happen many times. +markReusedDmd :: MaybeUsed -> MaybeUsed +markReusedDmd Abs = Abs +markReusedDmd (Use _ a) = Use Many (markReused a) -markUsed :: UseDmd -> UseDmd -markUsed (UCall _ u) = UCall Many u -- No need to recurse here -markUsed (UProd ux) = UProd (map markAsUsedDmd ux) -markUsed u = u +markReused :: UseDmd -> UseDmd +markReused (UCall _ u) = UCall Many u -- No need to recurse here +markReused (UProd ux) = UProd (map markReusedDmd ux) +markReused u = u isUsedMU :: MaybeUsed -> Bool --- True <=> markAsUsedDmd d = d +-- True <=> markReusedDmd d = d isUsedMU Abs = True isUsedMU (Use One _) = False isUsedMU (Use Many u) = isUsedU u isUsedU :: UseDmd -> Bool --- True <=> markUsed d = d +-- True <=> markReused d = d isUsedU Used = True isUsedU UHead = True isUsedU (UProd us) = all isUsedMU us @@ -1121,34 +1123,39 @@ toCleanDmd (JD { strd = s, absd = u }) (Lazy, Use c u') -> (CD { sd = HeadStr, ud = u' }, Just (True, c)) (_, Abs) -> (CD { sd = HeadStr, ud = Used }, Nothing) +-- This is used in dmdAnalStar when post-processing +-- a function's argument demand. So we only care about what +-- does to free variables, and whether it terminates. postProcessDmdTypeM :: DeferAndUseM -> DmdType -> DmdType postProcessDmdTypeM Nothing _ = nopDmdType -- Incoming demand was Absent, so just discard all usage information -- We only processed the thing at all to analyse the body -- See Note [Always analyse in virgin pass] -postProcessDmdTypeM (Just du) ty = postProcessDmdType du ty - -postProcessDmdType :: DeferAndUse -> DmdType -> DmdType -postProcessDmdType (True, Many) ty = deferAndUse ty -postProcessDmdType (False, Many) ty = useType ty -postProcessDmdType (True, One) ty = deferType ty -postProcessDmdType (False, One) ty = ty - -deferType, useType, deferAndUse :: DmdType -> DmdType -deferType (DmdType fv ds _) = DmdType (deferEnv fv) (map deferDmd ds) topRes -useType (DmdType fv ds res_ty) = DmdType (useEnv fv) (map useDmd ds) res_ty -deferAndUse (DmdType fv ds _) = DmdType (deferUseEnv fv) (map deferUseDmd ds) topRes - -deferEnv, useEnv, deferUseEnv :: DmdEnv -> DmdEnv -deferEnv fv = mapVarEnv deferDmd fv -useEnv fv = mapVarEnv useDmd fv -deferUseEnv fv = mapVarEnv deferUseDmd fv - -deferDmd, useDmd, deferUseDmd :: JointDmd -> JointDmd -deferDmd (JD {strd=_, absd=a}) = mkJointDmd Lazy a -useDmd (JD {strd=d, absd=a}) = mkJointDmd d (markAsUsedDmd a) -deferUseDmd (JD {strd=_, absd=a}) = mkJointDmd Lazy (markAsUsedDmd a) - +postProcessDmdTypeM (Just du) ty = postProcessUnsat du ty + +postProcessUnsat :: DeferAndUse -> DmdType -> DmdType +postProcessUnsat (True, Many) ty = deferReuse ty +postProcessUnsat (False, Many) ty = reuseType ty +postProcessUnsat (True, One) ty = deferType ty +postProcessUnsat (False, One) ty = ty + +deferType, reuseType, deferReuse :: DmdType -> DmdType +deferType (DmdType fv ds _) = DmdType (deferEnv fv) (map deferDmd ds) topRes +reuseType (DmdType fv ds res_ty) = DmdType (reuseEnv fv) (map reuseDmd ds) res_ty +deferReuse (DmdType fv ds _) = DmdType (deferReuseEnv fv) (map deferReuseDmd ds) topRes + +deferEnv, reuseEnv, deferReuseEnv :: DmdEnv -> DmdEnv +deferEnv fv = mapVarEnv deferDmd fv +reuseEnv fv = mapVarEnv reuseDmd fv +deferReuseEnv fv = mapVarEnv deferReuseDmd fv + +deferDmd, reuseDmd, deferReuseDmd :: JointDmd -> JointDmd +deferDmd (JD {strd=_, absd=a}) = mkJointDmd Lazy a +reuseDmd (JD {strd=d, absd=a}) = mkJointDmd d (markReusedDmd a) +deferReuseDmd (JD {strd=_, absd=a}) = mkJointDmd Lazy (markReusedDmd a) + +-- Peels one call level from the demand, and also returns +-- whether it was unsaturated (separately for strictness and usage) peelCallDmd :: CleanDemand -> (CleanDemand, DeferAndUse) -- Exploiting the fact that -- on the strictness side C(B) = B @@ -1352,8 +1359,8 @@ dmdTransformSig :: StrictSig -> CleanDemand -> DmdType -- signature is fun_sig, with demand dmd. We return the demand -- that the function places on its context (eg its args) dmdTransformSig (StrictSig dmd_ty@(DmdType _ arg_ds _)) cd - = postProcessDmdType (peelManyCalls arg_ds cd) dmd_ty - -- NB: it's important to use postProcessDmdType, and not + = postProcessUnsat (peelManyCalls arg_ds cd) dmd_ty + -- NB: it's important to use postProcessUnsat, and not -- just return nopDmdType for unsaturated calls -- Consider let { f x y = p + x } in f 1 -- The application isn't saturated, but we must nevertheless propagate @@ -1391,7 +1398,7 @@ dmdTransformDictSelSig :: StrictSig -> CleanDemand -> DmdType dmdTransformDictSelSig (StrictSig (DmdType _ [dict_dmd] _)) cd | (cd',defer_use) <- peelCallDmd cd , Just jds <- splitProdDmd_maybe dict_dmd - = postProcessDmdType defer_use $ + = postProcessUnsat defer_use $ DmdType emptyDmdEnv [mkOnceUsedDmd $ mkProdDmd $ map (enhance cd') jds] topRes | otherwise = nopDmdType -- See Note [Demand transformer for a dictionary selector] diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index 01c990a..cbdcc67 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -206,7 +206,7 @@ dmdAnal env dmd (Lam var body) (body_ty, body') = dmdAnal env' body_dmd body (lam_ty, var') = annotateLamIdBndr env notArgOfDfun body_ty one_shot var in - (postProcessDmdType defer_and_use lam_ty, Lam var' body') + (postProcessUnsat defer_and_use lam_ty, Lam var' body') dmdAnal env dmd (Case scrut case_bndr ty [alt@(DataAlt dc, _, _)]) -- Only one alternative with a product constructor @@ -619,7 +619,7 @@ dmdAnalRhs top_lvl rec_flag env id rhs -- See Note [Lazy and unleashable free variables] -- See Note [Aggregated demand for cardinality] rhs_fv1 = case rec_flag of - Just bs -> useEnv (delVarEnvList rhs_fv bs) + Just bs -> reuseEnv (delVarEnvList rhs_fv bs) Nothing -> rhs_fv (lazy_fv, sig_fv) = splitFVs is_thunk rhs_fv1 From git at git.haskell.org Thu Dec 12 17:57:09 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 12 Dec 2013 17:57:09 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Make types of bothDmdType more precise (a5505be) Message-ID: <20131212175709.CEFF72406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/a5505be2e5614007c01749ed0163e9f0055a657a/ghc >--------------------------------------------------------------- commit a5505be2e5614007c01749ed0163e9f0055a657a Author: Joachim Breitner Date: Mon Dec 9 18:40:09 2013 +0000 Make types of bothDmdType more precise by only passing the demand on the free variables, and whether the argument (resp. scrunitee) may or will diverge. Also make different postProcess code paths for function arguments (which are post-processed just to be both'ed) and unsaturated functions (which are post-processed for other reasons.) Also add a note [Demands from unsaturated function calls] that hopefully comprehensively and comprehensibly explains what is going on here. >--------------------------------------------------------------- a5505be2e5614007c01749ed0163e9f0055a657a compiler/basicTypes/Demand.lhs | 132 +++++++++++++++++++++++++++++----------- compiler/stranal/DmdAnal.lhs | 9 ++- 2 files changed, 101 insertions(+), 40 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 a5505be2e5614007c01749ed0163e9f0055a657a From git at git.haskell.org Thu Dec 12 17:57:14 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 12 Dec 2013 17:57:14 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Initial work on Nested CPR (31c651e) Message-ID: <20131212175715.58FE424069@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/31c651e0642ec5eb3ef93337d5821b40317f4178/ghc >--------------------------------------------------------------- commit 31c651e0642ec5eb3ef93337d5821b40317f4178 Author: Simon Peyton Jones Date: Mon Nov 25 09:59:16 2013 +0000 Initial work on Nested CPR >--------------------------------------------------------------- 31c651e0642ec5eb3ef93337d5821b40317f4178 compiler/basicTypes/Demand.lhs | 137 ++++++++++++++++++++++++---------------- compiler/stranal/DmdAnal.lhs | 111 ++++++++++++++++++++++---------- 2 files changed, 160 insertions(+), 88 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 31c651e0642ec5eb3ef93337d5821b40317f4178 From git at git.haskell.org Thu Dec 12 17:57:11 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 12 Dec 2013 17:57:11 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Add Converges to DmdResult (344ea58) Message-ID: <20131212175715.06E792406D@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/344ea58ed27b6c18c134feae9f63878f6b99d500/ghc >--------------------------------------------------------------- commit 344ea58ed27b6c18c134feae9f63878f6b99d500 Author: Joachim Breitner Date: Thu Dec 12 15:45:19 2013 +0000 Add Converges to DmdResult to detect definite convergence (required for nested CPR). >--------------------------------------------------------------- 344ea58ed27b6c18c134feae9f63878f6b99d500 compiler/basicTypes/Demand.lhs | 39 ++++++++++++++++++++++++++++----------- 1 file changed, 28 insertions(+), 11 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index bd050c7..8df5247 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -691,8 +691,8 @@ splitProdDmd_maybe (JD {strd = s, absd = u}) DmdResult: Dunno CPRResult - / - Diverges + / \ + Diverges Converges CPRResult CPRResult: NoCPR @@ -700,7 +700,7 @@ CPRResult: NoCPR RetProd RetSum ConTag -Product contructors return (Dunno (RetProd rs)) +Product contructors return (Converges (RetProd rs)) In a fixpoint iteration, start from Diverges We have lubs, but not glbs; but that is ok. @@ -711,6 +711,7 @@ We have lubs, but not glbs; but that is ok. ------------------------------------------------------------------------ data Termination r = Diverges -- Definitely diverges + | Converges r -- Definitely converges | Dunno r -- Might diverge or converge deriving( Eq, Show ) @@ -729,7 +730,11 @@ lubCPR _ _ = NoCPR lubDmdResult :: DmdResult -> DmdResult -> DmdResult lubDmdResult Diverges r = r +lubDmdResult (Converges c1) Diverges = Converges c1 +lubDmdResult (Converges c1) (Converges c2) = Converges (c1 `lubCPR` c2) +lubDmdResult (Converges c1) (Dunno c2) = Dunno (c1 `lubCPR` c2) lubDmdResult (Dunno c1) Diverges = Dunno c1 +lubDmdResult (Dunno c1) (Converges c2) = Dunno (c1 `lubCPR` c2) lubDmdResult (Dunno c1) (Dunno c2) = Dunno (c1 `lubCPR` c2) -- This needs to commute with defaultDmd, i.e. -- defaultDmd (r1 `lubDmdResult` r2) = defaultDmd r1 `lubDmd` defaultDmd r2 @@ -738,6 +743,7 @@ lubDmdResult (Dunno c1) (Dunno c2) = Dunno (c1 `lubCPR` c2) bothDmdResult :: DmdResult -> Termination () -> DmdResult -- See Note [Asymmetry of 'both' for DmdType and DmdResult] bothDmdResult _ Diverges = Diverges +bothDmdResult (Converges c1) (Dunno {}) = Dunno c1 bothDmdResult r _ = r -- This needs to commute with defaultDmd, i.e. -- defaultDmd (r1 `bothDmdResult` r2) = defaultDmd r1 `bothDmd` defaultDmd r2 @@ -745,6 +751,7 @@ bothDmdResult r _ = r instance Outputable DmdResult where ppr Diverges = char 'b' + ppr (Converges c) = char 't' <> ppr c ppr (Dunno c) = char 'd' <> ppr c instance Outputable CPRResult where @@ -754,6 +761,7 @@ instance Outputable CPRResult where seqDmdResult :: DmdResult -> () seqDmdResult Diverges = () +seqDmdResult (Converges c) = seqCPRResult c seqDmdResult (Dunno c) = seqCPRResult c seqCPRResult :: CPRResult -> () @@ -774,17 +782,17 @@ botRes = Diverges cprSumRes :: ConTag -> DmdResult cprSumRes tag | opt_CprOff = topRes - | otherwise = Dunno $ RetSum tag + | otherwise = Converges $ RetSum tag cprProdRes :: [DmdType] -> DmdResult cprProdRes _arg_tys | opt_CprOff = topRes - | otherwise = Dunno $ RetProd + | otherwise = Converges $ RetProd vanillaCprProdRes :: Arity -> DmdResult vanillaCprProdRes _arity | opt_CprOff = topRes - | otherwise = Dunno $ RetProd + | otherwise = Converges $ RetProd isTopRes :: DmdResult -> Bool isTopRes (Dunno NoCPR) = True @@ -798,6 +806,7 @@ trimCPRInfo :: Bool -> Bool -> DmdResult -> DmdResult trimCPRInfo trim_all trim_sums res = trimR res where + trimR (Converges c) = Converges (trimC c) trimR (Dunno c) = Dunno (trimC c) trimR Diverges = Diverges @@ -811,6 +820,7 @@ returnsCPR :: DmdResult -> Bool returnsCPR dr = isJust (returnsCPR_maybe dr) returnsCPR_maybe :: DmdResult -> Maybe ConTag +returnsCPR_maybe (Converges c) = retCPR_maybe c returnsCPR_maybe (Dunno c) = retCPR_maybe c returnsCPR_maybe Diverges = Nothing @@ -1036,6 +1046,7 @@ toBothDmdArg :: DmdType -> BothDmdArg toBothDmdArg (DmdType fv _ r) = (fv, go r) where go (Dunno {}) = Dunno () + go (Converges {}) = Converges () go Diverges = Diverges bothDmdType :: DmdType -> BothDmdArg -> DmdType @@ -1069,7 +1080,7 @@ botDmdType = DmdType emptyDmdEnv [] botRes cprProdDmdType :: Arity -> DmdType cprProdDmdType _arity - = DmdType emptyDmdEnv [] (Dunno RetProd) + = DmdType emptyDmdEnv [] (Converges RetProd) isNopDmdType :: DmdType -> Bool isNopDmdType (DmdType env [] res) @@ -1098,7 +1109,7 @@ splitDmdTy ty@(DmdType _ [] res_ty) = (resTypeArgDmd res_ty, ty) -- exit? -- * We have to kill all strictness demands (i.e. lub with a lazy demand) -- * We can keep demand information (i.e. lub with an absent deman) --- * We have to kill definite divergence +-- * We have to kill definite divergence and definite convergence -- * We can keep CPR information. -- See Note [IO hack in the demand analyser] deferAfterIO :: DmdType -> DmdType @@ -1107,6 +1118,7 @@ deferAfterIO d@(DmdType _ _ res) = DmdType fv ds _ -> DmdType fv ds (defer_res res) where defer_res Diverges = topRes + defer_res (Converges r) = Dunno r defer_res r = r strictenDmd :: JointDmd -> CleanDemand @@ -1149,9 +1161,12 @@ postProcessDmdTypeM (Just du) (DmdType fv _ res_ty) = (postProcessDmdEnv du fv, postProcessDmdResult du res_ty) postProcessDmdResult :: DeferAndUse -> DmdResult -> Termination () -postProcessDmdResult _ Dunno {} = Dunno () +postProcessDmdResult (True,_) _ = Converges () + -- if we use it lazily, there cannot be divergence worrying us + -- (Otherwise we'd lose the termination information of constructors in in dmdAnalVarApp, for example) +postProcessDmdResult _ (Dunno {}) = Dunno () +postProcessDmdResult _ (Converges {}) = Converges () postProcessDmdResult _ Diverges = Diverges - -- DeferAndUsed will be used by a later patch postProcessDmdEnv :: DeferAndUse -> DmdEnv -> DmdEnv postProcessDmdEnv (True, Many) env = deferReuseEnv env @@ -1722,11 +1737,13 @@ instance Binary DmdType where instance Binary DmdResult where put_ bh (Dunno c) = do { putByte bh 0; put_ bh c } - put_ bh Diverges = putByte bh 2 + put_ bh (Converges c) = do { putByte bh 1; put_ bh c } + put_ bh Diverges = putByte bh 3 get bh = do { h <- getByte bh ; case h of 0 -> do { c <- get bh; return (Dunno c) } + 1 -> do { c <- get bh; return (Converges c) } _ -> return Diverges } instance Binary CPRResult where From git at git.haskell.org Thu Dec 12 17:57:16 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 12 Dec 2013 17:57:16 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Use isTypeArg instead of isTyCoArg (forgot why) (8c501a9) Message-ID: <20131212175716.82CE52406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/8c501a9a4755fe7990cd811718b40da1a745cd22/ghc >--------------------------------------------------------------- commit 8c501a9a4755fe7990cd811718b40da1a745cd22 Author: Joachim Breitner Date: Thu Dec 5 16:14:07 2013 +0000 Use isTypeArg instead of isTyCoArg (forgot why) >--------------------------------------------------------------- 8c501a9a4755fe7990cd811718b40da1a745cd22 compiler/stranal/DmdAnal.lhs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index cb5aa4a..0da1085 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -509,7 +509,7 @@ completeApp :: AnalEnv completeApp _ fun_ty_fun [] = fun_ty_fun completeApp env (fun_ty, fun') (arg:args) - | isTyCoArg arg = completeApp env (fun_ty, App fun' arg) args + | isTypeArg arg = completeApp env (fun_ty, App fun' arg) args | otherwise = completeApp env (res_ty `bothDmdType` arg_ty, App fun' arg') args where (arg_dmd, res_ty) = splitDmdTy fun_ty From git at git.haskell.org Thu Dec 12 17:57:18 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 12 Dec 2013 17:57:18 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Fix a lubDmdResult equation (9dee3f1) Message-ID: <20131212175718.C2A732406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/9dee3f126e26e6feb823a6264765f7f5e9765d9e/ghc >--------------------------------------------------------------- commit 9dee3f126e26e6feb823a6264765f7f5e9765d9e Author: Joachim Breitner Date: Tue Nov 26 10:17:57 2013 +0000 Fix a lubDmdResult equation >--------------------------------------------------------------- 9dee3f126e26e6feb823a6264765f7f5e9765d9e compiler/basicTypes/Demand.lhs | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 943cc06..00c08dc 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -750,8 +750,10 @@ lubCPR (RetProd ds1) (RetProd ds2) lubCPR _ _ = NoCPR lubDmdResult :: DmdResult -> DmdResult -> DmdResult -lubDmdResult Diverges r = r -lubDmdResult (Converges c1) Diverges = Converges c1 +lubDmdResult Diverges (Dunno c2) = Dunno c2 +lubDmdResult Diverges Diverges = Diverges +lubDmdResult Diverges (Converges c2) = Dunno c2 +lubDmdResult (Converges c1) Diverges = Dunno c1 lubDmdResult (Converges c1) (Converges c2) = Converges (c1 `lubCPR` c2) lubDmdResult (Converges c1) (Dunno c2) = Dunno (c1 `lubCPR` c2) lubDmdResult (Dunno c1) Diverges = Dunno c1 From git at git.haskell.org Thu Dec 12 17:57:20 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 12 Dec 2013 17:57:20 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Recover [CPR for sum types] (slightly differently) (298dfff) Message-ID: <20131212175721.049292406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/298dfffce7c9d1ea860236a342160d703d35e01a/ghc >--------------------------------------------------------------- commit 298dfffce7c9d1ea860236a342160d703d35e01a Author: Joachim Breitner Date: Thu Nov 28 11:17:16 2013 +0000 Recover [CPR for sum types] (slightly differently) >--------------------------------------------------------------- 298dfffce7c9d1ea860236a342160d703d35e01a compiler/basicTypes/Demand.lhs | 24 ++++++++---------------- compiler/stranal/DmdAnal.lhs | 14 ++++++++------ 2 files changed, 16 insertions(+), 22 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index aa78e44..e71525b 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -30,10 +30,9 @@ module Demand ( isBotRes, isTopRes, getDmdResult, resTypeArgDmd, topRes, botRes, cprConRes, vanillaCprConRes, appIsBottom, isBottomingSig, pprIfaceStrictSig, - trimCPRInfo, returnsCPR, returnsCPR_maybe, + returnsCPR, returnsCPR_maybe, forgetCPR, StrictSig(..), mkStrictSig, mkClosedStrictSig, nopSig, botSig, cprProdSig, isNopSig, splitStrictSig, increaseStrictSigArity, - seqDemand, seqDemandList, seqDmdType, seqStrictSig, evalDmd, cleanEvalDmd, cleanEvalProdDmd, isStrictDmd, @@ -826,6 +825,13 @@ cutCPRResult :: Int -> CPRResult -> CPRResult cutCPRResult _ NoCPR = NoCPR cutCPRResult n (RetCon tag rs) = RetCon tag (map (cutDmdResult (n-1)) rs) +-- Forget the CPR information, but remember if it converges or diverges +-- Used for non-strict thunks and non-top-level things with sum type +forgetCPR :: DmdResult -> DmdResult +forgetCPR Diverges = Diverges +forgetCPR (Converges _) = Converges NoCPR +forgetCPR (Dunno _) = Dunno NoCPR + cprConRes :: ConTag -> [DmdResult] -> DmdResult cprConRes tag arg_ress | opt_CprOff = topRes @@ -844,20 +850,6 @@ isBotRes :: DmdResult -> Bool isBotRes Diverges = True isBotRes _ = False --- TODO: This currently ignores trim_sums. Evaluate if still required, and fix --- Note [CPR for sum types] -trimCPRInfo :: Bool -> Bool -> DmdResult -> DmdResult -trimCPRInfo trim_all _trim_sums res - = trimR res - where - trimR (Converges c) = Converges (trimC c) - trimR (Dunno c) = Dunno (trimC c) - trimR Diverges = Diverges - - trimC (RetCon n rs) | trim_all = NoCPR - | otherwise = RetCon n (map trimR rs) - trimC NoCPR = NoCPR - returnsCPR :: DmdResult -> Bool returnsCPR dr = isJust (returnsCPR_maybe dr) diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index 0da1085..ea1a588 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -655,9 +655,10 @@ dmdAnalRhs top_lvl rec_flag env id rhs -- See Note [NOINLINE and strictness] -- See Note [Product demands for function body] - body_dmd = case deepSplitProductType_maybe (exprType body) of - Nothing -> cleanEvalDmd - Just (dc, _, _, _) -> cleanEvalProdDmd (dataConRepArity dc) + (is_sum_type, body_dmd) + = case deepSplitProductType_maybe (exprType body) of + Nothing -> (True, cleanEvalDmd) + Just (dc, _, _, _) -> (False, cleanEvalProdDmd (dataConRepArity dc)) -- See Note [Lazy and unleashable free variables] -- See Note [Aggregated demand for cardinality] @@ -667,9 +668,10 @@ dmdAnalRhs top_lvl rec_flag env id rhs (lazy_fv, sig_fv) = splitFVs is_thunk rhs_fv1 - rhs_res' = trimCPRInfo trim_all trim_sums rhs_res - trim_all = is_thunk && not_strict - trim_sums = not (isTopLevel top_lvl) -- See Note [CPR for sum types] + -- Note [CPR for sum types] + rhs_res' | (is_sum_type && not (isTopLevel top_lvl)) || + (is_thunk && not_strict) = forgetCPR rhs_res + | otherwise = rhs_res -- See Note [CPR for thunks] is_thunk = not (exprIsHNF rhs) From git at git.haskell.org Thu Dec 12 17:57:23 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 12 Dec 2013 17:57:23 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Unify RetProd and RetSum to RetCon in CPRResult (3318049) Message-ID: <20131212175723.3C4BB2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/3318049dc1c16229fcc2ceff55a4ce1ddd732881/ghc >--------------------------------------------------------------- commit 3318049dc1c16229fcc2ceff55a4ce1ddd732881 Author: Joachim Breitner Date: Thu Dec 5 16:13:41 2013 +0000 Unify RetProd and RetSum to RetCon in CPRResult >--------------------------------------------------------------- 3318049dc1c16229fcc2ceff55a4ce1ddd732881 compiler/basicTypes/Demand.lhs | 102 ++++++++++++++++++++++------------------ compiler/basicTypes/MkId.lhs | 4 +- compiler/stranal/DmdAnal.lhs | 4 +- 3 files changed, 59 insertions(+), 51 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 3318049dc1c16229fcc2ceff55a4ce1ddd732881 From git at git.haskell.org Thu Dec 12 17:57:25 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 12 Dec 2013 17:57:25 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: In deferType, return convRes = Converges NoCPR (653f7da) Message-ID: <20131212175725.712572406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/653f7dad7d372c390a085d3c82787272db060c10/ghc >--------------------------------------------------------------- commit 653f7dad7d372c390a085d3c82787272db060c10 Author: Joachim Breitner Date: Wed Dec 4 16:55:18 2013 +0000 In deferType, return convRes = Converges NoCPR because this is the right-identity to `bothDmdResult`, and this is the right thing to do in a lazy context. >--------------------------------------------------------------- 653f7dad7d372c390a085d3c82787272db060c10 compiler/basicTypes/Demand.lhs | 7 ++++--- 1 file changed, 4 insertions(+), 3 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 8df5247..9d19981 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -776,8 +776,9 @@ seqCPRResult RetProd = () -- [cprRes] lets us switch off CPR analysis -- by making sure that everything uses TopRes -topRes, botRes :: DmdResult +topRes, convRes, botRes :: DmdResult topRes = Dunno NoCPR +convRes = Converges NoCPR botRes = Diverges cprSumRes :: ConTag -> DmdResult @@ -1182,9 +1183,9 @@ postProcessUnsat (True, One) ty = deferType ty postProcessUnsat (False, One) ty = ty deferType, reuseType, deferReuse :: DmdType -> DmdType -deferType (DmdType fv ds _) = DmdType (deferEnv fv) (map deferDmd ds) topRes +deferType (DmdType fv ds _) = DmdType (deferEnv fv) (map deferDmd ds) convRes reuseType (DmdType fv ds res_ty) = DmdType (reuseEnv fv) (map reuseDmd ds) res_ty -deferReuse (DmdType fv ds _) = DmdType (deferReuseEnv fv) (map deferReuseDmd ds) topRes +deferReuse (DmdType fv ds _) = DmdType (deferReuseEnv fv) (map deferReuseDmd ds) convRes deferEnv, reuseEnv, deferReuseEnv :: DmdEnv -> DmdEnv deferEnv fv = mapVarEnv deferDmd fv From git at git.haskell.org Thu Dec 12 17:57:27 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 12 Dec 2013 17:57:27 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Comments and small refactor (5da65a1) Message-ID: <20131212175727.B15DA2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/5da65a1695ed9dc5c9bba6283a94da21fe6ae29b/ghc >--------------------------------------------------------------- commit 5da65a1695ed9dc5c9bba6283a94da21fe6ae29b Author: Simon Peyton Jones Date: Wed Dec 4 16:00:24 2013 +0000 Comments and small refactor >--------------------------------------------------------------- 5da65a1695ed9dc5c9bba6283a94da21fe6ae29b compiler/basicTypes/Demand.lhs | 2 +- compiler/stranal/DmdAnal.lhs | 9 ++++++--- 2 files changed, 7 insertions(+), 4 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 0bb977e..943cc06 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -559,7 +559,7 @@ splitFVs is_thunk rhs_fvs %* * %************************************************************************ -This domain differst from JointDemand in the sense that pure absence +This domain differs from JointDemand in the sense that pure absence is taken away, i.e., we deal *only* with non-absent demands. Note [Strict demands] diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index 897b5b4..f94d53d 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -530,9 +530,6 @@ dmdAnalVarApp env dmd fun args -- , ppr arg_tys, ppr cpr_info, ppr res_ty]) $ ( res_ty , foldl App (Var fun) args') - - | otherwise - = completeApp env (dmdTransform env fun (mkCallDmdN n_val_args dmd), Var fun) args where n_val_args = valArgCount args cxt_ds = splitProdCleanDmd n_val_args dmd @@ -552,6 +549,12 @@ dmdAnalVarApp env dmd fun args , (arg_tys, arg_rets, args') <- anal_con_args ds args = (arg_ty:arg_tys, arg_ret:arg_rets, arg':args') anal_con_args ds args = pprPanic "anal_con_args" (ppr args $$ ppr ds) + +dmdAnalVarApp env dmd fun args + = --pprTrace "dmdAnalVarApp" (vcat [ ppr fun, ppr args + -- , ppr $ completeApp env (dmdTransform env fun (mkCallDmdN n_val_args dmd), Var fun) args + -- ]) + completeApp env (dmdTransform env fun (mkCallDmdN (valArgCount args) dmd), Var fun) args \end{code} %************************************************************************ From git at git.haskell.org Thu Dec 12 17:57:29 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 12 Dec 2013 17:57:29 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Loop breakers are not allowed to have a Converges DmdResult (7699aa5) Message-ID: <20131212175731.C89F52406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/7699aa5bbf06c21194ff3b944242eb9ded35a390/ghc >--------------------------------------------------------------- commit 7699aa5bbf06c21194ff3b944242eb9ded35a390 Author: Joachim Breitner Date: Tue Nov 26 10:18:35 2013 +0000 Loop breakers are not allowed to have a Converges DmdResult >--------------------------------------------------------------- 7699aa5bbf06c21194ff3b944242eb9ded35a390 compiler/basicTypes/Demand.lhs | 19 +++++++++++-------- compiler/stranal/DmdAnal.lhs | 5 ++++- 2 files changed, 15 insertions(+), 9 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index e71525b..2994235 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -33,6 +33,7 @@ module Demand ( returnsCPR, returnsCPR_maybe, forgetCPR, StrictSig(..), mkStrictSig, mkClosedStrictSig, nopSig, botSig, cprProdSig, isNopSig, splitStrictSig, increaseStrictSigArity, + sigMayConverge, seqDemand, seqDemandList, seqDmdType, seqStrictSig, evalDmd, cleanEvalDmd, cleanEvalProdDmd, isStrictDmd, @@ -806,15 +807,10 @@ getDmdResult _ = topRes maxCPRDepth :: Int maxCPRDepth = 3 --- With nested CPR, DmdResult can be arbitrarily deep; consider --- data Rec1 = Foo Rec2 Rec2 --- data Rec2 = Bar Rec1 Rec1 --- --- x = Foo y y --- y = Bar x x --- +-- With nested CPR, DmdResult can be arbitrarily deep; consider e.g. the +-- DmdResult of repeat -- So we need to forget information at a certain depth. We do that at all points --- where we are constructing new RetCon constructors. +-- where we are building RetCon constructors. cutDmdResult :: Int -> DmdResult -> DmdResult cutDmdResult 0 _ = topRes cutDmdResult _ Diverges = Diverges @@ -825,6 +821,10 @@ cutCPRResult :: Int -> CPRResult -> CPRResult cutCPRResult _ NoCPR = NoCPR cutCPRResult n (RetCon tag rs) = RetCon tag (map (cutDmdResult (n-1)) rs) +-- Forget that something might converge for sure +divergeDmdResult :: DmdResult -> DmdResult +divergeDmdResult r = r `lubDmdResult` botRes + -- Forget the CPR information, but remember if it converges or diverges -- Used for non-strict thunks and non-top-level things with sum type forgetCPR :: DmdResult -> DmdResult @@ -1445,6 +1445,9 @@ botSig = StrictSig botDmdType cprProdSig :: Arity -> StrictSig cprProdSig arity = StrictSig (cprProdDmdType arity) +sigMayConverge :: StrictSig -> StrictSig +sigMayConverge (StrictSig (DmdType env ds res)) = (StrictSig (DmdType env ds (divergeDmdResult res))) + argsOneShots :: StrictSig -> Arity -> [[OneShotInfo]] argsOneShots (StrictSig (DmdType _ arg_ds _)) n_val_args = go arg_ds diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index ea1a588..d5bf8a0 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -1084,7 +1084,10 @@ updSigEnv env sigs = env { ae_sigs = sigs } extendAnalEnv :: TopLevelFlag -> AnalEnv -> Id -> StrictSig -> AnalEnv extendAnalEnv top_lvl env var sig - = env { ae_sigs = extendSigEnv top_lvl (ae_sigs env) var sig } + = env { ae_sigs = extendSigEnv top_lvl (ae_sigs env) var sig' } + where + sig' | isWeakLoopBreaker (idOccInfo var) = sigMayConverge sig + | otherwise = sig extendSigEnv :: TopLevelFlag -> SigEnv -> Id -> StrictSig -> SigEnv extendSigEnv top_lvl sigs var sig = extendVarEnv sigs var (sig, top_lvl) From git at git.haskell.org Thu Dec 12 17:57:32 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 12 Dec 2013 17:57:32 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: in Demand.lhs, remember what is a sum type (8ec4693) Message-ID: <20131212175732.3403D2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/8ec4693cf429346b2dfa624e2382b110d17b3910/ghc >--------------------------------------------------------------- commit 8ec4693cf429346b2dfa624e2382b110d17b3910 Author: Joachim Breitner Date: Tue Dec 10 09:15:09 2013 +0000 in Demand.lhs, remember what is a sum type because we want to zap CPR information for sum types not only on the outermost level, but also nested. See Note [CPR for sum types] This comes up in sublist in Listplikefns in nofib?s boyer2. >--------------------------------------------------------------- 8ec4693cf429346b2dfa624e2382b110d17b3910 compiler/basicTypes/DataCon.lhs | 4 +++ compiler/basicTypes/Demand.lhs | 76 ++++++++++++++++++++++++--------------- compiler/basicTypes/MkId.lhs | 2 +- compiler/stranal/DmdAnal.lhs | 39 ++++++++++++-------- 4 files changed, 77 insertions(+), 44 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 8ec4693cf429346b2dfa624e2382b110d17b3910 From git at git.haskell.org Thu Dec 12 17:57:34 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 12 Dec 2013 17:57:34 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Add a flag -fnested-cpr-off to conveniently test the effect of nested CPR (b4a76c7) Message-ID: <20131212175734.8490A2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/b4a76c77ea91ea6d991d9f7e9daf6150f7fc9cbe/ghc >--------------------------------------------------------------- commit b4a76c77ea91ea6d991d9f7e9daf6150f7fc9cbe Author: Joachim Breitner Date: Wed Dec 4 09:14:26 2013 +0000 Add a flag -fnested-cpr-off to conveniently test the effect of nested CPR >--------------------------------------------------------------- b4a76c77ea91ea6d991d9f7e9daf6150f7fc9cbe compiler/basicTypes/Demand.lhs | 29 ++++++++++++++++++++--------- compiler/main/StaticFlags.hs | 9 +++++++-- 2 files changed, 27 insertions(+), 11 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 2994235..2adc69f 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -807,19 +807,29 @@ getDmdResult _ = topRes maxCPRDepth :: Int maxCPRDepth = 3 +-- This is the depth we use with -fnested-cpr-off, in order +-- to get precisely the same behaviour as before introduction of nested cpr +-- -fnested-cpr-off can eventually be removed if nested cpr is deemd to be +-- a good thing always. +flatCPRDepth :: Int +flatCPRDepth = 1 + -- With nested CPR, DmdResult can be arbitrarily deep; consider e.g. the -- DmdResult of repeat +-- -- So we need to forget information at a certain depth. We do that at all points -- where we are building RetCon constructors. -cutDmdResult :: Int -> DmdResult -> DmdResult -cutDmdResult 0 _ = topRes -cutDmdResult _ Diverges = Diverges -cutDmdResult n (Converges c) = Converges (cutCPRResult n c) -cutDmdResult n (Dunno c) = Dunno (cutCPRResult n c) - cutCPRResult :: Int -> CPRResult -> CPRResult -cutCPRResult _ NoCPR = NoCPR +cutCPRResult 0 _ = NoCPR +cutCPRResult _ NoCPR = NoCPR cutCPRResult n (RetCon tag rs) = RetCon tag (map (cutDmdResult (n-1)) rs) + where + cutDmdResult :: Int -> DmdResult -> DmdResult + cutDmdResult 0 _ = topRes + cutDmdResult _ Diverges = Diverges + cutDmdResult n (Converges c) = Converges (cutCPRResult n c) + cutDmdResult n (Dunno c) = Dunno (cutCPRResult n c) + -- Forget that something might converge for sure divergeDmdResult :: DmdResult -> DmdResult @@ -834,8 +844,9 @@ forgetCPR (Dunno _) = Dunno NoCPR cprConRes :: ConTag -> [DmdResult] -> DmdResult cprConRes tag arg_ress - | opt_CprOff = topRes - | otherwise = Converges $ cutCPRResult maxCPRDepth $ RetCon tag arg_ress + | opt_CprOff = topRes + | opt_NestedCprOff = Converges $ cutCPRResult flatCPRDepth $ RetCon tag arg_ress + | otherwise = Converges $ cutCPRResult maxCPRDepth $ RetCon tag arg_ress vanillaCprConRes :: ConTag -> Arity -> DmdResult vanillaCprConRes tag arity diff --git a/compiler/main/StaticFlags.hs b/compiler/main/StaticFlags.hs index 01dc3b7..feb7235 100644 --- a/compiler/main/StaticFlags.hs +++ b/compiler/main/StaticFlags.hs @@ -27,6 +27,7 @@ module StaticFlags ( -- optimisation opts opt_NoStateHack, opt_CprOff, + opt_NestedCprOff, opt_NoOptCoercion, -- For the parser @@ -140,7 +141,8 @@ flagsStaticNames :: [String] flagsStaticNames = [ "fno-state-hack", "fno-opt-coercion", - "fcpr-off" + "fcpr-off", + "fnested-cpr-off" ] -- We specifically need to discard static flags for clients of the @@ -195,10 +197,13 @@ opt_NoDebugOutput = lookUp (fsLit "-dno-debug-output") opt_NoStateHack :: Bool opt_NoStateHack = lookUp (fsLit "-fno-state-hack") --- Switch off CPR analysis in the new demand analyser +-- Switch off CPR analysis in the demand analyser opt_CprOff :: Bool opt_CprOff = lookUp (fsLit "-fcpr-off") +opt_NestedCprOff :: Bool +opt_NestedCprOff = lookUp (fsLit "-fnested-cpr-off") + opt_NoOptCoercion :: Bool opt_NoOptCoercion = lookUp (fsLit "-fno-opt-coercion") From git at git.haskell.org Thu Dec 12 17:57:36 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 12 Dec 2013 17:57:36 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Allow the CPR w/w to take unboxed tuples apart (ae465a0) Message-ID: <20131212175736.C04F72406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/ae465a0b50e91d27ce3282d1f7676fb5a67ebeac/ghc >--------------------------------------------------------------- commit ae465a0b50e91d27ce3282d1f7676fb5a67ebeac Author: Joachim Breitner Date: Thu Nov 28 10:29:47 2013 +0000 Allow the CPR w/w to take unboxed tuples apart >--------------------------------------------------------------- ae465a0b50e91d27ce3282d1f7676fb5a67ebeac compiler/stranal/WwLib.lhs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/stranal/WwLib.lhs b/compiler/stranal/WwLib.lhs index ce4112c..5168d8f 100644 --- a/compiler/stranal/WwLib.lhs +++ b/compiler/stranal/WwLib.lhs @@ -502,7 +502,7 @@ deepSplitCprType_maybe :: ConTag -> Type -> Maybe (DataCon, [Type], [Type], Coer deepSplitCprType_maybe con_tag ty | let (co, ty1) = topNormaliseNewType_maybe ty `orElse` (mkReflCo Representational ty, ty) , Just (tc, tc_args) <- splitTyConApp_maybe ty1 - , isDataTyCon tc + , isDataTyCon tc || isUnboxedTupleTyCon tc , let cons = tyConDataCons tc con = ASSERT( cons `lengthAtLeast` con_tag ) cons !! (con_tag - fIRST_TAG) = Just (con, tc_args, dataConInstArgTys con tc_args, co) From git at git.haskell.org Thu Dec 12 17:57:38 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 12 Dec 2013 17:57:38 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Temporarily disable nested CPR inside sum types (2d5f07a) Message-ID: <20131212175739.0A39A2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/2d5f07acd483677908117ba39062e6308114aae6/ghc >--------------------------------------------------------------- commit 2d5f07acd483677908117ba39062e6308114aae6 Author: Joachim Breitner Date: Tue Dec 10 10:12:46 2013 +0000 Temporarily disable nested CPR inside sum types >--------------------------------------------------------------- 2d5f07acd483677908117ba39062e6308114aae6 compiler/basicTypes/Demand.lhs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 326cfc1..acd1653 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -865,7 +865,7 @@ cprConRes isProd tag arg_ress | opt_NestedCprOff = Converges $ cutCPRResult flatCPRDepth $ retCon arg_ress | otherwise = Converges $ cutCPRResult maxCPRDepth $ retCon arg_ress where retCon | isProd = RetProd - | otherwise = RetSum tag + | otherwise = RetSum tag . map (const topRes) vanillaCprConRes :: Bool -> ConTag -> Arity -> DmdResult vanillaCprConRes isProd tag arity = cprConRes isProd tag (replicate arity topRes) From git at git.haskell.org Thu Dec 12 17:57:41 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 12 Dec 2013 17:57:41 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Check mAX_CPR_SIZE in dmdAnalVarApp (0f6b75c) Message-ID: <20131212175741.914342406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/0f6b75c17765bc70bd8eb3629da4bb8a375a9250/ghc >--------------------------------------------------------------- commit 0f6b75c17765bc70bd8eb3629da4bb8a375a9250 Author: Joachim Breitner Date: Thu Dec 5 18:01:34 2013 +0000 Check mAX_CPR_SIZE in dmdAnalVarApp >--------------------------------------------------------------- 0f6b75c17765bc70bd8eb3629da4bb8a375a9250 compiler/stranal/DmdAnal.lhs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index d5bf8a0..3c613b2 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -522,6 +522,8 @@ dmdAnalVarApp env dmd fun args | Just con <- isDataConWorkId_maybe fun -- Data constructor , isVanillaDataCon con , n_val_args == dataConRepArity con -- Saturated + , dataConRepArity con > 0 + , dataConRepArity con < 10 -- TODO: Sync with mAX_CPR_SIZE in MkId , let cpr_info = cprConRes (dataConTag con) arg_rets res_ty = foldl bothDmdType (DmdType emptyDmdEnv [] cpr_info) arg_tys = -- pprTrace "dmdAnalVarApp" (vcat [ ppr con, ppr args, ppr n_val_args, ppr cxt_ds From git at git.haskell.org Thu Dec 12 17:57:43 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 12 Dec 2013 17:57:43 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Add a warning to dmdTransformDataConSig (which I believe is dead code) (f609620) Message-ID: <20131212175743.B92F72406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/f609620d042944ef6fc7ffb247a3e0307d1d7a24/ghc >--------------------------------------------------------------- commit f609620d042944ef6fc7ffb247a3e0307d1d7a24 Author: Joachim Breitner Date: Tue Dec 10 13:56:08 2013 +0000 Add a warning to dmdTransformDataConSig (which I believe is dead code) >--------------------------------------------------------------- f609620d042944ef6fc7ffb247a3e0307d1d7a24 compiler/basicTypes/Demand.lhs | 1 + 1 file changed, 1 insertion(+) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index acd1653..0ee1b80 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -1519,6 +1519,7 @@ dmdTransformDataConSig arity (StrictSig (DmdType _ _ con_res)) (CD { sd = str, ud = abs }) | Just str_dmds <- go_str arity str , Just abs_dmds <- go_abs arity abs + , WARN( True, text "dmdTransformDataConSig indeed still in use" ) True = DmdType emptyDmdEnv (mkJointDmds str_dmds abs_dmds) con_res -- Must remember whether it's a product, hence con_res, not TopRes From git at git.haskell.org Thu Dec 12 17:57:45 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 12 Dec 2013 17:57:45 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Actually create a nested CPR worker-wrapper (046b6ca) Message-ID: <20131212175745.F105F2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/046b6ca575333772e2bf7264015eeb8dee4c4c75/ghc >--------------------------------------------------------------- commit 046b6ca575333772e2bf7264015eeb8dee4c4c75 Author: Joachim Breitner Date: Thu Dec 5 18:58:07 2013 +0000 Actually create a nested CPR worker-wrapper >--------------------------------------------------------------- 046b6ca575333772e2bf7264015eeb8dee4c4c75 compiler/basicTypes/Demand.lhs | 15 +++-- compiler/stranal/WwLib.lhs | 141 +++++++++++++++++++++++++--------------- 2 files changed, 95 insertions(+), 61 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 046b6ca575333772e2bf7264015eeb8dee4c4c75 From git at git.haskell.org Thu Dec 12 17:57:48 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 12 Dec 2013 17:57:48 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr's head updated: Add a warning to dmdTransformDataConSig (which I believe is dead code) (f609620) Message-ID: <20131212175748.2BA232406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/nested-cpr' now includes: 7558231 Do not generate given kind-equalities (fix Trac #8566) 0849d02 Better debug printing f114826 Spelling in comment 838da6f Some refactoring of Demand and DmdAnal ba78bf1 Do not split void functions 0558911 Assign strictness signatures to primitive operations 869f69f Guarding against silly shifts 80989de Improve the handling of used-once stuff 6b6a30d Move peelFV from DmdAnal to Demand 2b6a6a4 Clarify the default demand on demand environments 07b097a Remove dmdAnalArg and replace by easier to understand code 6de91c9 Add Note [non-algebraic or open body type warning] 43fa766 Split DmdResult into DmdResult and CPRResult 9fcf856 Do not export DmdResult constructors in Demand.lhs 715ed45 Rename postProcessDmdType to postProcessUnsat and use* to reuse* a5505be Make types of bothDmdType more precise 344ea58 Add Converges to DmdResult 653f7da In deferType, return convRes = Converges NoCPR 31c651e Initial work on Nested CPR 5da65a1 Comments and small refactor 9dee3f1 Fix a lubDmdResult equation 3318049 Unify RetProd and RetSum to RetCon in CPRResult 8c501a9 Use isTypeArg instead of isTyCoArg (forgot why) 298dfff Recover [CPR for sum types] (slightly differently) 7699aa5 Loop breakers are not allowed to have a Converges DmdResult 0f6b75c Check mAX_CPR_SIZE in dmdAnalVarApp b4a76c7 Add a flag -fnested-cpr-off to conveniently test the effect of nested CPR 046b6ca Actually create a nested CPR worker-wrapper 8ec4693 in Demand.lhs, remember what is a sum type 2d5f07a Temporarily disable nested CPR inside sum types ae465a0 Allow the CPR w/w to take unboxed tuples apart f609620 Add a warning to dmdTransformDataConSig (which I believe is dead code) From git at git.haskell.org Sat Dec 14 22:21:56 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 14 Dec 2013 22:21:56 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Refactor peelManyCalls (87cf401) Message-ID: <20131214222156.AAD7A2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/87cf4011bf62b0c676ffea8d3aca38bf08daf436/ghc >--------------------------------------------------------------- commit 87cf4011bf62b0c676ffea8d3aca38bf08daf436 Author: Joachim Breitner Date: Sat Dec 14 22:07:04 2013 +0100 Refactor peelManyCalls its first argument is just used for its length (the arity of the call). So changing the type to Int to reflect that. Also add a note [Demands from unsaturated function calls] that hopefully comprehensively and comprehensibly explains what is going on here. >--------------------------------------------------------------- 87cf4011bf62b0c676ffea8d3aca38bf08daf436 compiler/basicTypes/Demand.lhs | 71 ++++++++++++++++++++++++++++++---------- 1 file changed, 53 insertions(+), 18 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index ba4f789..54cc6d7 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -1172,21 +1172,60 @@ peelCallDmd (CD {sd = s, ud = u}) -- because the body isn't used at all! -- c.f. the Abs case in toCleanDmd -peelManyCalls :: [Demand] -> CleanDemand -> DeferAndUse -peelManyCalls arg_ds (CD { sd = str, ud = abs }) - = (go_str arg_ds str, go_abs arg_ds abs) +-- Peels that multiple nestings of calls clean demand and also returns +-- whether it was unsaturated (separately for strictness and usage +-- see Note [Demands from unsaturated function calls] +peelManyCalls :: Int -> CleanDemand -> DeferAndUse +peelManyCalls n (CD { sd = str, ud = abs }) + = (go_str n str, go_abs n abs) where - go_str :: [Demand] -> StrDmd -> Bool -- True <=> unsaturated, defer - go_str [] _ = False - go_str (_:_) HyperStr = False -- HyperStr = Call(HyperStr) - go_str (_:as) (SCall d') = go_str as d' - go_str _ _ = True + go_str :: Int -> StrDmd -> Bool -- True <=> unsaturated, defer + go_str 0 _ = False + go_str _ HyperStr = False -- == go_str (n-1) HyperStr, as HyperStr = Call(HyperStr) + go_str n (SCall d') = go_str (n-1) d' + go_str _ _ = True + + go_abs :: Int -> UseDmd -> Count -- Many <=> unsaturated, or at least + go_abs 0 _ = One -- one UCall Many in the demand + go_abs n (UCall One d') = go_abs (n-1) d' + go_abs _ _ = Many +\end{code} - go_abs :: [Demand] -> UseDmd -> Count -- Many <=> unsaturated, or at least - go_abs [] _ = One -- one UCall Many in the demand - go_abs (_:as) (UCall One d') = go_abs as d' - go_abs _ _ = Many +Note [Demands from unsaturated function calls] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + +Consider a demand transformer d1 -> d2 -> r for f. +If a sufficiently detailed demand is fed into this transformer, +e.g arising from "f x1 x2" in a strict, use-once context, +then d1 and d2 is precisely the demand unleashed onto x1 and x2 (similar for +the free variable environment) and furthermore the result information r is the +one we want to use. + +But the demand fed into f might be less than . There are a few cases: + * Not enough demand on the strictness side: + - In that case, we need to zap all strictness in the demand on arguments and + free variables. + - Furthermore, we need to remove CPR information (after all, "f x1" surely + does not return a constructor). + - And finally, if r said that f would (possible or definitely) diverge when + called with two arguments, then "f x1" may diverge. So we use topRes here. + (We could return "Converges NoCPR" if f would converge for sure, but that + information would currently not be useful in any way.) + * Not enough demand from the usage side: The missing usage can expanded using + UCall Many, therefore this is subsumed by the third case: + * At least one of the uses has a cardinality of Many. + - Even if f puts a One demand on any of its argument or free variables, if + we call f multiple times, we may evaluate this argument or free variable + multiple times. So forget about any occurrence of "One" in the demand. + +In dmdTransformSig, we call peelManyCalls to find out if we are in any of these +cases, and then call postProcessUnsat to reduce the demand appropriately. + +Similarly, dmdTransformDictSelSig and dmdAnal, when analyzing a Lambda, use +peelCallDmd, which peels only one level, but also returns the demand put on the +body of the function. +\begin{code} peelFV :: DmdType -> Var -> (DmdType, Demand) peelFV (DmdType fv ds res) id = -- pprTrace "rfv" (ppr id <+> ppr dmd $$ ppr fv) (DmdType fv' ds res, dmd) @@ -1359,12 +1398,8 @@ dmdTransformSig :: StrictSig -> CleanDemand -> DmdType -- signature is fun_sig, with demand dmd. We return the demand -- that the function places on its context (eg its args) dmdTransformSig (StrictSig dmd_ty@(DmdType _ arg_ds _)) cd - = postProcessUnsat (peelManyCalls arg_ds cd) dmd_ty - -- NB: it's important to use postProcessUnsat, and not - -- just return nopDmdType for unsaturated calls - -- Consider let { f x y = p + x } in f 1 - -- The application isn't saturated, but we must nevertheless propagate - -- a lazy demand for p! + = postProcessUnsat (peelManyCalls (length arg_ds) cd) dmd_ty + -- see Note [Demands from unsaturated function calls] dmdTransformDataConSig :: Arity -> StrictSig -> CleanDemand -> DmdType -- Same as dmdTransformSig but for a data constructor (worker), From git at git.haskell.org Sat Dec 14 22:21:58 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 14 Dec 2013 22:21:58 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Disentangle postProcessDmdTypeM and postProcessUnsat (113f7d9) Message-ID: <20131214222159.D99662406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/113f7d998dbf2f1d1320e825ba833a0f9b194265/ghc >--------------------------------------------------------------- commit 113f7d998dbf2f1d1320e825ba833a0f9b194265 Author: Joachim Breitner Date: Mon Dec 9 18:40:09 2013 +0000 Disentangle postProcessDmdTypeM and postProcessUnsat Make different postProcess code paths for function arguments (which are post-processed just to be both'ed) and unsaturated functions (which are post-processed for other reasons.) >--------------------------------------------------------------- 113f7d998dbf2f1d1320e825ba833a0f9b194265 compiler/basicTypes/Demand.lhs | 14 +++++++++++++- 1 file changed, 13 insertions(+), 1 deletion(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 54cc6d7..e4f49a9 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -1131,7 +1131,19 @@ postProcessDmdTypeM Nothing _ = nopDmdType -- Incoming demand was Absent, so just discard all usage information -- We only processed the thing at all to analyse the body -- See Note [Always analyse in virgin pass] -postProcessDmdTypeM (Just du) ty = postProcessUnsat du ty +postProcessDmdTypeM (Just du) (DmdType fv _ res_ty) + = DmdType (postProcessDmdEnv du fv) [] (postProcessDmdResult du res_ty) + +postProcessDmdResult :: DeferAndUse -> DmdResult -> DmdResult +postProcessDmdResult (True,_) r = topRes +postProcessDmdResult (False,_) r = r + +postProcessDmdEnv :: DeferAndUse -> DmdEnv -> DmdEnv +postProcessDmdEnv (True, Many) env = deferReuseEnv env +postProcessDmdEnv (False, Many) env = reuseEnv env +postProcessDmdEnv (True, One) env = deferEnv env +postProcessDmdEnv (False, One) env = env + postProcessUnsat :: DeferAndUse -> DmdType -> DmdType postProcessUnsat (True, Many) ty = deferReuse ty From git at git.haskell.org Sat Dec 14 22:22:01 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 14 Dec 2013 22:22:01 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Make types of bothDmdType more precise (0596028) Message-ID: <20131214222201.30B792406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/05960283bcb7d6243dd4398e29d66719d17398d1/ghc >--------------------------------------------------------------- commit 05960283bcb7d6243dd4398e29d66719d17398d1 Author: Joachim Breitner Date: Mon Dec 9 18:40:09 2013 +0000 Make types of bothDmdType more precise by only passing the demand on the free variables, and whether the argument (resp. scrunitee) may or will diverge. >--------------------------------------------------------------- 05960283bcb7d6243dd4398e29d66719d17398d1 compiler/basicTypes/Demand.lhs | 55 +++++++++++++++++++++++++--------------- compiler/stranal/DmdAnal.lhs | 9 +++---- 2 files changed, 39 insertions(+), 25 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index e4f49a9..bd68ea5 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -21,6 +21,7 @@ module Demand ( DmdType(..), dmdTypeDepth, lubDmdType, bothDmdType, nopDmdType, botDmdType, mkDmdType, addDemand, + BothDmdArg, mkBothDmdArg, toBothDmdArg, DmdEnv, emptyDmdEnv, peelFV, @@ -709,14 +710,15 @@ We have lubs, but not glbs; but that is ok. -- Constructed Product Result ------------------------------------------------------------------------ -data CPRResult = NoCPR -- Top of the lattice - | RetProd -- Returns a constructor from a product type - | RetSum ConTag -- Returns a constructor from a sum type with this tag +data Termination r = Diverges -- Definitely diverges + | Dunno r -- Might diverge or converge deriving( Eq, Show ) -data DmdResult = Diverges -- Definitely diverges - | Dunno CPRResult -- Might diverge or converge, but in the latter case the - -- result shape is described by CPRResult +type DmdResult = Termination CPRResult + +data CPRResult = NoCPR -- Top of the lattice + | RetProd -- Returns a constructor from a product type + | RetSum ConTag -- Returns a constructor from a data type deriving( Eq, Show ) lubCPR :: CPRResult -> CPRResult -> CPRResult @@ -733,7 +735,7 @@ lubDmdResult (Dunno c1) (Dunno c2) = Dunno (c1 `lubCPR` c2) -- defaultDmd (r1 `lubDmdResult` r2) = defaultDmd r1 `lubDmd` defaultDmd r2 -- (See Note [Default demand on free variables] for why) -bothDmdResult :: DmdResult -> DmdResult -> DmdResult +bothDmdResult :: DmdResult -> Termination () -> DmdResult -- See Note [Asymmetry of 'both' for DmdType and DmdResult] bothDmdResult _ Diverges = Diverges bothDmdResult r _ = r @@ -1024,13 +1026,25 @@ lubDmdType (DmdType fv1 ds1 r1) (DmdType fv2 ds2 r2) lub_ds ds1 [] = map (`lubDmd` resTypeArgDmd r2) ds1 lub_ds [] ds2 = map (resTypeArgDmd r1 `lubDmd`) ds2 -bothDmdType :: DmdType -> DmdType -> DmdType -bothDmdType (DmdType fv1 ds1 r1) (DmdType fv2 _ r2) + +type BothDmdArg = (DmdEnv, Termination ()) + +mkBothDmdArg :: DmdEnv -> BothDmdArg +mkBothDmdArg env = (env, Dunno ()) + +toBothDmdArg :: DmdType -> BothDmdArg +toBothDmdArg (DmdType fv _ r) = (fv, go r) + where + go (Dunno {}) = Dunno () + go Diverges = Diverges + +bothDmdType :: DmdType -> BothDmdArg -> DmdType +bothDmdType (DmdType fv1 ds1 r1) (fv2, t2) -- See Note [Asymmetry of 'both' for DmdType and DmdResult] -- 'both' takes the argument/result info from its *first* arg, -- using its second arg just for its free-var info. - = DmdType both_fv ds1 (r1 `bothDmdResult` r2) - where both_fv = plusVarEnv_CD bothDmd fv1 (defaultDmd r1) fv2 (defaultDmd r2) + = DmdType both_fv ds1 (r1 `bothDmdResult` t2) + where both_fv = plusVarEnv_CD bothDmd fv1 (defaultDmd r1) fv2 (defaultDmd t2) instance Outputable DmdType where ppr (DmdType fv ds res) @@ -1126,17 +1140,18 @@ toCleanDmd (JD { strd = s, absd = u }) -- This is used in dmdAnalStar when post-processing -- a function's argument demand. So we only care about what -- does to free variables, and whether it terminates. -postProcessDmdTypeM :: DeferAndUseM -> DmdType -> DmdType -postProcessDmdTypeM Nothing _ = nopDmdType +postProcessDmdTypeM :: DeferAndUseM -> DmdType -> BothDmdArg +postProcessDmdTypeM Nothing _ = (emptyDmdEnv, Dunno ()) -- Incoming demand was Absent, so just discard all usage information -- We only processed the thing at all to analyse the body -- See Note [Always analyse in virgin pass] postProcessDmdTypeM (Just du) (DmdType fv _ res_ty) - = DmdType (postProcessDmdEnv du fv) [] (postProcessDmdResult du res_ty) + = (postProcessDmdEnv du fv, postProcessDmdResult du res_ty) -postProcessDmdResult :: DeferAndUse -> DmdResult -> DmdResult -postProcessDmdResult (True,_) r = topRes -postProcessDmdResult (False,_) r = r +postProcessDmdResult :: DeferAndUse -> DmdResult -> Termination () +postProcessDmdResult (True,_) _ = topRes +postProcessDmdResult (False,_) (Dunno {}) = Dunno () +postProcessDmdResult (False,_) Diverges = Diverges postProcessDmdEnv :: DeferAndUse -> DmdEnv -> DmdEnv postProcessDmdEnv (True, Many) env = deferReuseEnv env @@ -1246,9 +1261,9 @@ peelFV (DmdType fv ds res) id = -- pprTrace "rfv" (ppr id <+> ppr dmd $$ ppr fv) -- See note [Default demand on free variables] dmd = lookupVarEnv fv id `orElse` defaultDmd res -defaultDmd :: DmdResult -> Demand -defaultDmd res | isBotRes res = botDmd - | otherwise = absDmd +defaultDmd :: Termination r -> Demand +defaultDmd Diverges = botDmd +defaultDmd _ = absDmd addDemand :: Demand -> DmdType -> DmdType addDemand dmd (DmdType fv ds res) = DmdType fv (dmd:ds) res diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index cbdcc67..a942c4e 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -115,7 +115,7 @@ dmdTransformThunkDmd e -- See |-* relation in the companion paper dmdAnalStar :: AnalEnv -> Demand -- This one takes a *Demand* - -> CoreExpr -> (DmdType, CoreExpr) + -> CoreExpr -> (BothDmdArg, CoreExpr) dmdAnalStar env dmd e | (cd, defer_and_use) <- toCleanDmd dmd , (dmd_ty, e') <- dmdAnal env cd e @@ -255,7 +255,7 @@ dmdAnal env dmd (Case scrut case_bndr ty [alt@(DataAlt dc, _, _)]) scrut_dmd = scrut_dmd1 `bothCleanDmd` scrut_dmd2 (scrut_ty, scrut') = dmdAnal env scrut_dmd scrut - res_ty = alt_ty1 `bothDmdType` scrut_ty + res_ty = alt_ty1 `bothDmdType` toBothDmdArg scrut_ty in -- pprTrace "dmdAnal:Case1" (vcat [ text "scrut" <+> ppr scrut -- , text "dmd" <+> ppr dmd @@ -271,7 +271,7 @@ dmdAnal env dmd (Case scrut case_bndr ty alts) (alt_tys, alts') = mapAndUnzip (dmdAnalAlt env dmd) alts (scrut_ty, scrut') = dmdAnal env cleanEvalDmd scrut (alt_ty, case_bndr') = annotateBndr env (foldr lubDmdType botDmdType alt_tys) case_bndr - res_ty = alt_ty `bothDmdType` scrut_ty + res_ty = alt_ty `bothDmdType` toBothDmdArg scrut_ty in -- pprTrace "dmdAnal:Case2" (vcat [ text "scrut" <+> ppr scrut -- , text "scrut_ty" <+> ppr scrut_ty @@ -509,7 +509,6 @@ dmdTransform env var dmd | otherwise -- Local non-letrec-bound thing = unitVarDmd var (mkOnceUsedDmd dmd) - \end{code} %************************************************************************ @@ -698,7 +697,7 @@ addVarDmd (DmdType fv ds res) var dmd addLazyFVs :: DmdType -> DmdEnv -> DmdType addLazyFVs dmd_ty lazy_fvs - = dmd_ty `bothDmdType` mkDmdType lazy_fvs [] topRes + = dmd_ty `bothDmdType` mkBothDmdArg lazy_fvs -- Using bothDmdType (rather than just both'ing the envs) -- is vital. Consider -- let f = \x -> (x,y) From git at git.haskell.org Sat Dec 14 22:22:03 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 14 Dec 2013 22:22:03 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Add Converges to DmdResult (40e46e6) Message-ID: <20131214222203.DBAEA2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/40e46e6c738ba3297a6187047828b25fe393acc7/ghc >--------------------------------------------------------------- commit 40e46e6c738ba3297a6187047828b25fe393acc7 Author: Joachim Breitner Date: Thu Dec 12 15:45:19 2013 +0000 Add Converges to DmdResult to detect definite convergence (required for nested CPR). >--------------------------------------------------------------- 40e46e6c738ba3297a6187047828b25fe393acc7 compiler/basicTypes/Demand.lhs | 41 ++++++++++++++++++++++++++++------------ 1 file changed, 29 insertions(+), 12 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index bd68ea5..7e455f8 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -691,8 +691,8 @@ splitProdDmd_maybe (JD {strd = s, absd = u}) DmdResult: Dunno CPRResult - / - Diverges + / \ + Diverges Converges CPRResult CPRResult: NoCPR @@ -700,7 +700,7 @@ CPRResult: NoCPR RetProd RetSum ConTag -Product contructors return (Dunno (RetProd rs)) +Product contructors return (Converges (RetProd rs)) In a fixpoint iteration, start from Diverges We have lubs, but not glbs; but that is ok. @@ -711,6 +711,7 @@ We have lubs, but not glbs; but that is ok. ------------------------------------------------------------------------ data Termination r = Diverges -- Definitely diverges + | Converges r -- Definitely converges | Dunno r -- Might diverge or converge deriving( Eq, Show ) @@ -729,7 +730,11 @@ lubCPR _ _ = NoCPR lubDmdResult :: DmdResult -> DmdResult -> DmdResult lubDmdResult Diverges r = r +lubDmdResult (Converges c1) Diverges = Converges c1 +lubDmdResult (Converges c1) (Converges c2) = Converges (c1 `lubCPR` c2) +lubDmdResult (Converges c1) (Dunno c2) = Dunno (c1 `lubCPR` c2) lubDmdResult (Dunno c1) Diverges = Dunno c1 +lubDmdResult (Dunno c1) (Converges c2) = Dunno (c1 `lubCPR` c2) lubDmdResult (Dunno c1) (Dunno c2) = Dunno (c1 `lubCPR` c2) -- This needs to commute with defaultDmd, i.e. -- defaultDmd (r1 `lubDmdResult` r2) = defaultDmd r1 `lubDmd` defaultDmd r2 @@ -738,6 +743,7 @@ lubDmdResult (Dunno c1) (Dunno c2) = Dunno (c1 `lubCPR` c2) bothDmdResult :: DmdResult -> Termination () -> DmdResult -- See Note [Asymmetry of 'both' for DmdType and DmdResult] bothDmdResult _ Diverges = Diverges +bothDmdResult (Converges c1) (Dunno {}) = Dunno c1 bothDmdResult r _ = r -- This needs to commute with defaultDmd, i.e. -- defaultDmd (r1 `bothDmdResult` r2) = defaultDmd r1 `bothDmd` defaultDmd r2 @@ -745,6 +751,7 @@ bothDmdResult r _ = r instance Outputable DmdResult where ppr Diverges = char 'b' + ppr (Converges c) = char 't' <> ppr c ppr (Dunno c) = char 'd' <> ppr c instance Outputable CPRResult where @@ -754,6 +761,7 @@ instance Outputable CPRResult where seqDmdResult :: DmdResult -> () seqDmdResult Diverges = () +seqDmdResult (Converges c) = seqCPRResult c seqDmdResult (Dunno c) = seqCPRResult c seqCPRResult :: CPRResult -> () @@ -774,17 +782,17 @@ botRes = Diverges cprSumRes :: ConTag -> DmdResult cprSumRes tag | opt_CprOff = topRes - | otherwise = Dunno $ RetSum tag + | otherwise = Converges $ RetSum tag cprProdRes :: [DmdType] -> DmdResult cprProdRes _arg_tys | opt_CprOff = topRes - | otherwise = Dunno $ RetProd + | otherwise = Converges $ RetProd vanillaCprProdRes :: Arity -> DmdResult vanillaCprProdRes _arity | opt_CprOff = topRes - | otherwise = Dunno $ RetProd + | otherwise = Converges $ RetProd isTopRes :: DmdResult -> Bool isTopRes (Dunno NoCPR) = True @@ -798,6 +806,7 @@ trimCPRInfo :: Bool -> Bool -> DmdResult -> DmdResult trimCPRInfo trim_all trim_sums res = trimR res where + trimR (Converges c) = Converges (trimC c) trimR (Dunno c) = Dunno (trimC c) trimR Diverges = Diverges @@ -811,6 +820,7 @@ returnsCPR :: DmdResult -> Bool returnsCPR dr = isJust (returnsCPR_maybe dr) returnsCPR_maybe :: DmdResult -> Maybe ConTag +returnsCPR_maybe (Converges c) = retCPR_maybe c returnsCPR_maybe (Dunno c) = retCPR_maybe c returnsCPR_maybe Diverges = Nothing @@ -1036,6 +1046,7 @@ toBothDmdArg :: DmdType -> BothDmdArg toBothDmdArg (DmdType fv _ r) = (fv, go r) where go (Dunno {}) = Dunno () + go (Converges {}) = Converges () go Diverges = Diverges bothDmdType :: DmdType -> BothDmdArg -> DmdType @@ -1069,7 +1080,7 @@ botDmdType = DmdType emptyDmdEnv [] botRes cprProdDmdType :: Arity -> DmdType cprProdDmdType _arity - = DmdType emptyDmdEnv [] (Dunno RetProd) + = DmdType emptyDmdEnv [] (Converges RetProd) isNopDmdType :: DmdType -> Bool isNopDmdType (DmdType env [] res) @@ -1098,7 +1109,7 @@ splitDmdTy ty@(DmdType _ [] res_ty) = (resTypeArgDmd res_ty, ty) -- exit? -- * We have to kill all strictness demands (i.e. lub with a lazy demand) -- * We can keep demand information (i.e. lub with an absent deman) --- * We have to kill definite divergence +-- * We have to kill definite divergence and definite convergence -- * We can keep CPR information. -- See Note [IO hack in the demand analyser] deferAfterIO :: DmdType -> DmdType @@ -1107,6 +1118,7 @@ deferAfterIO d@(DmdType _ _ res) = DmdType fv ds _ -> DmdType fv ds (defer_res res) where defer_res Diverges = topRes + defer_res (Converges r) = Dunno r defer_res r = r strictenDmd :: JointDmd -> CleanDemand @@ -1149,9 +1161,12 @@ postProcessDmdTypeM (Just du) (DmdType fv _ res_ty) = (postProcessDmdEnv du fv, postProcessDmdResult du res_ty) postProcessDmdResult :: DeferAndUse -> DmdResult -> Termination () -postProcessDmdResult (True,_) _ = topRes -postProcessDmdResult (False,_) (Dunno {}) = Dunno () -postProcessDmdResult (False,_) Diverges = Diverges + -- if we use it lazily, there cannot be divergence worrying us + -- (Otherwise we'd lose the termination information of constructors in in dmdAnalVarApp, for example) +postProcessDmdResult (True,_) _ = topRes +postProcessDmdResult (False,_) (Dunno {}) = Dunno () +postProcessDmdResult (False,_) (Converges {}) = Converges () +postProcessDmdResult (False,_) Diverges = Diverges postProcessDmdEnv :: DeferAndUse -> DmdEnv -> DmdEnv postProcessDmdEnv (True, Many) env = deferReuseEnv env @@ -1722,11 +1737,13 @@ instance Binary DmdType where instance Binary DmdResult where put_ bh (Dunno c) = do { putByte bh 0; put_ bh c } - put_ bh Diverges = putByte bh 2 + put_ bh (Converges c) = do { putByte bh 1; put_ bh c } + put_ bh Diverges = putByte bh 3 get bh = do { h <- getByte bh ; case h of 0 -> do { c <- get bh; return (Dunno c) } + 1 -> do { c <- get bh; return (Converges c) } _ -> return Diverges } instance Binary CPRResult where From git at git.haskell.org Sat Dec 14 22:22:06 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 14 Dec 2013 22:22:06 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: In deferType, return convRes = Converges NoCPR (ed27ce6) Message-ID: <20131214222206.31FED2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/ed27ce6c0d51253f7b2a25054d06d01bb81512be/ghc >--------------------------------------------------------------- commit ed27ce6c0d51253f7b2a25054d06d01bb81512be Author: Joachim Breitner Date: Wed Dec 4 16:55:18 2013 +0000 In deferType, return convRes = Converges NoCPR because this is the right-identity to `bothDmdResult`, and this is the right thing to do in a lazy context. >--------------------------------------------------------------- ed27ce6c0d51253f7b2a25054d06d01bb81512be compiler/basicTypes/Demand.lhs | 7 ++++--- 1 file changed, 4 insertions(+), 3 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 7e455f8..cadec37 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -776,8 +776,9 @@ seqCPRResult RetProd = () -- [cprRes] lets us switch off CPR analysis -- by making sure that everything uses TopRes -topRes, botRes :: DmdResult +topRes, convRes, botRes :: DmdResult topRes = Dunno NoCPR +convRes = Converges NoCPR botRes = Diverges cprSumRes :: ConTag -> DmdResult @@ -1182,9 +1183,9 @@ postProcessUnsat (True, One) ty = deferType ty postProcessUnsat (False, One) ty = ty deferType, reuseType, deferReuse :: DmdType -> DmdType -deferType (DmdType fv ds _) = DmdType (deferEnv fv) (map deferDmd ds) topRes +deferType (DmdType fv ds _) = DmdType (deferEnv fv) (map deferDmd ds) convRes reuseType (DmdType fv ds res_ty) = DmdType (reuseEnv fv) (map reuseDmd ds) res_ty -deferReuse (DmdType fv ds _) = DmdType (deferReuseEnv fv) (map deferReuseDmd ds) topRes +deferReuse (DmdType fv ds _) = DmdType (deferReuseEnv fv) (map deferReuseDmd ds) convRes deferEnv, reuseEnv, deferReuseEnv :: DmdEnv -> DmdEnv deferEnv fv = mapVarEnv deferDmd fv From git at git.haskell.org Sat Dec 14 22:22:08 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 14 Dec 2013 22:22:08 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Initial work on Nested CPR (5ef4b19) Message-ID: <20131214222208.9C7122406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/5ef4b19e069b8068e630111a43cfe43263ecf2b3/ghc >--------------------------------------------------------------- commit 5ef4b19e069b8068e630111a43cfe43263ecf2b3 Author: Simon Peyton Jones Date: Mon Nov 25 09:59:16 2013 +0000 Initial work on Nested CPR >--------------------------------------------------------------- 5ef4b19e069b8068e630111a43cfe43263ecf2b3 compiler/basicTypes/Demand.lhs | 137 ++++++++++++++++++++++++---------------- compiler/stranal/DmdAnal.lhs | 111 ++++++++++++++++++++++---------- 2 files changed, 160 insertions(+), 88 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 5ef4b19e069b8068e630111a43cfe43263ecf2b3 From git at git.haskell.org Sat Dec 14 22:22:10 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 14 Dec 2013 22:22:10 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Temporarily disable nested CPR inside sum types (960873a) Message-ID: <20131214222210.D8A372406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/960873a248e1766ba5f8595ca5e7c866ac5ce348/ghc >--------------------------------------------------------------- commit 960873a248e1766ba5f8595ca5e7c866ac5ce348 Author: Joachim Breitner Date: Tue Dec 10 10:12:46 2013 +0000 Temporarily disable nested CPR inside sum types >--------------------------------------------------------------- 960873a248e1766ba5f8595ca5e7c866ac5ce348 compiler/basicTypes/Demand.lhs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 721cfc9..8abcbcd 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -865,7 +865,7 @@ cprConRes isProd tag arg_ress | opt_NestedCprOff = Converges $ cutCPRResult flatCPRDepth $ retCon arg_ress | otherwise = Converges $ cutCPRResult maxCPRDepth $ retCon arg_ress where retCon | isProd = RetProd - | otherwise = RetSum tag + | otherwise = RetSum tag . map (const topRes) vanillaCprConRes :: Bool -> ConTag -> Arity -> DmdResult vanillaCprConRes isProd tag arity = cprConRes isProd tag (replicate arity topRes) From git at git.haskell.org Sat Dec 14 22:22:13 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 14 Dec 2013 22:22:13 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Add a warning to dmdTransformDataConSig (which I believe is dead code) (bb26ae8) Message-ID: <20131214222213.33C6E2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/bb26ae8fe2c7cb7337739f7a319f67c2d13e0a48/ghc >--------------------------------------------------------------- commit bb26ae8fe2c7cb7337739f7a319f67c2d13e0a48 Author: Joachim Breitner Date: Tue Dec 10 13:56:08 2013 +0000 Add a warning to dmdTransformDataConSig (which I believe is dead code) >--------------------------------------------------------------- bb26ae8fe2c7cb7337739f7a319f67c2d13e0a48 compiler/basicTypes/Demand.lhs | 1 + 1 file changed, 1 insertion(+) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 8abcbcd..865287f 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -1519,6 +1519,7 @@ dmdTransformDataConSig arity (StrictSig (DmdType _ _ con_res)) (CD { sd = str, ud = abs }) | Just str_dmds <- go_str arity str , Just abs_dmds <- go_abs arity abs + , WARN( True, text "dmdTransformDataConSig indeed still in use" ) True = DmdType emptyDmdEnv (mkJointDmds str_dmds abs_dmds) con_res -- Must remember whether it's a product, hence con_res, not TopRes From git at git.haskell.org Sat Dec 14 22:22:15 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 14 Dec 2013 22:22:15 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Allow the CPR w/w to take unboxed tuples apart (20df148) Message-ID: <20131214222215.5D4452406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/20df14838a3c0868e012d4f2f0041bf89e8c3b20/ghc >--------------------------------------------------------------- commit 20df14838a3c0868e012d4f2f0041bf89e8c3b20 Author: Joachim Breitner Date: Thu Nov 28 10:29:47 2013 +0000 Allow the CPR w/w to take unboxed tuples apart >--------------------------------------------------------------- 20df14838a3c0868e012d4f2f0041bf89e8c3b20 compiler/stranal/WwLib.lhs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/stranal/WwLib.lhs b/compiler/stranal/WwLib.lhs index ce4112c..5168d8f 100644 --- a/compiler/stranal/WwLib.lhs +++ b/compiler/stranal/WwLib.lhs @@ -502,7 +502,7 @@ deepSplitCprType_maybe :: ConTag -> Type -> Maybe (DataCon, [Type], [Type], Coer deepSplitCprType_maybe con_tag ty | let (co, ty1) = topNormaliseNewType_maybe ty `orElse` (mkReflCo Representational ty, ty) , Just (tc, tc_args) <- splitTyConApp_maybe ty1 - , isDataTyCon tc + , isDataTyCon tc || isUnboxedTupleTyCon tc , let cons = tyConDataCons tc con = ASSERT( cons `lengthAtLeast` con_tag ) cons !! (con_tag - fIRST_TAG) = Just (con, tc_args, dataConInstArgTys con tc_args, co) From git at git.haskell.org Sat Dec 14 22:22:17 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 14 Dec 2013 22:22:17 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Add a flag -fnested-cpr-off to conveniently test the effect of nested CPR (fb9b3ab) Message-ID: <20131214222217.A88092406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/fb9b3ab9f9db118bf14bab3e48bbf66638fa8426/ghc >--------------------------------------------------------------- commit fb9b3ab9f9db118bf14bab3e48bbf66638fa8426 Author: Joachim Breitner Date: Wed Dec 4 09:14:26 2013 +0000 Add a flag -fnested-cpr-off to conveniently test the effect of nested CPR >--------------------------------------------------------------- fb9b3ab9f9db118bf14bab3e48bbf66638fa8426 compiler/basicTypes/Demand.lhs | 29 ++++++++++++++++++++--------- compiler/main/StaticFlags.hs | 9 +++++++-- 2 files changed, 27 insertions(+), 11 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index ead28e3..6fd8076 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -807,19 +807,29 @@ getDmdResult _ = topRes maxCPRDepth :: Int maxCPRDepth = 3 +-- This is the depth we use with -fnested-cpr-off, in order +-- to get precisely the same behaviour as before introduction of nested cpr +-- -fnested-cpr-off can eventually be removed if nested cpr is deemd to be +-- a good thing always. +flatCPRDepth :: Int +flatCPRDepth = 1 + -- With nested CPR, DmdResult can be arbitrarily deep; consider e.g. the -- DmdResult of repeat +-- -- So we need to forget information at a certain depth. We do that at all points -- where we are building RetCon constructors. -cutDmdResult :: Int -> DmdResult -> DmdResult -cutDmdResult 0 _ = topRes -cutDmdResult _ Diverges = Diverges -cutDmdResult n (Converges c) = Converges (cutCPRResult n c) -cutDmdResult n (Dunno c) = Dunno (cutCPRResult n c) - cutCPRResult :: Int -> CPRResult -> CPRResult -cutCPRResult _ NoCPR = NoCPR +cutCPRResult 0 _ = NoCPR +cutCPRResult _ NoCPR = NoCPR cutCPRResult n (RetCon tag rs) = RetCon tag (map (cutDmdResult (n-1)) rs) + where + cutDmdResult :: Int -> DmdResult -> DmdResult + cutDmdResult 0 _ = topRes + cutDmdResult _ Diverges = Diverges + cutDmdResult n (Converges c) = Converges (cutCPRResult n c) + cutDmdResult n (Dunno c) = Dunno (cutCPRResult n c) + -- Forget that something might converge for sure divergeDmdResult :: DmdResult -> DmdResult @@ -834,8 +844,9 @@ forgetCPR (Dunno _) = Dunno NoCPR cprConRes :: ConTag -> [DmdResult] -> DmdResult cprConRes tag arg_ress - | opt_CprOff = topRes - | otherwise = Converges $ cutCPRResult maxCPRDepth $ RetCon tag arg_ress + | opt_CprOff = topRes + | opt_NestedCprOff = Converges $ cutCPRResult flatCPRDepth $ RetCon tag arg_ress + | otherwise = Converges $ cutCPRResult maxCPRDepth $ RetCon tag arg_ress vanillaCprConRes :: ConTag -> Arity -> DmdResult vanillaCprConRes tag arity diff --git a/compiler/main/StaticFlags.hs b/compiler/main/StaticFlags.hs index 01dc3b7..feb7235 100644 --- a/compiler/main/StaticFlags.hs +++ b/compiler/main/StaticFlags.hs @@ -27,6 +27,7 @@ module StaticFlags ( -- optimisation opts opt_NoStateHack, opt_CprOff, + opt_NestedCprOff, opt_NoOptCoercion, -- For the parser @@ -140,7 +141,8 @@ flagsStaticNames :: [String] flagsStaticNames = [ "fno-state-hack", "fno-opt-coercion", - "fcpr-off" + "fcpr-off", + "fnested-cpr-off" ] -- We specifically need to discard static flags for clients of the @@ -195,10 +197,13 @@ opt_NoDebugOutput = lookUp (fsLit "-dno-debug-output") opt_NoStateHack :: Bool opt_NoStateHack = lookUp (fsLit "-fno-state-hack") --- Switch off CPR analysis in the new demand analyser +-- Switch off CPR analysis in the demand analyser opt_CprOff :: Bool opt_CprOff = lookUp (fsLit "-fcpr-off") +opt_NestedCprOff :: Bool +opt_NestedCprOff = lookUp (fsLit "-fnested-cpr-off") + opt_NoOptCoercion :: Bool opt_NoOptCoercion = lookUp (fsLit "-fno-opt-coercion") From git at git.haskell.org Sat Dec 14 22:22:20 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 14 Dec 2013 22:22:20 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Recover [CPR for sum types] (slightly differently) (614b965) Message-ID: <20131214222220.308B22406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/614b96520e84a91bc80c85df51046e6ee601a52d/ghc >--------------------------------------------------------------- commit 614b96520e84a91bc80c85df51046e6ee601a52d Author: Joachim Breitner Date: Thu Nov 28 11:17:16 2013 +0000 Recover [CPR for sum types] (slightly differently) >--------------------------------------------------------------- 614b96520e84a91bc80c85df51046e6ee601a52d compiler/basicTypes/Demand.lhs | 24 ++++++++---------------- compiler/stranal/DmdAnal.lhs | 14 ++++++++------ 2 files changed, 16 insertions(+), 22 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 4a31dd4..0a8c9ff 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -30,10 +30,9 @@ module Demand ( isBotRes, isTopRes, getDmdResult, resTypeArgDmd, topRes, botRes, cprConRes, vanillaCprConRes, appIsBottom, isBottomingSig, pprIfaceStrictSig, - trimCPRInfo, returnsCPR, returnsCPR_maybe, + returnsCPR, returnsCPR_maybe, forgetCPR, StrictSig(..), mkStrictSig, mkClosedStrictSig, nopSig, botSig, cprProdSig, isNopSig, splitStrictSig, increaseStrictSigArity, - seqDemand, seqDemandList, seqDmdType, seqStrictSig, evalDmd, cleanEvalDmd, cleanEvalProdDmd, isStrictDmd, @@ -826,6 +825,13 @@ cutCPRResult :: Int -> CPRResult -> CPRResult cutCPRResult _ NoCPR = NoCPR cutCPRResult n (RetCon tag rs) = RetCon tag (map (cutDmdResult (n-1)) rs) +-- Forget the CPR information, but remember if it converges or diverges +-- Used for non-strict thunks and non-top-level things with sum type +forgetCPR :: DmdResult -> DmdResult +forgetCPR Diverges = Diverges +forgetCPR (Converges _) = Converges NoCPR +forgetCPR (Dunno _) = Dunno NoCPR + cprConRes :: ConTag -> [DmdResult] -> DmdResult cprConRes tag arg_ress | opt_CprOff = topRes @@ -844,20 +850,6 @@ isBotRes :: DmdResult -> Bool isBotRes Diverges = True isBotRes _ = False --- TODO: This currently ignores trim_sums. Evaluate if still required, and fix --- Note [CPR for sum types] -trimCPRInfo :: Bool -> Bool -> DmdResult -> DmdResult -trimCPRInfo trim_all _trim_sums res - = trimR res - where - trimR (Converges c) = Converges (trimC c) - trimR (Dunno c) = Dunno (trimC c) - trimR Diverges = Diverges - - trimC (RetCon n rs) | trim_all = NoCPR - | otherwise = RetCon n (map trimR rs) - trimC NoCPR = NoCPR - returnsCPR :: DmdResult -> Bool returnsCPR dr = isJust (returnsCPR_maybe dr) diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index 0da1085..ea1a588 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -655,9 +655,10 @@ dmdAnalRhs top_lvl rec_flag env id rhs -- See Note [NOINLINE and strictness] -- See Note [Product demands for function body] - body_dmd = case deepSplitProductType_maybe (exprType body) of - Nothing -> cleanEvalDmd - Just (dc, _, _, _) -> cleanEvalProdDmd (dataConRepArity dc) + (is_sum_type, body_dmd) + = case deepSplitProductType_maybe (exprType body) of + Nothing -> (True, cleanEvalDmd) + Just (dc, _, _, _) -> (False, cleanEvalProdDmd (dataConRepArity dc)) -- See Note [Lazy and unleashable free variables] -- See Note [Aggregated demand for cardinality] @@ -667,9 +668,10 @@ dmdAnalRhs top_lvl rec_flag env id rhs (lazy_fv, sig_fv) = splitFVs is_thunk rhs_fv1 - rhs_res' = trimCPRInfo trim_all trim_sums rhs_res - trim_all = is_thunk && not_strict - trim_sums = not (isTopLevel top_lvl) -- See Note [CPR for sum types] + -- Note [CPR for sum types] + rhs_res' | (is_sum_type && not (isTopLevel top_lvl)) || + (is_thunk && not_strict) = forgetCPR rhs_res + | otherwise = rhs_res -- See Note [CPR for thunks] is_thunk = not (exprIsHNF rhs) From git at git.haskell.org Sat Dec 14 22:22:22 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 14 Dec 2013 22:22:22 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: in Demand.lhs, remember what is a sum type (43c93dc) Message-ID: <20131214222222.A46132406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/43c93dc066275b42afc78b16c774c013c5fb166a/ghc >--------------------------------------------------------------- commit 43c93dc066275b42afc78b16c774c013c5fb166a Author: Joachim Breitner Date: Tue Dec 10 09:15:09 2013 +0000 in Demand.lhs, remember what is a sum type because we want to zap CPR information for sum types not only on the outermost level, but also nested. See Note [CPR for sum types] This comes up in sublist in Listplikefns in nofib?s boyer2. >--------------------------------------------------------------- 43c93dc066275b42afc78b16c774c013c5fb166a compiler/basicTypes/DataCon.lhs | 4 +++ compiler/basicTypes/Demand.lhs | 76 ++++++++++++++++++++++++--------------- compiler/basicTypes/MkId.lhs | 2 +- compiler/stranal/DmdAnal.lhs | 39 ++++++++++++-------- 4 files changed, 77 insertions(+), 44 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 43c93dc066275b42afc78b16c774c013c5fb166a From git at git.haskell.org Sat Dec 14 22:22:24 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 14 Dec 2013 22:22:24 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Loop breakers are not allowed to have a Converges DmdResult (f12a8f3) Message-ID: <20131214222224.B29942406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/f12a8f3c11956669540212c75bd859f4f46d2efc/ghc >--------------------------------------------------------------- commit f12a8f3c11956669540212c75bd859f4f46d2efc Author: Joachim Breitner Date: Tue Nov 26 10:18:35 2013 +0000 Loop breakers are not allowed to have a Converges DmdResult >--------------------------------------------------------------- f12a8f3c11956669540212c75bd859f4f46d2efc compiler/basicTypes/Demand.lhs | 19 +++++++++++-------- compiler/stranal/DmdAnal.lhs | 5 ++++- 2 files changed, 15 insertions(+), 9 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 0a8c9ff..ead28e3 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -33,6 +33,7 @@ module Demand ( returnsCPR, returnsCPR_maybe, forgetCPR, StrictSig(..), mkStrictSig, mkClosedStrictSig, nopSig, botSig, cprProdSig, isNopSig, splitStrictSig, increaseStrictSigArity, + sigMayConverge, seqDemand, seqDemandList, seqDmdType, seqStrictSig, evalDmd, cleanEvalDmd, cleanEvalProdDmd, isStrictDmd, @@ -806,15 +807,10 @@ getDmdResult _ = topRes maxCPRDepth :: Int maxCPRDepth = 3 --- With nested CPR, DmdResult can be arbitrarily deep; consider --- data Rec1 = Foo Rec2 Rec2 --- data Rec2 = Bar Rec1 Rec1 --- --- x = Foo y y --- y = Bar x x --- +-- With nested CPR, DmdResult can be arbitrarily deep; consider e.g. the +-- DmdResult of repeat -- So we need to forget information at a certain depth. We do that at all points --- where we are constructing new RetCon constructors. +-- where we are building RetCon constructors. cutDmdResult :: Int -> DmdResult -> DmdResult cutDmdResult 0 _ = topRes cutDmdResult _ Diverges = Diverges @@ -825,6 +821,10 @@ cutCPRResult :: Int -> CPRResult -> CPRResult cutCPRResult _ NoCPR = NoCPR cutCPRResult n (RetCon tag rs) = RetCon tag (map (cutDmdResult (n-1)) rs) +-- Forget that something might converge for sure +divergeDmdResult :: DmdResult -> DmdResult +divergeDmdResult r = r `lubDmdResult` botRes + -- Forget the CPR information, but remember if it converges or diverges -- Used for non-strict thunks and non-top-level things with sum type forgetCPR :: DmdResult -> DmdResult @@ -1445,6 +1445,9 @@ botSig = StrictSig botDmdType cprProdSig :: Arity -> StrictSig cprProdSig arity = StrictSig (cprProdDmdType arity) +sigMayConverge :: StrictSig -> StrictSig +sigMayConverge (StrictSig (DmdType env ds res)) = (StrictSig (DmdType env ds (divergeDmdResult res))) + argsOneShots :: StrictSig -> Arity -> [[OneShotInfo]] argsOneShots (StrictSig (DmdType _ arg_ds _)) n_val_args = go arg_ds diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index ea1a588..d5bf8a0 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -1084,7 +1084,10 @@ updSigEnv env sigs = env { ae_sigs = sigs } extendAnalEnv :: TopLevelFlag -> AnalEnv -> Id -> StrictSig -> AnalEnv extendAnalEnv top_lvl env var sig - = env { ae_sigs = extendSigEnv top_lvl (ae_sigs env) var sig } + = env { ae_sigs = extendSigEnv top_lvl (ae_sigs env) var sig' } + where + sig' | isWeakLoopBreaker (idOccInfo var) = sigMayConverge sig + | otherwise = sig extendSigEnv :: TopLevelFlag -> SigEnv -> Id -> StrictSig -> SigEnv extendSigEnv top_lvl sigs var sig = extendVarEnv sigs var (sig, top_lvl) From git at git.haskell.org Sat Dec 14 22:22:26 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 14 Dec 2013 22:22:26 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Unify RetProd and RetSum to RetCon in CPRResult (17f6221) Message-ID: <20131214222226.E15A12406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/17f6221dc8b83a9c4f3c5b21ad0b8fc0930d895a/ghc >--------------------------------------------------------------- commit 17f6221dc8b83a9c4f3c5b21ad0b8fc0930d895a Author: Joachim Breitner Date: Thu Dec 5 16:13:41 2013 +0000 Unify RetProd and RetSum to RetCon in CPRResult >--------------------------------------------------------------- 17f6221dc8b83a9c4f3c5b21ad0b8fc0930d895a compiler/basicTypes/Demand.lhs | 102 ++++++++++++++++++++++------------------ compiler/basicTypes/MkId.lhs | 4 +- compiler/stranal/DmdAnal.lhs | 4 +- 3 files changed, 59 insertions(+), 51 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 17f6221dc8b83a9c4f3c5b21ad0b8fc0930d895a From git at git.haskell.org Sat Dec 14 22:22:29 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 14 Dec 2013 22:22:29 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Check mAX_CPR_SIZE in dmdAnalVarApp (5e875bc) Message-ID: <20131214222229.AE6E82406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/5e875bc5835c9c6b0b5cffcbd1cd2fc68d159916/ghc >--------------------------------------------------------------- commit 5e875bc5835c9c6b0b5cffcbd1cd2fc68d159916 Author: Joachim Breitner Date: Thu Dec 5 18:01:34 2013 +0000 Check mAX_CPR_SIZE in dmdAnalVarApp >--------------------------------------------------------------- 5e875bc5835c9c6b0b5cffcbd1cd2fc68d159916 compiler/stranal/DmdAnal.lhs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index d5bf8a0..3c613b2 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -522,6 +522,8 @@ dmdAnalVarApp env dmd fun args | Just con <- isDataConWorkId_maybe fun -- Data constructor , isVanillaDataCon con , n_val_args == dataConRepArity con -- Saturated + , dataConRepArity con > 0 + , dataConRepArity con < 10 -- TODO: Sync with mAX_CPR_SIZE in MkId , let cpr_info = cprConRes (dataConTag con) arg_rets res_ty = foldl bothDmdType (DmdType emptyDmdEnv [] cpr_info) arg_tys = -- pprTrace "dmdAnalVarApp" (vcat [ ppr con, ppr args, ppr n_val_args, ppr cxt_ds From git at git.haskell.org Sat Dec 14 22:22:31 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 14 Dec 2013 22:22:31 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Comments and small refactor (a2a5b36) Message-ID: <20131214222231.C8F062406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/a2a5b363091e9d7134fbe66beeb42570a7800ed7/ghc >--------------------------------------------------------------- commit a2a5b363091e9d7134fbe66beeb42570a7800ed7 Author: Simon Peyton Jones Date: Wed Dec 4 16:00:24 2013 +0000 Comments and small refactor >--------------------------------------------------------------- a2a5b363091e9d7134fbe66beeb42570a7800ed7 compiler/basicTypes/Demand.lhs | 2 +- compiler/stranal/DmdAnal.lhs | 9 ++++++--- 2 files changed, 7 insertions(+), 4 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 84d8748..4a0ab39 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -559,7 +559,7 @@ splitFVs is_thunk rhs_fvs %* * %************************************************************************ -This domain differst from JointDemand in the sense that pure absence +This domain differs from JointDemand in the sense that pure absence is taken away, i.e., we deal *only* with non-absent demands. Note [Strict demands] diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index 897b5b4..f94d53d 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -530,9 +530,6 @@ dmdAnalVarApp env dmd fun args -- , ppr arg_tys, ppr cpr_info, ppr res_ty]) $ ( res_ty , foldl App (Var fun) args') - - | otherwise - = completeApp env (dmdTransform env fun (mkCallDmdN n_val_args dmd), Var fun) args where n_val_args = valArgCount args cxt_ds = splitProdCleanDmd n_val_args dmd @@ -552,6 +549,12 @@ dmdAnalVarApp env dmd fun args , (arg_tys, arg_rets, args') <- anal_con_args ds args = (arg_ty:arg_tys, arg_ret:arg_rets, arg':args') anal_con_args ds args = pprPanic "anal_con_args" (ppr args $$ ppr ds) + +dmdAnalVarApp env dmd fun args + = --pprTrace "dmdAnalVarApp" (vcat [ ppr fun, ppr args + -- , ppr $ completeApp env (dmdTransform env fun (mkCallDmdN n_val_args dmd), Var fun) args + -- ]) + completeApp env (dmdTransform env fun (mkCallDmdN (valArgCount args) dmd), Var fun) args \end{code} %************************************************************************ From git at git.haskell.org Sat Dec 14 22:22:34 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 14 Dec 2013 22:22:34 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Actually create a nested CPR worker-wrapper (48c7abb) Message-ID: <20131214222234.6E3AF2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/48c7abbe137ec4e2166aead2edc8f977d62b2cb6/ghc >--------------------------------------------------------------- commit 48c7abbe137ec4e2166aead2edc8f977d62b2cb6 Author: Joachim Breitner Date: Thu Dec 5 18:58:07 2013 +0000 Actually create a nested CPR worker-wrapper >--------------------------------------------------------------- 48c7abbe137ec4e2166aead2edc8f977d62b2cb6 compiler/basicTypes/Demand.lhs | 15 +++-- compiler/stranal/WwLib.lhs | 141 +++++++++++++++++++++++++--------------- 2 files changed, 95 insertions(+), 61 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 48c7abbe137ec4e2166aead2edc8f977d62b2cb6 From git at git.haskell.org Sat Dec 14 22:22:36 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 14 Dec 2013 22:22:36 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Fix a lubDmdResult equation (b63793e) Message-ID: <20131214222236.97F362406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/b63793e09c5ec5967efa0283223075bbad67576a/ghc >--------------------------------------------------------------- commit b63793e09c5ec5967efa0283223075bbad67576a Author: Joachim Breitner Date: Tue Nov 26 10:17:57 2013 +0000 Fix a lubDmdResult equation >--------------------------------------------------------------- b63793e09c5ec5967efa0283223075bbad67576a compiler/basicTypes/Demand.lhs | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 4a0ab39..edfb17c 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -750,8 +750,10 @@ lubCPR (RetProd ds1) (RetProd ds2) lubCPR _ _ = NoCPR lubDmdResult :: DmdResult -> DmdResult -> DmdResult -lubDmdResult Diverges r = r -lubDmdResult (Converges c1) Diverges = Converges c1 +lubDmdResult Diverges (Dunno c2) = Dunno c2 +lubDmdResult Diverges Diverges = Diverges +lubDmdResult Diverges (Converges c2) = Dunno c2 +lubDmdResult (Converges c1) Diverges = Dunno c1 lubDmdResult (Converges c1) (Converges c2) = Converges (c1 `lubCPR` c2) lubDmdResult (Converges c1) (Dunno c2) = Dunno (c1 `lubCPR` c2) lubDmdResult (Dunno c1) Diverges = Dunno c1 From git at git.haskell.org Sat Dec 14 22:22:39 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 14 Dec 2013 22:22:39 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Use isTypeArg instead of isTyCoArg (forgot why) (0ff9e41) Message-ID: <20131214222240.D40CF2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/0ff9e4139622d0833127e33b678139da68e5ff1e/ghc >--------------------------------------------------------------- commit 0ff9e4139622d0833127e33b678139da68e5ff1e Author: Joachim Breitner Date: Thu Dec 5 16:14:07 2013 +0000 Use isTypeArg instead of isTyCoArg (forgot why) >--------------------------------------------------------------- 0ff9e4139622d0833127e33b678139da68e5ff1e compiler/stranal/DmdAnal.lhs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index cb5aa4a..0da1085 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -509,7 +509,7 @@ completeApp :: AnalEnv completeApp _ fun_ty_fun [] = fun_ty_fun completeApp env (fun_ty, fun') (arg:args) - | isTyCoArg arg = completeApp env (fun_ty, App fun' arg) args + | isTypeArg arg = completeApp env (fun_ty, App fun' arg) args | otherwise = completeApp env (res_ty `bothDmdType` arg_ty, App fun' arg') args where (arg_dmd, res_ty) = splitDmdTy fun_ty From git at git.haskell.org Sat Dec 14 22:31:34 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 14 Dec 2013 22:31:34 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Disentangle postProcessDmdTypeM and postProcessUnsat (764044f) Message-ID: <20131214223134.F17DB2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/764044f3f1ce79c67bf940ddaf6a1bbc4d6f69fd/ghc >--------------------------------------------------------------- commit 764044f3f1ce79c67bf940ddaf6a1bbc4d6f69fd Author: Joachim Breitner Date: Mon Dec 9 18:40:09 2013 +0000 Disentangle postProcessDmdTypeM and postProcessUnsat Make different postProcess code paths for function arguments (which are post-processed just to be both'ed) and unsaturated functions (which are post-processed for other reasons.) >--------------------------------------------------------------- 764044f3f1ce79c67bf940ddaf6a1bbc4d6f69fd compiler/basicTypes/Demand.lhs | 14 +++++++++++++- 1 file changed, 13 insertions(+), 1 deletion(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 54cc6d7..76e96b1 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -1131,7 +1131,19 @@ postProcessDmdTypeM Nothing _ = nopDmdType -- Incoming demand was Absent, so just discard all usage information -- We only processed the thing at all to analyse the body -- See Note [Always analyse in virgin pass] -postProcessDmdTypeM (Just du) ty = postProcessUnsat du ty +postProcessDmdTypeM (Just du) (DmdType fv _ res_ty) + = DmdType (postProcessDmdEnv du fv) [] (postProcessDmdResult du res_ty) + +postProcessDmdResult :: DeferAndUse -> DmdResult -> DmdResult +postProcessDmdResult (True,_) _ = topRes +postProcessDmdResult (False,_) r = r + +postProcessDmdEnv :: DeferAndUse -> DmdEnv -> DmdEnv +postProcessDmdEnv (True, Many) env = deferReuseEnv env +postProcessDmdEnv (False, Many) env = reuseEnv env +postProcessDmdEnv (True, One) env = deferEnv env +postProcessDmdEnv (False, One) env = env + postProcessUnsat :: DeferAndUse -> DmdType -> DmdType postProcessUnsat (True, Many) ty = deferReuse ty From git at git.haskell.org Sat Dec 14 22:31:37 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 14 Dec 2013 22:31:37 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Make types of bothDmdType more precise (c8dea98) Message-ID: <20131214223137.3E6A82406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/c8dea98f58b6ae27081af30bd035e0a40c8197b8/ghc >--------------------------------------------------------------- commit c8dea98f58b6ae27081af30bd035e0a40c8197b8 Author: Joachim Breitner Date: Mon Dec 9 18:40:09 2013 +0000 Make types of bothDmdType more precise by only passing the demand on the free variables, and whether the argument (resp. scrunitee) may or will diverge. >--------------------------------------------------------------- c8dea98f58b6ae27081af30bd035e0a40c8197b8 compiler/basicTypes/Demand.lhs | 55 +++++++++++++++++++++++++--------------- compiler/stranal/DmdAnal.lhs | 9 +++---- 2 files changed, 39 insertions(+), 25 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 76e96b1..bd68ea5 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -21,6 +21,7 @@ module Demand ( DmdType(..), dmdTypeDepth, lubDmdType, bothDmdType, nopDmdType, botDmdType, mkDmdType, addDemand, + BothDmdArg, mkBothDmdArg, toBothDmdArg, DmdEnv, emptyDmdEnv, peelFV, @@ -709,14 +710,15 @@ We have lubs, but not glbs; but that is ok. -- Constructed Product Result ------------------------------------------------------------------------ -data CPRResult = NoCPR -- Top of the lattice - | RetProd -- Returns a constructor from a product type - | RetSum ConTag -- Returns a constructor from a sum type with this tag +data Termination r = Diverges -- Definitely diverges + | Dunno r -- Might diverge or converge deriving( Eq, Show ) -data DmdResult = Diverges -- Definitely diverges - | Dunno CPRResult -- Might diverge or converge, but in the latter case the - -- result shape is described by CPRResult +type DmdResult = Termination CPRResult + +data CPRResult = NoCPR -- Top of the lattice + | RetProd -- Returns a constructor from a product type + | RetSum ConTag -- Returns a constructor from a data type deriving( Eq, Show ) lubCPR :: CPRResult -> CPRResult -> CPRResult @@ -733,7 +735,7 @@ lubDmdResult (Dunno c1) (Dunno c2) = Dunno (c1 `lubCPR` c2) -- defaultDmd (r1 `lubDmdResult` r2) = defaultDmd r1 `lubDmd` defaultDmd r2 -- (See Note [Default demand on free variables] for why) -bothDmdResult :: DmdResult -> DmdResult -> DmdResult +bothDmdResult :: DmdResult -> Termination () -> DmdResult -- See Note [Asymmetry of 'both' for DmdType and DmdResult] bothDmdResult _ Diverges = Diverges bothDmdResult r _ = r @@ -1024,13 +1026,25 @@ lubDmdType (DmdType fv1 ds1 r1) (DmdType fv2 ds2 r2) lub_ds ds1 [] = map (`lubDmd` resTypeArgDmd r2) ds1 lub_ds [] ds2 = map (resTypeArgDmd r1 `lubDmd`) ds2 -bothDmdType :: DmdType -> DmdType -> DmdType -bothDmdType (DmdType fv1 ds1 r1) (DmdType fv2 _ r2) + +type BothDmdArg = (DmdEnv, Termination ()) + +mkBothDmdArg :: DmdEnv -> BothDmdArg +mkBothDmdArg env = (env, Dunno ()) + +toBothDmdArg :: DmdType -> BothDmdArg +toBothDmdArg (DmdType fv _ r) = (fv, go r) + where + go (Dunno {}) = Dunno () + go Diverges = Diverges + +bothDmdType :: DmdType -> BothDmdArg -> DmdType +bothDmdType (DmdType fv1 ds1 r1) (fv2, t2) -- See Note [Asymmetry of 'both' for DmdType and DmdResult] -- 'both' takes the argument/result info from its *first* arg, -- using its second arg just for its free-var info. - = DmdType both_fv ds1 (r1 `bothDmdResult` r2) - where both_fv = plusVarEnv_CD bothDmd fv1 (defaultDmd r1) fv2 (defaultDmd r2) + = DmdType both_fv ds1 (r1 `bothDmdResult` t2) + where both_fv = plusVarEnv_CD bothDmd fv1 (defaultDmd r1) fv2 (defaultDmd t2) instance Outputable DmdType where ppr (DmdType fv ds res) @@ -1126,17 +1140,18 @@ toCleanDmd (JD { strd = s, absd = u }) -- This is used in dmdAnalStar when post-processing -- a function's argument demand. So we only care about what -- does to free variables, and whether it terminates. -postProcessDmdTypeM :: DeferAndUseM -> DmdType -> DmdType -postProcessDmdTypeM Nothing _ = nopDmdType +postProcessDmdTypeM :: DeferAndUseM -> DmdType -> BothDmdArg +postProcessDmdTypeM Nothing _ = (emptyDmdEnv, Dunno ()) -- Incoming demand was Absent, so just discard all usage information -- We only processed the thing at all to analyse the body -- See Note [Always analyse in virgin pass] postProcessDmdTypeM (Just du) (DmdType fv _ res_ty) - = DmdType (postProcessDmdEnv du fv) [] (postProcessDmdResult du res_ty) + = (postProcessDmdEnv du fv, postProcessDmdResult du res_ty) -postProcessDmdResult :: DeferAndUse -> DmdResult -> DmdResult -postProcessDmdResult (True,_) _ = topRes -postProcessDmdResult (False,_) r = r +postProcessDmdResult :: DeferAndUse -> DmdResult -> Termination () +postProcessDmdResult (True,_) _ = topRes +postProcessDmdResult (False,_) (Dunno {}) = Dunno () +postProcessDmdResult (False,_) Diverges = Diverges postProcessDmdEnv :: DeferAndUse -> DmdEnv -> DmdEnv postProcessDmdEnv (True, Many) env = deferReuseEnv env @@ -1246,9 +1261,9 @@ peelFV (DmdType fv ds res) id = -- pprTrace "rfv" (ppr id <+> ppr dmd $$ ppr fv) -- See note [Default demand on free variables] dmd = lookupVarEnv fv id `orElse` defaultDmd res -defaultDmd :: DmdResult -> Demand -defaultDmd res | isBotRes res = botDmd - | otherwise = absDmd +defaultDmd :: Termination r -> Demand +defaultDmd Diverges = botDmd +defaultDmd _ = absDmd addDemand :: Demand -> DmdType -> DmdType addDemand dmd (DmdType fv ds res) = DmdType fv (dmd:ds) res diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index cbdcc67..a942c4e 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -115,7 +115,7 @@ dmdTransformThunkDmd e -- See |-* relation in the companion paper dmdAnalStar :: AnalEnv -> Demand -- This one takes a *Demand* - -> CoreExpr -> (DmdType, CoreExpr) + -> CoreExpr -> (BothDmdArg, CoreExpr) dmdAnalStar env dmd e | (cd, defer_and_use) <- toCleanDmd dmd , (dmd_ty, e') <- dmdAnal env cd e @@ -255,7 +255,7 @@ dmdAnal env dmd (Case scrut case_bndr ty [alt@(DataAlt dc, _, _)]) scrut_dmd = scrut_dmd1 `bothCleanDmd` scrut_dmd2 (scrut_ty, scrut') = dmdAnal env scrut_dmd scrut - res_ty = alt_ty1 `bothDmdType` scrut_ty + res_ty = alt_ty1 `bothDmdType` toBothDmdArg scrut_ty in -- pprTrace "dmdAnal:Case1" (vcat [ text "scrut" <+> ppr scrut -- , text "dmd" <+> ppr dmd @@ -271,7 +271,7 @@ dmdAnal env dmd (Case scrut case_bndr ty alts) (alt_tys, alts') = mapAndUnzip (dmdAnalAlt env dmd) alts (scrut_ty, scrut') = dmdAnal env cleanEvalDmd scrut (alt_ty, case_bndr') = annotateBndr env (foldr lubDmdType botDmdType alt_tys) case_bndr - res_ty = alt_ty `bothDmdType` scrut_ty + res_ty = alt_ty `bothDmdType` toBothDmdArg scrut_ty in -- pprTrace "dmdAnal:Case2" (vcat [ text "scrut" <+> ppr scrut -- , text "scrut_ty" <+> ppr scrut_ty @@ -509,7 +509,6 @@ dmdTransform env var dmd | otherwise -- Local non-letrec-bound thing = unitVarDmd var (mkOnceUsedDmd dmd) - \end{code} %************************************************************************ @@ -698,7 +697,7 @@ addVarDmd (DmdType fv ds res) var dmd addLazyFVs :: DmdType -> DmdEnv -> DmdType addLazyFVs dmd_ty lazy_fvs - = dmd_ty `bothDmdType` mkDmdType lazy_fvs [] topRes + = dmd_ty `bothDmdType` mkBothDmdArg lazy_fvs -- Using bothDmdType (rather than just both'ing the envs) -- is vital. Consider -- let f = \x -> (x,y) From git at git.haskell.org Sat Dec 14 22:31:39 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 14 Dec 2013 22:31:39 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Initial work on Nested CPR (a148777) Message-ID: <20131214223139.734712406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/a1487775a56691c75010d53625b5e9b05cee7971/ghc >--------------------------------------------------------------- commit a1487775a56691c75010d53625b5e9b05cee7971 Author: Simon Peyton Jones Date: Mon Nov 25 09:59:16 2013 +0000 Initial work on Nested CPR >--------------------------------------------------------------- a1487775a56691c75010d53625b5e9b05cee7971 compiler/basicTypes/Demand.lhs | 137 ++++++++++++++++++++++++---------------- compiler/stranal/DmdAnal.lhs | 111 ++++++++++++++++++++++---------- 2 files changed, 160 insertions(+), 88 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 a1487775a56691c75010d53625b5e9b05cee7971 From git at git.haskell.org Sat Dec 14 22:31:41 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 14 Dec 2013 22:31:41 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Add Converges to DmdResult (4afcad2) Message-ID: <20131214223141.AE0312406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/4afcad2a78f90c529eff0e3a91e674a2311ce1c7/ghc >--------------------------------------------------------------- commit 4afcad2a78f90c529eff0e3a91e674a2311ce1c7 Author: Joachim Breitner Date: Thu Dec 12 15:45:19 2013 +0000 Add Converges to DmdResult to detect definite convergence (required for nested CPR). >--------------------------------------------------------------- 4afcad2a78f90c529eff0e3a91e674a2311ce1c7 compiler/basicTypes/Demand.lhs | 41 ++++++++++++++++++++++++++++------------ 1 file changed, 29 insertions(+), 12 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index bd68ea5..7e455f8 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -691,8 +691,8 @@ splitProdDmd_maybe (JD {strd = s, absd = u}) DmdResult: Dunno CPRResult - / - Diverges + / \ + Diverges Converges CPRResult CPRResult: NoCPR @@ -700,7 +700,7 @@ CPRResult: NoCPR RetProd RetSum ConTag -Product contructors return (Dunno (RetProd rs)) +Product contructors return (Converges (RetProd rs)) In a fixpoint iteration, start from Diverges We have lubs, but not glbs; but that is ok. @@ -711,6 +711,7 @@ We have lubs, but not glbs; but that is ok. ------------------------------------------------------------------------ data Termination r = Diverges -- Definitely diverges + | Converges r -- Definitely converges | Dunno r -- Might diverge or converge deriving( Eq, Show ) @@ -729,7 +730,11 @@ lubCPR _ _ = NoCPR lubDmdResult :: DmdResult -> DmdResult -> DmdResult lubDmdResult Diverges r = r +lubDmdResult (Converges c1) Diverges = Converges c1 +lubDmdResult (Converges c1) (Converges c2) = Converges (c1 `lubCPR` c2) +lubDmdResult (Converges c1) (Dunno c2) = Dunno (c1 `lubCPR` c2) lubDmdResult (Dunno c1) Diverges = Dunno c1 +lubDmdResult (Dunno c1) (Converges c2) = Dunno (c1 `lubCPR` c2) lubDmdResult (Dunno c1) (Dunno c2) = Dunno (c1 `lubCPR` c2) -- This needs to commute with defaultDmd, i.e. -- defaultDmd (r1 `lubDmdResult` r2) = defaultDmd r1 `lubDmd` defaultDmd r2 @@ -738,6 +743,7 @@ lubDmdResult (Dunno c1) (Dunno c2) = Dunno (c1 `lubCPR` c2) bothDmdResult :: DmdResult -> Termination () -> DmdResult -- See Note [Asymmetry of 'both' for DmdType and DmdResult] bothDmdResult _ Diverges = Diverges +bothDmdResult (Converges c1) (Dunno {}) = Dunno c1 bothDmdResult r _ = r -- This needs to commute with defaultDmd, i.e. -- defaultDmd (r1 `bothDmdResult` r2) = defaultDmd r1 `bothDmd` defaultDmd r2 @@ -745,6 +751,7 @@ bothDmdResult r _ = r instance Outputable DmdResult where ppr Diverges = char 'b' + ppr (Converges c) = char 't' <> ppr c ppr (Dunno c) = char 'd' <> ppr c instance Outputable CPRResult where @@ -754,6 +761,7 @@ instance Outputable CPRResult where seqDmdResult :: DmdResult -> () seqDmdResult Diverges = () +seqDmdResult (Converges c) = seqCPRResult c seqDmdResult (Dunno c) = seqCPRResult c seqCPRResult :: CPRResult -> () @@ -774,17 +782,17 @@ botRes = Diverges cprSumRes :: ConTag -> DmdResult cprSumRes tag | opt_CprOff = topRes - | otherwise = Dunno $ RetSum tag + | otherwise = Converges $ RetSum tag cprProdRes :: [DmdType] -> DmdResult cprProdRes _arg_tys | opt_CprOff = topRes - | otherwise = Dunno $ RetProd + | otherwise = Converges $ RetProd vanillaCprProdRes :: Arity -> DmdResult vanillaCprProdRes _arity | opt_CprOff = topRes - | otherwise = Dunno $ RetProd + | otherwise = Converges $ RetProd isTopRes :: DmdResult -> Bool isTopRes (Dunno NoCPR) = True @@ -798,6 +806,7 @@ trimCPRInfo :: Bool -> Bool -> DmdResult -> DmdResult trimCPRInfo trim_all trim_sums res = trimR res where + trimR (Converges c) = Converges (trimC c) trimR (Dunno c) = Dunno (trimC c) trimR Diverges = Diverges @@ -811,6 +820,7 @@ returnsCPR :: DmdResult -> Bool returnsCPR dr = isJust (returnsCPR_maybe dr) returnsCPR_maybe :: DmdResult -> Maybe ConTag +returnsCPR_maybe (Converges c) = retCPR_maybe c returnsCPR_maybe (Dunno c) = retCPR_maybe c returnsCPR_maybe Diverges = Nothing @@ -1036,6 +1046,7 @@ toBothDmdArg :: DmdType -> BothDmdArg toBothDmdArg (DmdType fv _ r) = (fv, go r) where go (Dunno {}) = Dunno () + go (Converges {}) = Converges () go Diverges = Diverges bothDmdType :: DmdType -> BothDmdArg -> DmdType @@ -1069,7 +1080,7 @@ botDmdType = DmdType emptyDmdEnv [] botRes cprProdDmdType :: Arity -> DmdType cprProdDmdType _arity - = DmdType emptyDmdEnv [] (Dunno RetProd) + = DmdType emptyDmdEnv [] (Converges RetProd) isNopDmdType :: DmdType -> Bool isNopDmdType (DmdType env [] res) @@ -1098,7 +1109,7 @@ splitDmdTy ty@(DmdType _ [] res_ty) = (resTypeArgDmd res_ty, ty) -- exit? -- * We have to kill all strictness demands (i.e. lub with a lazy demand) -- * We can keep demand information (i.e. lub with an absent deman) --- * We have to kill definite divergence +-- * We have to kill definite divergence and definite convergence -- * We can keep CPR information. -- See Note [IO hack in the demand analyser] deferAfterIO :: DmdType -> DmdType @@ -1107,6 +1118,7 @@ deferAfterIO d@(DmdType _ _ res) = DmdType fv ds _ -> DmdType fv ds (defer_res res) where defer_res Diverges = topRes + defer_res (Converges r) = Dunno r defer_res r = r strictenDmd :: JointDmd -> CleanDemand @@ -1149,9 +1161,12 @@ postProcessDmdTypeM (Just du) (DmdType fv _ res_ty) = (postProcessDmdEnv du fv, postProcessDmdResult du res_ty) postProcessDmdResult :: DeferAndUse -> DmdResult -> Termination () -postProcessDmdResult (True,_) _ = topRes -postProcessDmdResult (False,_) (Dunno {}) = Dunno () -postProcessDmdResult (False,_) Diverges = Diverges + -- if we use it lazily, there cannot be divergence worrying us + -- (Otherwise we'd lose the termination information of constructors in in dmdAnalVarApp, for example) +postProcessDmdResult (True,_) _ = topRes +postProcessDmdResult (False,_) (Dunno {}) = Dunno () +postProcessDmdResult (False,_) (Converges {}) = Converges () +postProcessDmdResult (False,_) Diverges = Diverges postProcessDmdEnv :: DeferAndUse -> DmdEnv -> DmdEnv postProcessDmdEnv (True, Many) env = deferReuseEnv env @@ -1722,11 +1737,13 @@ instance Binary DmdType where instance Binary DmdResult where put_ bh (Dunno c) = do { putByte bh 0; put_ bh c } - put_ bh Diverges = putByte bh 2 + put_ bh (Converges c) = do { putByte bh 1; put_ bh c } + put_ bh Diverges = putByte bh 3 get bh = do { h <- getByte bh ; case h of 0 -> do { c <- get bh; return (Dunno c) } + 1 -> do { c <- get bh; return (Converges c) } _ -> return Diverges } instance Binary CPRResult where From git at git.haskell.org Sat Dec 14 22:31:43 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 14 Dec 2013 22:31:43 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Use isTypeArg instead of isTyCoArg (forgot why) (135496d) Message-ID: <20131214223143.E534E2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/135496d306a6e05dc4f427e9664dd044d98d0c5a/ghc >--------------------------------------------------------------- commit 135496d306a6e05dc4f427e9664dd044d98d0c5a Author: Joachim Breitner Date: Thu Dec 5 16:14:07 2013 +0000 Use isTypeArg instead of isTyCoArg (forgot why) >--------------------------------------------------------------- 135496d306a6e05dc4f427e9664dd044d98d0c5a compiler/stranal/DmdAnal.lhs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index cb5aa4a..0da1085 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -509,7 +509,7 @@ completeApp :: AnalEnv completeApp _ fun_ty_fun [] = fun_ty_fun completeApp env (fun_ty, fun') (arg:args) - | isTyCoArg arg = completeApp env (fun_ty, App fun' arg) args + | isTypeArg arg = completeApp env (fun_ty, App fun' arg) args | otherwise = completeApp env (res_ty `bothDmdType` arg_ty, App fun' arg') args where (arg_dmd, res_ty) = splitDmdTy fun_ty From git at git.haskell.org Sat Dec 14 22:31:46 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 14 Dec 2013 22:31:46 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Fix a lubDmdResult equation (9021044) Message-ID: <20131214223146.362852406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/902104487d0c0e7b04cbd689e6c1cf8d74b1f090/ghc >--------------------------------------------------------------- commit 902104487d0c0e7b04cbd689e6c1cf8d74b1f090 Author: Joachim Breitner Date: Tue Nov 26 10:17:57 2013 +0000 Fix a lubDmdResult equation >--------------------------------------------------------------- 902104487d0c0e7b04cbd689e6c1cf8d74b1f090 compiler/basicTypes/Demand.lhs | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 4a0ab39..edfb17c 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -750,8 +750,10 @@ lubCPR (RetProd ds1) (RetProd ds2) lubCPR _ _ = NoCPR lubDmdResult :: DmdResult -> DmdResult -> DmdResult -lubDmdResult Diverges r = r -lubDmdResult (Converges c1) Diverges = Converges c1 +lubDmdResult Diverges (Dunno c2) = Dunno c2 +lubDmdResult Diverges Diverges = Diverges +lubDmdResult Diverges (Converges c2) = Dunno c2 +lubDmdResult (Converges c1) Diverges = Dunno c1 lubDmdResult (Converges c1) (Converges c2) = Converges (c1 `lubCPR` c2) lubDmdResult (Converges c1) (Dunno c2) = Dunno (c1 `lubCPR` c2) lubDmdResult (Dunno c1) Diverges = Dunno c1 From git at git.haskell.org Sat Dec 14 22:31:48 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 14 Dec 2013 22:31:48 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Comments and small refactor (0f80c45) Message-ID: <20131214223148.B23262406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/0f80c459aa84cbe3304c21272f747e0ece0412c0/ghc >--------------------------------------------------------------- commit 0f80c459aa84cbe3304c21272f747e0ece0412c0 Author: Simon Peyton Jones Date: Wed Dec 4 16:00:24 2013 +0000 Comments and small refactor >--------------------------------------------------------------- 0f80c459aa84cbe3304c21272f747e0ece0412c0 compiler/basicTypes/Demand.lhs | 2 +- compiler/stranal/DmdAnal.lhs | 9 ++++++--- 2 files changed, 7 insertions(+), 4 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 84d8748..4a0ab39 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -559,7 +559,7 @@ splitFVs is_thunk rhs_fvs %* * %************************************************************************ -This domain differst from JointDemand in the sense that pure absence +This domain differs from JointDemand in the sense that pure absence is taken away, i.e., we deal *only* with non-absent demands. Note [Strict demands] diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index 897b5b4..f94d53d 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -530,9 +530,6 @@ dmdAnalVarApp env dmd fun args -- , ppr arg_tys, ppr cpr_info, ppr res_ty]) $ ( res_ty , foldl App (Var fun) args') - - | otherwise - = completeApp env (dmdTransform env fun (mkCallDmdN n_val_args dmd), Var fun) args where n_val_args = valArgCount args cxt_ds = splitProdCleanDmd n_val_args dmd @@ -552,6 +549,12 @@ dmdAnalVarApp env dmd fun args , (arg_tys, arg_rets, args') <- anal_con_args ds args = (arg_ty:arg_tys, arg_ret:arg_rets, arg':args') anal_con_args ds args = pprPanic "anal_con_args" (ppr args $$ ppr ds) + +dmdAnalVarApp env dmd fun args + = --pprTrace "dmdAnalVarApp" (vcat [ ppr fun, ppr args + -- , ppr $ completeApp env (dmdTransform env fun (mkCallDmdN n_val_args dmd), Var fun) args + -- ]) + completeApp env (dmdTransform env fun (mkCallDmdN (valArgCount args) dmd), Var fun) args \end{code} %************************************************************************ From git at git.haskell.org Sat Dec 14 22:31:50 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 14 Dec 2013 22:31:50 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Unify RetProd and RetSum to RetCon in CPRResult (fbfbeeb) Message-ID: <20131214223150.9DD682406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/fbfbeeb2a78ec8df2cbced4ffaa7613fadad8310/ghc >--------------------------------------------------------------- commit fbfbeeb2a78ec8df2cbced4ffaa7613fadad8310 Author: Joachim Breitner Date: Thu Dec 5 16:13:41 2013 +0000 Unify RetProd and RetSum to RetCon in CPRResult >--------------------------------------------------------------- fbfbeeb2a78ec8df2cbced4ffaa7613fadad8310 compiler/basicTypes/Demand.lhs | 102 ++++++++++++++++++++++------------------ compiler/basicTypes/MkId.lhs | 4 +- compiler/stranal/DmdAnal.lhs | 4 +- 3 files changed, 59 insertions(+), 51 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 fbfbeeb2a78ec8df2cbced4ffaa7613fadad8310 From git at git.haskell.org Sat Dec 14 22:31:52 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 14 Dec 2013 22:31:52 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: In deferType, return convRes = Converges NoCPR (9003f07) Message-ID: <20131214223152.D6C1F2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/9003f07caa6676e535b9c2b3b192bb916d784140/ghc >--------------------------------------------------------------- commit 9003f07caa6676e535b9c2b3b192bb916d784140 Author: Joachim Breitner Date: Wed Dec 4 16:55:18 2013 +0000 In deferType, return convRes = Converges NoCPR because this is the right-identity to `bothDmdResult`, and this is the right thing to do in a lazy context. >--------------------------------------------------------------- 9003f07caa6676e535b9c2b3b192bb916d784140 compiler/basicTypes/Demand.lhs | 7 ++++--- 1 file changed, 4 insertions(+), 3 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 7e455f8..cadec37 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -776,8 +776,9 @@ seqCPRResult RetProd = () -- [cprRes] lets us switch off CPR analysis -- by making sure that everything uses TopRes -topRes, botRes :: DmdResult +topRes, convRes, botRes :: DmdResult topRes = Dunno NoCPR +convRes = Converges NoCPR botRes = Diverges cprSumRes :: ConTag -> DmdResult @@ -1182,9 +1183,9 @@ postProcessUnsat (True, One) ty = deferType ty postProcessUnsat (False, One) ty = ty deferType, reuseType, deferReuse :: DmdType -> DmdType -deferType (DmdType fv ds _) = DmdType (deferEnv fv) (map deferDmd ds) topRes +deferType (DmdType fv ds _) = DmdType (deferEnv fv) (map deferDmd ds) convRes reuseType (DmdType fv ds res_ty) = DmdType (reuseEnv fv) (map reuseDmd ds) res_ty -deferReuse (DmdType fv ds _) = DmdType (deferReuseEnv fv) (map deferReuseDmd ds) topRes +deferReuse (DmdType fv ds _) = DmdType (deferReuseEnv fv) (map deferReuseDmd ds) convRes deferEnv, reuseEnv, deferReuseEnv :: DmdEnv -> DmdEnv deferEnv fv = mapVarEnv deferDmd fv From git at git.haskell.org Sat Dec 14 22:31:55 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 14 Dec 2013 22:31:55 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Add a warning to dmdTransformDataConSig (which I believe is dead code) (bc50fa3) Message-ID: <20131214223155.78DB72406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/bc50fa39289fb8581f9dd50874c49e4b3a241e84/ghc >--------------------------------------------------------------- commit bc50fa39289fb8581f9dd50874c49e4b3a241e84 Author: Joachim Breitner Date: Tue Dec 10 13:56:08 2013 +0000 Add a warning to dmdTransformDataConSig (which I believe is dead code) >--------------------------------------------------------------- bc50fa39289fb8581f9dd50874c49e4b3a241e84 compiler/basicTypes/Demand.lhs | 1 + 1 file changed, 1 insertion(+) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 8abcbcd..865287f 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -1519,6 +1519,7 @@ dmdTransformDataConSig arity (StrictSig (DmdType _ _ con_res)) (CD { sd = str, ud = abs }) | Just str_dmds <- go_str arity str , Just abs_dmds <- go_abs arity abs + , WARN( True, text "dmdTransformDataConSig indeed still in use" ) True = DmdType emptyDmdEnv (mkJointDmds str_dmds abs_dmds) con_res -- Must remember whether it's a product, hence con_res, not TopRes From git at git.haskell.org Sat Dec 14 22:31:57 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 14 Dec 2013 22:31:57 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Recover [CPR for sum types] (slightly differently) (6c3c9af) Message-ID: <20131214223157.BBE502406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/6c3c9afed02c112c32f004cc8b1a13e0a72809bf/ghc >--------------------------------------------------------------- commit 6c3c9afed02c112c32f004cc8b1a13e0a72809bf Author: Joachim Breitner Date: Thu Nov 28 11:17:16 2013 +0000 Recover [CPR for sum types] (slightly differently) >--------------------------------------------------------------- 6c3c9afed02c112c32f004cc8b1a13e0a72809bf compiler/basicTypes/Demand.lhs | 24 ++++++++---------------- compiler/stranal/DmdAnal.lhs | 14 ++++++++------ 2 files changed, 16 insertions(+), 22 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 4a31dd4..0a8c9ff 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -30,10 +30,9 @@ module Demand ( isBotRes, isTopRes, getDmdResult, resTypeArgDmd, topRes, botRes, cprConRes, vanillaCprConRes, appIsBottom, isBottomingSig, pprIfaceStrictSig, - trimCPRInfo, returnsCPR, returnsCPR_maybe, + returnsCPR, returnsCPR_maybe, forgetCPR, StrictSig(..), mkStrictSig, mkClosedStrictSig, nopSig, botSig, cprProdSig, isNopSig, splitStrictSig, increaseStrictSigArity, - seqDemand, seqDemandList, seqDmdType, seqStrictSig, evalDmd, cleanEvalDmd, cleanEvalProdDmd, isStrictDmd, @@ -826,6 +825,13 @@ cutCPRResult :: Int -> CPRResult -> CPRResult cutCPRResult _ NoCPR = NoCPR cutCPRResult n (RetCon tag rs) = RetCon tag (map (cutDmdResult (n-1)) rs) +-- Forget the CPR information, but remember if it converges or diverges +-- Used for non-strict thunks and non-top-level things with sum type +forgetCPR :: DmdResult -> DmdResult +forgetCPR Diverges = Diverges +forgetCPR (Converges _) = Converges NoCPR +forgetCPR (Dunno _) = Dunno NoCPR + cprConRes :: ConTag -> [DmdResult] -> DmdResult cprConRes tag arg_ress | opt_CprOff = topRes @@ -844,20 +850,6 @@ isBotRes :: DmdResult -> Bool isBotRes Diverges = True isBotRes _ = False --- TODO: This currently ignores trim_sums. Evaluate if still required, and fix --- Note [CPR for sum types] -trimCPRInfo :: Bool -> Bool -> DmdResult -> DmdResult -trimCPRInfo trim_all _trim_sums res - = trimR res - where - trimR (Converges c) = Converges (trimC c) - trimR (Dunno c) = Dunno (trimC c) - trimR Diverges = Diverges - - trimC (RetCon n rs) | trim_all = NoCPR - | otherwise = RetCon n (map trimR rs) - trimC NoCPR = NoCPR - returnsCPR :: DmdResult -> Bool returnsCPR dr = isJust (returnsCPR_maybe dr) diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index 0da1085..ea1a588 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -655,9 +655,10 @@ dmdAnalRhs top_lvl rec_flag env id rhs -- See Note [NOINLINE and strictness] -- See Note [Product demands for function body] - body_dmd = case deepSplitProductType_maybe (exprType body) of - Nothing -> cleanEvalDmd - Just (dc, _, _, _) -> cleanEvalProdDmd (dataConRepArity dc) + (is_sum_type, body_dmd) + = case deepSplitProductType_maybe (exprType body) of + Nothing -> (True, cleanEvalDmd) + Just (dc, _, _, _) -> (False, cleanEvalProdDmd (dataConRepArity dc)) -- See Note [Lazy and unleashable free variables] -- See Note [Aggregated demand for cardinality] @@ -667,9 +668,10 @@ dmdAnalRhs top_lvl rec_flag env id rhs (lazy_fv, sig_fv) = splitFVs is_thunk rhs_fv1 - rhs_res' = trimCPRInfo trim_all trim_sums rhs_res - trim_all = is_thunk && not_strict - trim_sums = not (isTopLevel top_lvl) -- See Note [CPR for sum types] + -- Note [CPR for sum types] + rhs_res' | (is_sum_type && not (isTopLevel top_lvl)) || + (is_thunk && not_strict) = forgetCPR rhs_res + | otherwise = rhs_res -- See Note [CPR for thunks] is_thunk = not (exprIsHNF rhs) From git at git.haskell.org Sat Dec 14 22:31:59 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 14 Dec 2013 22:31:59 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Allow the CPR w/w to take unboxed tuples apart (55f423b) Message-ID: <20131214223201.DECDF2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/55f423b84ba5e3e8b409772549e115a0bf977379/ghc >--------------------------------------------------------------- commit 55f423b84ba5e3e8b409772549e115a0bf977379 Author: Joachim Breitner Date: Thu Nov 28 10:29:47 2013 +0000 Allow the CPR w/w to take unboxed tuples apart >--------------------------------------------------------------- 55f423b84ba5e3e8b409772549e115a0bf977379 compiler/stranal/WwLib.lhs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/stranal/WwLib.lhs b/compiler/stranal/WwLib.lhs index ce4112c..5168d8f 100644 --- a/compiler/stranal/WwLib.lhs +++ b/compiler/stranal/WwLib.lhs @@ -502,7 +502,7 @@ deepSplitCprType_maybe :: ConTag -> Type -> Maybe (DataCon, [Type], [Type], Coer deepSplitCprType_maybe con_tag ty | let (co, ty1) = topNormaliseNewType_maybe ty `orElse` (mkReflCo Representational ty, ty) , Just (tc, tc_args) <- splitTyConApp_maybe ty1 - , isDataTyCon tc + , isDataTyCon tc || isUnboxedTupleTyCon tc , let cons = tyConDataCons tc con = ASSERT( cons `lengthAtLeast` con_tag ) cons !! (con_tag - fIRST_TAG) = Just (con, tc_args, dataConInstArgTys con tc_args, co) From git at git.haskell.org Sat Dec 14 22:32:02 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 14 Dec 2013 22:32:02 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Actually create a nested CPR worker-wrapper (8d874aa) Message-ID: <20131214223202.3BCCA2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/8d874aae742886a42266142366f384d6a4f843e9/ghc >--------------------------------------------------------------- commit 8d874aae742886a42266142366f384d6a4f843e9 Author: Joachim Breitner Date: Thu Dec 5 18:58:07 2013 +0000 Actually create a nested CPR worker-wrapper >--------------------------------------------------------------- 8d874aae742886a42266142366f384d6a4f843e9 compiler/basicTypes/Demand.lhs | 15 +++-- compiler/stranal/WwLib.lhs | 141 +++++++++++++++++++++++++--------------- 2 files changed, 95 insertions(+), 61 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 8d874aae742886a42266142366f384d6a4f843e9 From git at git.haskell.org Sat Dec 14 22:32:04 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 14 Dec 2013 22:32:04 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Temporarily disable nested CPR inside sum types (291f5e7) Message-ID: <20131214223204.7B0B02406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/291f5e7fb01a0f70203be14ae321e1d57e115a9e/ghc >--------------------------------------------------------------- commit 291f5e7fb01a0f70203be14ae321e1d57e115a9e Author: Joachim Breitner Date: Tue Dec 10 10:12:46 2013 +0000 Temporarily disable nested CPR inside sum types >--------------------------------------------------------------- 291f5e7fb01a0f70203be14ae321e1d57e115a9e compiler/basicTypes/Demand.lhs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 721cfc9..8abcbcd 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -865,7 +865,7 @@ cprConRes isProd tag arg_ress | opt_NestedCprOff = Converges $ cutCPRResult flatCPRDepth $ retCon arg_ress | otherwise = Converges $ cutCPRResult maxCPRDepth $ retCon arg_ress where retCon | isProd = RetProd - | otherwise = RetSum tag + | otherwise = RetSum tag . map (const topRes) vanillaCprConRes :: Bool -> ConTag -> Arity -> DmdResult vanillaCprConRes isProd tag arity = cprConRes isProd tag (replicate arity topRes) From git at git.haskell.org Sat Dec 14 22:32:06 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 14 Dec 2013 22:32:06 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Add a flag -fnested-cpr-off to conveniently test the effect of nested CPR (3d0dcf0) Message-ID: <20131214223206.CC7252406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/3d0dcf01b59752a5ea6d9b5a372eaf23911a8fc3/ghc >--------------------------------------------------------------- commit 3d0dcf01b59752a5ea6d9b5a372eaf23911a8fc3 Author: Joachim Breitner Date: Wed Dec 4 09:14:26 2013 +0000 Add a flag -fnested-cpr-off to conveniently test the effect of nested CPR >--------------------------------------------------------------- 3d0dcf01b59752a5ea6d9b5a372eaf23911a8fc3 compiler/basicTypes/Demand.lhs | 29 ++++++++++++++++++++--------- compiler/main/StaticFlags.hs | 9 +++++++-- 2 files changed, 27 insertions(+), 11 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index ead28e3..6fd8076 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -807,19 +807,29 @@ getDmdResult _ = topRes maxCPRDepth :: Int maxCPRDepth = 3 +-- This is the depth we use with -fnested-cpr-off, in order +-- to get precisely the same behaviour as before introduction of nested cpr +-- -fnested-cpr-off can eventually be removed if nested cpr is deemd to be +-- a good thing always. +flatCPRDepth :: Int +flatCPRDepth = 1 + -- With nested CPR, DmdResult can be arbitrarily deep; consider e.g. the -- DmdResult of repeat +-- -- So we need to forget information at a certain depth. We do that at all points -- where we are building RetCon constructors. -cutDmdResult :: Int -> DmdResult -> DmdResult -cutDmdResult 0 _ = topRes -cutDmdResult _ Diverges = Diverges -cutDmdResult n (Converges c) = Converges (cutCPRResult n c) -cutDmdResult n (Dunno c) = Dunno (cutCPRResult n c) - cutCPRResult :: Int -> CPRResult -> CPRResult -cutCPRResult _ NoCPR = NoCPR +cutCPRResult 0 _ = NoCPR +cutCPRResult _ NoCPR = NoCPR cutCPRResult n (RetCon tag rs) = RetCon tag (map (cutDmdResult (n-1)) rs) + where + cutDmdResult :: Int -> DmdResult -> DmdResult + cutDmdResult 0 _ = topRes + cutDmdResult _ Diverges = Diverges + cutDmdResult n (Converges c) = Converges (cutCPRResult n c) + cutDmdResult n (Dunno c) = Dunno (cutCPRResult n c) + -- Forget that something might converge for sure divergeDmdResult :: DmdResult -> DmdResult @@ -834,8 +844,9 @@ forgetCPR (Dunno _) = Dunno NoCPR cprConRes :: ConTag -> [DmdResult] -> DmdResult cprConRes tag arg_ress - | opt_CprOff = topRes - | otherwise = Converges $ cutCPRResult maxCPRDepth $ RetCon tag arg_ress + | opt_CprOff = topRes + | opt_NestedCprOff = Converges $ cutCPRResult flatCPRDepth $ RetCon tag arg_ress + | otherwise = Converges $ cutCPRResult maxCPRDepth $ RetCon tag arg_ress vanillaCprConRes :: ConTag -> Arity -> DmdResult vanillaCprConRes tag arity diff --git a/compiler/main/StaticFlags.hs b/compiler/main/StaticFlags.hs index 01dc3b7..feb7235 100644 --- a/compiler/main/StaticFlags.hs +++ b/compiler/main/StaticFlags.hs @@ -27,6 +27,7 @@ module StaticFlags ( -- optimisation opts opt_NoStateHack, opt_CprOff, + opt_NestedCprOff, opt_NoOptCoercion, -- For the parser @@ -140,7 +141,8 @@ flagsStaticNames :: [String] flagsStaticNames = [ "fno-state-hack", "fno-opt-coercion", - "fcpr-off" + "fcpr-off", + "fnested-cpr-off" ] -- We specifically need to discard static flags for clients of the @@ -195,10 +197,13 @@ opt_NoDebugOutput = lookUp (fsLit "-dno-debug-output") opt_NoStateHack :: Bool opt_NoStateHack = lookUp (fsLit "-fno-state-hack") --- Switch off CPR analysis in the new demand analyser +-- Switch off CPR analysis in the demand analyser opt_CprOff :: Bool opt_CprOff = lookUp (fsLit "-fcpr-off") +opt_NestedCprOff :: Bool +opt_NestedCprOff = lookUp (fsLit "-fnested-cpr-off") + opt_NoOptCoercion :: Bool opt_NoOptCoercion = lookUp (fsLit "-fno-opt-coercion") From git at git.haskell.org Sat Dec 14 22:32:08 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 14 Dec 2013 22:32:08 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Check mAX_CPR_SIZE in dmdAnalVarApp (3936c69) Message-ID: <20131214223209.2C5C22406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/3936c699d4f0822568bf5787fcea68420c7819d1/ghc >--------------------------------------------------------------- commit 3936c699d4f0822568bf5787fcea68420c7819d1 Author: Joachim Breitner Date: Thu Dec 5 18:01:34 2013 +0000 Check mAX_CPR_SIZE in dmdAnalVarApp >--------------------------------------------------------------- 3936c699d4f0822568bf5787fcea68420c7819d1 compiler/stranal/DmdAnal.lhs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index d5bf8a0..3c613b2 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -522,6 +522,8 @@ dmdAnalVarApp env dmd fun args | Just con <- isDataConWorkId_maybe fun -- Data constructor , isVanillaDataCon con , n_val_args == dataConRepArity con -- Saturated + , dataConRepArity con > 0 + , dataConRepArity con < 10 -- TODO: Sync with mAX_CPR_SIZE in MkId , let cpr_info = cprConRes (dataConTag con) arg_rets res_ty = foldl bothDmdType (DmdType emptyDmdEnv [] cpr_info) arg_tys = -- pprTrace "dmdAnalVarApp" (vcat [ ppr con, ppr args, ppr n_val_args, ppr cxt_ds From git at git.haskell.org Sat Dec 14 22:32:11 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 14 Dec 2013 22:32:11 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: in Demand.lhs, remember what is a sum type (f43081b) Message-ID: <20131214223211.278E12406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/f43081bc1344199359d68903689df9a84e03d1f7/ghc >--------------------------------------------------------------- commit f43081bc1344199359d68903689df9a84e03d1f7 Author: Joachim Breitner Date: Tue Dec 10 09:15:09 2013 +0000 in Demand.lhs, remember what is a sum type because we want to zap CPR information for sum types not only on the outermost level, but also nested. See Note [CPR for sum types] This comes up in sublist in Listplikefns in nofib?s boyer2. >--------------------------------------------------------------- f43081bc1344199359d68903689df9a84e03d1f7 compiler/basicTypes/DataCon.lhs | 4 +++ compiler/basicTypes/Demand.lhs | 76 ++++++++++++++++++++++++--------------- compiler/basicTypes/MkId.lhs | 2 +- compiler/stranal/DmdAnal.lhs | 39 ++++++++++++-------- 4 files changed, 77 insertions(+), 44 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 f43081bc1344199359d68903689df9a84e03d1f7 From git at git.haskell.org Sat Dec 14 22:32:13 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 14 Dec 2013 22:32:13 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Loop breakers are not allowed to have a Converges DmdResult (de6762f) Message-ID: <20131214223213.669172406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/de6762f69a9a226fa77e875ad0cbff74ccf71a8e/ghc >--------------------------------------------------------------- commit de6762f69a9a226fa77e875ad0cbff74ccf71a8e Author: Joachim Breitner Date: Tue Nov 26 10:18:35 2013 +0000 Loop breakers are not allowed to have a Converges DmdResult >--------------------------------------------------------------- de6762f69a9a226fa77e875ad0cbff74ccf71a8e compiler/basicTypes/Demand.lhs | 19 +++++++++++-------- compiler/stranal/DmdAnal.lhs | 5 ++++- 2 files changed, 15 insertions(+), 9 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 0a8c9ff..ead28e3 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -33,6 +33,7 @@ module Demand ( returnsCPR, returnsCPR_maybe, forgetCPR, StrictSig(..), mkStrictSig, mkClosedStrictSig, nopSig, botSig, cprProdSig, isNopSig, splitStrictSig, increaseStrictSigArity, + sigMayConverge, seqDemand, seqDemandList, seqDmdType, seqStrictSig, evalDmd, cleanEvalDmd, cleanEvalProdDmd, isStrictDmd, @@ -806,15 +807,10 @@ getDmdResult _ = topRes maxCPRDepth :: Int maxCPRDepth = 3 --- With nested CPR, DmdResult can be arbitrarily deep; consider --- data Rec1 = Foo Rec2 Rec2 --- data Rec2 = Bar Rec1 Rec1 --- --- x = Foo y y --- y = Bar x x --- +-- With nested CPR, DmdResult can be arbitrarily deep; consider e.g. the +-- DmdResult of repeat -- So we need to forget information at a certain depth. We do that at all points --- where we are constructing new RetCon constructors. +-- where we are building RetCon constructors. cutDmdResult :: Int -> DmdResult -> DmdResult cutDmdResult 0 _ = topRes cutDmdResult _ Diverges = Diverges @@ -825,6 +821,10 @@ cutCPRResult :: Int -> CPRResult -> CPRResult cutCPRResult _ NoCPR = NoCPR cutCPRResult n (RetCon tag rs) = RetCon tag (map (cutDmdResult (n-1)) rs) +-- Forget that something might converge for sure +divergeDmdResult :: DmdResult -> DmdResult +divergeDmdResult r = r `lubDmdResult` botRes + -- Forget the CPR information, but remember if it converges or diverges -- Used for non-strict thunks and non-top-level things with sum type forgetCPR :: DmdResult -> DmdResult @@ -1445,6 +1445,9 @@ botSig = StrictSig botDmdType cprProdSig :: Arity -> StrictSig cprProdSig arity = StrictSig (cprProdDmdType arity) +sigMayConverge :: StrictSig -> StrictSig +sigMayConverge (StrictSig (DmdType env ds res)) = (StrictSig (DmdType env ds (divergeDmdResult res))) + argsOneShots :: StrictSig -> Arity -> [[OneShotInfo]] argsOneShots (StrictSig (DmdType _ arg_ds _)) n_val_args = go arg_ds diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index ea1a588..d5bf8a0 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -1084,7 +1084,10 @@ updSigEnv env sigs = env { ae_sigs = sigs } extendAnalEnv :: TopLevelFlag -> AnalEnv -> Id -> StrictSig -> AnalEnv extendAnalEnv top_lvl env var sig - = env { ae_sigs = extendSigEnv top_lvl (ae_sigs env) var sig } + = env { ae_sigs = extendSigEnv top_lvl (ae_sigs env) var sig' } + where + sig' | isWeakLoopBreaker (idOccInfo var) = sigMayConverge sig + | otherwise = sig extendSigEnv :: TopLevelFlag -> SigEnv -> Id -> StrictSig -> SigEnv extendSigEnv top_lvl sigs var sig = extendVarEnv sigs var (sig, top_lvl) From git at git.haskell.org Sun Dec 15 16:23:22 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 15 Dec 2013 16:23:22 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Split DmdResult into DmdResult and CPRResult (d54cfac) Message-ID: <20131215162322.5C1D62406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/d54cfac2511f57d056529cb778ced2b405269fdc/ghc >--------------------------------------------------------------- commit d54cfac2511f57d056529cb778ced2b405269fdc Author: Joachim Breitner Date: Thu Dec 12 15:39:30 2013 +0000 Split DmdResult into DmdResult and CPRResult this is a small-step-refactoring patch and not very interesting on its own. >--------------------------------------------------------------- d54cfac2511f57d056529cb778ced2b405269fdc compiler/basicTypes/Demand.lhs | 170 ++++++++++++++++++++++++++-------------- compiler/basicTypes/MkId.lhs | 4 +- compiler/stranal/DmdAnal.lhs | 16 ++-- 3 files changed, 119 insertions(+), 71 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 d54cfac2511f57d056529cb778ced2b405269fdc From git at git.haskell.org Sun Dec 15 16:23:24 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 15 Dec 2013 16:23:24 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Do not export DmdResult constructors in Demand.lhs (9b41137) Message-ID: <20131215162324.8C41D2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/9b411376f793cdfc207434e0bcdc7462c5597120/ghc >--------------------------------------------------------------- commit 9b411376f793cdfc207434e0bcdc7462c5597120 Author: Joachim Breitner Date: Mon Dec 9 16:56:32 2013 +0000 Do not export DmdResult constructors in Demand.lhs >--------------------------------------------------------------- 9b411376f793cdfc207434e0bcdc7462c5597120 compiler/basicTypes/Demand.lhs | 20 ++++++++++---------- compiler/basicTypes/MkId.lhs | 4 ++-- 2 files changed, 12 insertions(+), 12 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 3d393f1..3ca8466 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -25,7 +25,7 @@ module Demand ( DmdEnv, emptyDmdEnv, peelFV, - DmdResult(..), CPRResult(..), + DmdResult, CPRResult, isBotRes, isTopRes, resTypeArgDmd, topRes, botRes, cprProdRes, vanillaCprProdRes, cprSumRes, appIsBottom, isBottomingSig, pprIfaceStrictSig, @@ -768,19 +768,19 @@ topRes, botRes :: DmdResult topRes = Dunno NoCPR botRes = Diverges -cprSumRes :: ConTag -> CPRResult -cprSumRes tag | opt_CprOff = NoCPR - | otherwise = RetSum tag +cprSumRes :: ConTag -> DmdResult +cprSumRes tag | opt_CprOff = topRes + | otherwise = Dunno $ RetSum tag -cprProdRes :: [DmdType] -> CPRResult +cprProdRes :: [DmdType] -> DmdResult cprProdRes _arg_tys - | opt_CprOff = NoCPR - | otherwise = RetProd + | opt_CprOff = topRes + | otherwise = Dunno $ RetProd -vanillaCprProdRes :: Arity -> CPRResult +vanillaCprProdRes :: Arity -> DmdResult vanillaCprProdRes _arity - | opt_CprOff = NoCPR - | otherwise = RetProd + | opt_CprOff = topRes + | otherwise = Dunno $ RetProd isTopRes :: DmdResult -> Bool isTopRes (Dunno NoCPR) = True diff --git a/compiler/basicTypes/MkId.lhs b/compiler/basicTypes/MkId.lhs index 6120b56..604163f 100644 --- a/compiler/basicTypes/MkId.lhs +++ b/compiler/basicTypes/MkId.lhs @@ -434,8 +434,8 @@ dataConCPR con , isVanillaDataCon con -- No existentials , wkr_arity > 0 , wkr_arity <= mAX_CPR_SIZE - = if is_prod then Dunno (vanillaCprProdRes (dataConRepArity con)) - else Dunno (cprSumRes (dataConTag con)) + = if is_prod then vanillaCprProdRes (dataConRepArity con) + else cprSumRes (dataConTag con) | otherwise = topRes where From git at git.haskell.org Sun Dec 15 16:23:27 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 15 Dec 2013 16:23:27 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Rename postProcessDmdType to postProcessUnsat and use* to reuse* (d651a93) Message-ID: <20131215162327.309492406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/d651a93ef627a555c453bf9dbd79c20a0e5b3fb1/ghc >--------------------------------------------------------------- commit d651a93ef627a555c453bf9dbd79c20a0e5b3fb1 Author: Joachim Breitner Date: Thu Dec 12 16:12:00 2013 +0000 Rename postProcessDmdType to postProcessUnsat and use* to reuse* >--------------------------------------------------------------- d651a93ef627a555c453bf9dbd79c20a0e5b3fb1 compiler/basicTypes/Demand.lhs | 81 ++++++++++++++++++++++------------------ compiler/stranal/DmdAnal.lhs | 4 +- 2 files changed, 46 insertions(+), 39 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 3ca8466..cdb60af 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -38,13 +38,13 @@ module Demand ( evalDmd, cleanEvalDmd, cleanEvalProdDmd, isStrictDmd, splitDmdTy, splitFVs, deferAfterIO, - postProcessDmdType, postProcessDmdTypeM, + postProcessUnsat, postProcessDmdTypeM, splitProdDmd, splitProdDmd_maybe, peelCallDmd, mkCallDmd, dmdTransformSig, dmdTransformDataConSig, dmdTransformDictSelSig, argOneShots, argsOneShots, - isSingleUsed, useEnv, zapDemand, zapStrictSig, + isSingleUsed, reuseEnv, zapDemand, zapStrictSig, worthSplittingArgDmd, worthSplittingThunkDmd, @@ -400,23 +400,25 @@ Compare with: (C) making Used win for both, but UProd win for lub \begin{code} -markAsUsedDmd :: MaybeUsed -> MaybeUsed -markAsUsedDmd Abs = Abs -markAsUsedDmd (Use _ a) = Use Many (markUsed a) +-- If a demand is used multiple times (i.e. reused), than any use-once +-- mentioned there, that is not protected by a UCall, can happen many times. +markReusedDmd :: MaybeUsed -> MaybeUsed +markReusedDmd Abs = Abs +markReusedDmd (Use _ a) = Use Many (markReused a) -markUsed :: UseDmd -> UseDmd -markUsed (UCall _ u) = UCall Many u -- No need to recurse here -markUsed (UProd ux) = UProd (map markAsUsedDmd ux) -markUsed u = u +markReused :: UseDmd -> UseDmd +markReused (UCall _ u) = UCall Many u -- No need to recurse here +markReused (UProd ux) = UProd (map markReusedDmd ux) +markReused u = u isUsedMU :: MaybeUsed -> Bool --- True <=> markAsUsedDmd d = d +-- True <=> markReusedDmd d = d isUsedMU Abs = True isUsedMU (Use One _) = False isUsedMU (Use Many u) = isUsedU u isUsedU :: UseDmd -> Bool --- True <=> markUsed d = d +-- True <=> markReused d = d isUsedU Used = True isUsedU UHead = True isUsedU (UProd us) = all isUsedMU us @@ -1121,34 +1123,39 @@ toCleanDmd (JD { strd = s, absd = u }) (Lazy, Use c u') -> (CD { sd = HeadStr, ud = u' }, Just (True, c)) (_, Abs) -> (CD { sd = HeadStr, ud = Used }, Nothing) +-- This is used in dmdAnalStar when post-processing +-- a function's argument demand. So we only care about what +-- does to free variables, and whether it terminates. postProcessDmdTypeM :: DeferAndUseM -> DmdType -> DmdType postProcessDmdTypeM Nothing _ = nopDmdType -- Incoming demand was Absent, so just discard all usage information -- We only processed the thing at all to analyse the body -- See Note [Always analyse in virgin pass] -postProcessDmdTypeM (Just du) ty = postProcessDmdType du ty - -postProcessDmdType :: DeferAndUse -> DmdType -> DmdType -postProcessDmdType (True, Many) ty = deferAndUse ty -postProcessDmdType (False, Many) ty = useType ty -postProcessDmdType (True, One) ty = deferType ty -postProcessDmdType (False, One) ty = ty - -deferType, useType, deferAndUse :: DmdType -> DmdType -deferType (DmdType fv ds _) = DmdType (deferEnv fv) (map deferDmd ds) topRes -useType (DmdType fv ds res_ty) = DmdType (useEnv fv) (map useDmd ds) res_ty -deferAndUse (DmdType fv ds _) = DmdType (deferUseEnv fv) (map deferUseDmd ds) topRes - -deferEnv, useEnv, deferUseEnv :: DmdEnv -> DmdEnv -deferEnv fv = mapVarEnv deferDmd fv -useEnv fv = mapVarEnv useDmd fv -deferUseEnv fv = mapVarEnv deferUseDmd fv - -deferDmd, useDmd, deferUseDmd :: JointDmd -> JointDmd -deferDmd (JD {strd=_, absd=a}) = mkJointDmd Lazy a -useDmd (JD {strd=d, absd=a}) = mkJointDmd d (markAsUsedDmd a) -deferUseDmd (JD {strd=_, absd=a}) = mkJointDmd Lazy (markAsUsedDmd a) - +postProcessDmdTypeM (Just du) ty = postProcessUnsat du ty + +postProcessUnsat :: DeferAndUse -> DmdType -> DmdType +postProcessUnsat (True, Many) ty = deferReuse ty +postProcessUnsat (False, Many) ty = reuseType ty +postProcessUnsat (True, One) ty = deferType ty +postProcessUnsat (False, One) ty = ty + +deferType, reuseType, deferReuse :: DmdType -> DmdType +deferType (DmdType fv ds _) = DmdType (deferEnv fv) (map deferDmd ds) topRes +reuseType (DmdType fv ds res_ty) = DmdType (reuseEnv fv) (map reuseDmd ds) res_ty +deferReuse (DmdType fv ds _) = DmdType (deferReuseEnv fv) (map deferReuseDmd ds) topRes + +deferEnv, reuseEnv, deferReuseEnv :: DmdEnv -> DmdEnv +deferEnv fv = mapVarEnv deferDmd fv +reuseEnv fv = mapVarEnv reuseDmd fv +deferReuseEnv fv = mapVarEnv deferReuseDmd fv + +deferDmd, reuseDmd, deferReuseDmd :: JointDmd -> JointDmd +deferDmd (JD {strd=_, absd=a}) = mkJointDmd Lazy a +reuseDmd (JD {strd=d, absd=a}) = mkJointDmd d (markReusedDmd a) +deferReuseDmd (JD {strd=_, absd=a}) = mkJointDmd Lazy (markReusedDmd a) + +-- Peels one call level from the demand, and also returns +-- whether it was unsaturated (separately for strictness and usage) peelCallDmd :: CleanDemand -> (CleanDemand, DeferAndUse) -- Exploiting the fact that -- on the strictness side C(B) = B @@ -1352,8 +1359,8 @@ dmdTransformSig :: StrictSig -> CleanDemand -> DmdType -- signature is fun_sig, with demand dmd. We return the demand -- that the function places on its context (eg its args) dmdTransformSig (StrictSig dmd_ty@(DmdType _ arg_ds _)) cd - = postProcessDmdType (peelManyCalls arg_ds cd) dmd_ty - -- NB: it's important to use postProcessDmdType, and not + = postProcessUnsat (peelManyCalls arg_ds cd) dmd_ty + -- NB: it's important to use postProcessUnsat, and not -- just return nopDmdType for unsaturated calls -- Consider let { f x y = p + x } in f 1 -- The application isn't saturated, but we must nevertheless propagate @@ -1391,7 +1398,7 @@ dmdTransformDictSelSig :: StrictSig -> CleanDemand -> DmdType dmdTransformDictSelSig (StrictSig (DmdType _ [dict_dmd] _)) cd | (cd',defer_use) <- peelCallDmd cd , Just jds <- splitProdDmd_maybe dict_dmd - = postProcessDmdType defer_use $ + = postProcessUnsat defer_use $ DmdType emptyDmdEnv [mkOnceUsedDmd $ mkProdDmd $ map (enhance cd') jds] topRes | otherwise = nopDmdType -- See Note [Demand transformer for a dictionary selector] diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index 01c990a..cbdcc67 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -206,7 +206,7 @@ dmdAnal env dmd (Lam var body) (body_ty, body') = dmdAnal env' body_dmd body (lam_ty, var') = annotateLamIdBndr env notArgOfDfun body_ty one_shot var in - (postProcessDmdType defer_and_use lam_ty, Lam var' body') + (postProcessUnsat defer_and_use lam_ty, Lam var' body') dmdAnal env dmd (Case scrut case_bndr ty [alt@(DataAlt dc, _, _)]) -- Only one alternative with a product constructor @@ -619,7 +619,7 @@ dmdAnalRhs top_lvl rec_flag env id rhs -- See Note [Lazy and unleashable free variables] -- See Note [Aggregated demand for cardinality] rhs_fv1 = case rec_flag of - Just bs -> useEnv (delVarEnvList rhs_fv bs) + Just bs -> reuseEnv (delVarEnvList rhs_fv bs) Nothing -> rhs_fv (lazy_fv, sig_fv) = splitFVs is_thunk rhs_fv1 From git at git.haskell.org Sun Dec 15 16:23:29 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 15 Dec 2013 16:23:29 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Refactor peelManyCalls (dc76ff0) Message-ID: <20131215162329.5746D2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/dc76ff0b6354c5c9785cf315ffd204b59ba4ba44/ghc >--------------------------------------------------------------- commit dc76ff0b6354c5c9785cf315ffd204b59ba4ba44 Author: Joachim Breitner Date: Sat Dec 14 22:07:04 2013 +0100 Refactor peelManyCalls its first argument is just used for its length (the arity of the call). So changing the type to Int to reflect that. Also add a note [Demands from unsaturated function calls] that hopefully comprehensively and comprehensibly explains what is going on here. >--------------------------------------------------------------- dc76ff0b6354c5c9785cf315ffd204b59ba4ba44 compiler/basicTypes/Demand.lhs | 71 ++++++++++++++++++++++++++++++---------- 1 file changed, 53 insertions(+), 18 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index cdb60af..bb88e40 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -1172,21 +1172,60 @@ peelCallDmd (CD {sd = s, ud = u}) -- because the body isn't used at all! -- c.f. the Abs case in toCleanDmd -peelManyCalls :: [Demand] -> CleanDemand -> DeferAndUse -peelManyCalls arg_ds (CD { sd = str, ud = abs }) - = (go_str arg_ds str, go_abs arg_ds abs) +-- Peels that multiple nestings of calls clean demand and also returns +-- whether it was unsaturated (separately for strictness and usage +-- see Note [Demands from unsaturated function calls] +peelManyCalls :: Int -> CleanDemand -> DeferAndUse +peelManyCalls n (CD { sd = str, ud = abs }) + = (go_str n str, go_abs n abs) where - go_str :: [Demand] -> StrDmd -> Bool -- True <=> unsaturated, defer - go_str [] _ = False - go_str (_:_) HyperStr = False -- HyperStr = Call(HyperStr) - go_str (_:as) (SCall d') = go_str as d' - go_str _ _ = True + go_str :: Int -> StrDmd -> Bool -- True <=> unsaturated, defer + go_str 0 _ = False + go_str _ HyperStr = False -- == go_str (n-1) HyperStr, as HyperStr = Call(HyperStr) + go_str n (SCall d') = go_str (n-1) d' + go_str _ _ = True + + go_abs :: Int -> UseDmd -> Count -- Many <=> unsaturated, or at least + go_abs 0 _ = One -- one UCall Many in the demand + go_abs n (UCall One d') = go_abs (n-1) d' + go_abs _ _ = Many +\end{code} - go_abs :: [Demand] -> UseDmd -> Count -- Many <=> unsaturated, or at least - go_abs [] _ = One -- one UCall Many in the demand - go_abs (_:as) (UCall One d') = go_abs as d' - go_abs _ _ = Many +Note [Demands from unsaturated function calls] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + +Consider a demand transformer d1 -> d2 -> r for f. +If a sufficiently detailed demand is fed into this transformer, +e.g arising from "f x1 x2" in a strict, use-once context, +then d1 and d2 is precisely the demand unleashed onto x1 and x2 (similar for +the free variable environment) and furthermore the result information r is the +one we want to use. + +But the demand fed into f might be less than . There are a few cases: + * Not enough demand on the strictness side: + - In that case, we need to zap all strictness in the demand on arguments and + free variables. + - Furthermore, we need to remove CPR information (after all, "f x1" surely + does not return a constructor). + - And finally, if r said that f would (possible or definitely) diverge when + called with two arguments, then "f x1" may diverge. So we use topRes here. + (We could return "Converges NoCPR" if f would converge for sure, but that + information would currently not be useful in any way.) + * Not enough demand from the usage side: The missing usage can expanded using + UCall Many, therefore this is subsumed by the third case: + * At least one of the uses has a cardinality of Many. + - Even if f puts a One demand on any of its argument or free variables, if + we call f multiple times, we may evaluate this argument or free variable + multiple times. So forget about any occurrence of "One" in the demand. + +In dmdTransformSig, we call peelManyCalls to find out if we are in any of these +cases, and then call postProcessUnsat to reduce the demand appropriately. + +Similarly, dmdTransformDictSelSig and dmdAnal, when analyzing a Lambda, use +peelCallDmd, which peels only one level, but also returns the demand put on the +body of the function. +\begin{code} peelFV :: DmdType -> Var -> (DmdType, Demand) peelFV (DmdType fv ds res) id = -- pprTrace "rfv" (ppr id <+> ppr dmd $$ ppr fv) (DmdType fv' ds res, dmd) @@ -1359,12 +1398,8 @@ dmdTransformSig :: StrictSig -> CleanDemand -> DmdType -- signature is fun_sig, with demand dmd. We return the demand -- that the function places on its context (eg its args) dmdTransformSig (StrictSig dmd_ty@(DmdType _ arg_ds _)) cd - = postProcessUnsat (peelManyCalls arg_ds cd) dmd_ty - -- NB: it's important to use postProcessUnsat, and not - -- just return nopDmdType for unsaturated calls - -- Consider let { f x y = p + x } in f 1 - -- The application isn't saturated, but we must nevertheless propagate - -- a lazy demand for p! + = postProcessUnsat (peelManyCalls (length arg_ds) cd) dmd_ty + -- see Note [Demands from unsaturated function calls] dmdTransformDataConSig :: Arity -> StrictSig -> CleanDemand -> DmdType -- Same as dmdTransformSig but for a data constructor (worker), From git at git.haskell.org Sun Dec 15 16:23:31 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 15 Dec 2013 16:23:31 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Disentangle postProcessDmdTypeM and postProcessUnsat (a2f9fb9) Message-ID: <20131215162331.A28172406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/a2f9fb99297cc8585b1b2af2bcfe8352bacce13f/ghc >--------------------------------------------------------------- commit a2f9fb99297cc8585b1b2af2bcfe8352bacce13f Author: Joachim Breitner Date: Mon Dec 9 18:40:09 2013 +0000 Disentangle postProcessDmdTypeM and postProcessUnsat Make different postProcess code paths for function arguments (which are post-processed just to be both'ed) and unsaturated functions (which are post-processed for other reasons.) >--------------------------------------------------------------- a2f9fb99297cc8585b1b2af2bcfe8352bacce13f compiler/basicTypes/Demand.lhs | 14 +++++++++++++- 1 file changed, 13 insertions(+), 1 deletion(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index bb88e40..09b6f60 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -1131,7 +1131,19 @@ postProcessDmdTypeM Nothing _ = nopDmdType -- Incoming demand was Absent, so just discard all usage information -- We only processed the thing at all to analyse the body -- See Note [Always analyse in virgin pass] -postProcessDmdTypeM (Just du) ty = postProcessUnsat du ty +postProcessDmdTypeM (Just du) (DmdType fv _ res_ty) + = DmdType (postProcessDmdEnv du fv) [] (postProcessDmdResult du res_ty) + +postProcessDmdResult :: DeferAndUse -> DmdResult -> DmdResult +postProcessDmdResult (True,_) r = topRes +postProcessDmdResult (False,_) r = r + +postProcessDmdEnv :: DeferAndUse -> DmdEnv -> DmdEnv +postProcessDmdEnv (True, Many) env = deferReuseEnv env +postProcessDmdEnv (False, Many) env = reuseEnv env +postProcessDmdEnv (True, One) env = deferEnv env +postProcessDmdEnv (False, One) env = env + postProcessUnsat :: DeferAndUse -> DmdType -> DmdType postProcessUnsat (True, Many) ty = deferReuse ty From git at git.haskell.org Sun Dec 15 16:23:33 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 15 Dec 2013 16:23:33 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Make types of bothDmdType more precise (c26d31d) Message-ID: <20131215162333.E5A6C2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/c26d31d0591e91b283e4c048a89b82821e30eeeb/ghc >--------------------------------------------------------------- commit c26d31d0591e91b283e4c048a89b82821e30eeeb Author: Joachim Breitner Date: Mon Dec 9 18:40:09 2013 +0000 Make types of bothDmdType more precise by only passing the demand on the free variables, and whether the argument (resp. scrunitee) may or will diverge. >--------------------------------------------------------------- c26d31d0591e91b283e4c048a89b82821e30eeeb compiler/basicTypes/Demand.lhs | 55 +++++++++++++++++++++++++--------------- compiler/stranal/DmdAnal.lhs | 9 +++---- 2 files changed, 39 insertions(+), 25 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 09b6f60..2b69b4d 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -21,6 +21,7 @@ module Demand ( DmdType(..), dmdTypeDepth, lubDmdType, bothDmdType, nopDmdType, botDmdType, mkDmdType, addDemand, + BothDmdArg, mkBothDmdArg, toBothDmdArg, DmdEnv, emptyDmdEnv, peelFV, @@ -709,14 +710,15 @@ We have lubs, but not glbs; but that is ok. -- Constructed Product Result ------------------------------------------------------------------------ -data CPRResult = NoCPR -- Top of the lattice - | RetProd -- Returns a constructor from a product type - | RetSum ConTag -- Returns a constructor from a sum type with this tag +data Termination r = Diverges -- Definitely diverges + | Dunno r -- Might diverge or converge deriving( Eq, Show ) -data DmdResult = Diverges -- Definitely diverges - | Dunno CPRResult -- Might diverge or converge, but in the latter case the - -- result shape is described by CPRResult +type DmdResult = Termination CPRResult + +data CPRResult = NoCPR -- Top of the lattice + | RetProd -- Returns a constructor from a product type + | RetSum ConTag -- Returns a constructor from a data type deriving( Eq, Show ) lubCPR :: CPRResult -> CPRResult -> CPRResult @@ -733,7 +735,7 @@ lubDmdResult (Dunno c1) (Dunno c2) = Dunno (c1 `lubCPR` c2) -- defaultDmd (r1 `lubDmdResult` r2) = defaultDmd r1 `lubDmd` defaultDmd r2 -- (See Note [Default demand on free variables] for why) -bothDmdResult :: DmdResult -> DmdResult -> DmdResult +bothDmdResult :: DmdResult -> Termination () -> DmdResult -- See Note [Asymmetry of 'both' for DmdType and DmdResult] bothDmdResult _ Diverges = Diverges bothDmdResult r _ = r @@ -1024,13 +1026,25 @@ lubDmdType (DmdType fv1 ds1 r1) (DmdType fv2 ds2 r2) lub_ds ds1 [] = map (`lubDmd` resTypeArgDmd r2) ds1 lub_ds [] ds2 = map (resTypeArgDmd r1 `lubDmd`) ds2 -bothDmdType :: DmdType -> DmdType -> DmdType -bothDmdType (DmdType fv1 ds1 r1) (DmdType fv2 _ r2) + +type BothDmdArg = (DmdEnv, Termination ()) + +mkBothDmdArg :: DmdEnv -> BothDmdArg +mkBothDmdArg env = (env, Dunno ()) + +toBothDmdArg :: DmdType -> BothDmdArg +toBothDmdArg (DmdType fv _ r) = (fv, go r) + where + go (Dunno {}) = Dunno () + go Diverges = Diverges + +bothDmdType :: DmdType -> BothDmdArg -> DmdType +bothDmdType (DmdType fv1 ds1 r1) (fv2, t2) -- See Note [Asymmetry of 'both' for DmdType and DmdResult] -- 'both' takes the argument/result info from its *first* arg, -- using its second arg just for its free-var info. - = DmdType both_fv ds1 (r1 `bothDmdResult` r2) - where both_fv = plusVarEnv_CD bothDmd fv1 (defaultDmd r1) fv2 (defaultDmd r2) + = DmdType both_fv ds1 (r1 `bothDmdResult` t2) + where both_fv = plusVarEnv_CD bothDmd fv1 (defaultDmd r1) fv2 (defaultDmd t2) instance Outputable DmdType where ppr (DmdType fv ds res) @@ -1126,17 +1140,18 @@ toCleanDmd (JD { strd = s, absd = u }) -- This is used in dmdAnalStar when post-processing -- a function's argument demand. So we only care about what -- does to free variables, and whether it terminates. -postProcessDmdTypeM :: DeferAndUseM -> DmdType -> DmdType -postProcessDmdTypeM Nothing _ = nopDmdType +postProcessDmdTypeM :: DeferAndUseM -> DmdType -> BothDmdArg +postProcessDmdTypeM Nothing _ = (emptyDmdEnv, Dunno ()) -- Incoming demand was Absent, so just discard all usage information -- We only processed the thing at all to analyse the body -- See Note [Always analyse in virgin pass] postProcessDmdTypeM (Just du) (DmdType fv _ res_ty) - = DmdType (postProcessDmdEnv du fv) [] (postProcessDmdResult du res_ty) + = (postProcessDmdEnv du fv, postProcessDmdResult du res_ty) -postProcessDmdResult :: DeferAndUse -> DmdResult -> DmdResult -postProcessDmdResult (True,_) r = topRes -postProcessDmdResult (False,_) r = r +postProcessDmdResult :: DeferAndUse -> DmdResult -> Termination () +postProcessDmdResult (True,_) _ = Dunno () +postProcessDmdResult (False,_) (Dunno {}) = Dunno () +postProcessDmdResult (False,_) Diverges = Diverges postProcessDmdEnv :: DeferAndUse -> DmdEnv -> DmdEnv postProcessDmdEnv (True, Many) env = deferReuseEnv env @@ -1246,9 +1261,9 @@ peelFV (DmdType fv ds res) id = -- pprTrace "rfv" (ppr id <+> ppr dmd $$ ppr fv) -- See note [Default demand on free variables] dmd = lookupVarEnv fv id `orElse` defaultDmd res -defaultDmd :: DmdResult -> Demand -defaultDmd res | isBotRes res = botDmd - | otherwise = absDmd +defaultDmd :: Termination r -> Demand +defaultDmd Diverges = botDmd +defaultDmd _ = absDmd addDemand :: Demand -> DmdType -> DmdType addDemand dmd (DmdType fv ds res) = DmdType fv (dmd:ds) res diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index cbdcc67..a942c4e 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -115,7 +115,7 @@ dmdTransformThunkDmd e -- See |-* relation in the companion paper dmdAnalStar :: AnalEnv -> Demand -- This one takes a *Demand* - -> CoreExpr -> (DmdType, CoreExpr) + -> CoreExpr -> (BothDmdArg, CoreExpr) dmdAnalStar env dmd e | (cd, defer_and_use) <- toCleanDmd dmd , (dmd_ty, e') <- dmdAnal env cd e @@ -255,7 +255,7 @@ dmdAnal env dmd (Case scrut case_bndr ty [alt@(DataAlt dc, _, _)]) scrut_dmd = scrut_dmd1 `bothCleanDmd` scrut_dmd2 (scrut_ty, scrut') = dmdAnal env scrut_dmd scrut - res_ty = alt_ty1 `bothDmdType` scrut_ty + res_ty = alt_ty1 `bothDmdType` toBothDmdArg scrut_ty in -- pprTrace "dmdAnal:Case1" (vcat [ text "scrut" <+> ppr scrut -- , text "dmd" <+> ppr dmd @@ -271,7 +271,7 @@ dmdAnal env dmd (Case scrut case_bndr ty alts) (alt_tys, alts') = mapAndUnzip (dmdAnalAlt env dmd) alts (scrut_ty, scrut') = dmdAnal env cleanEvalDmd scrut (alt_ty, case_bndr') = annotateBndr env (foldr lubDmdType botDmdType alt_tys) case_bndr - res_ty = alt_ty `bothDmdType` scrut_ty + res_ty = alt_ty `bothDmdType` toBothDmdArg scrut_ty in -- pprTrace "dmdAnal:Case2" (vcat [ text "scrut" <+> ppr scrut -- , text "scrut_ty" <+> ppr scrut_ty @@ -509,7 +509,6 @@ dmdTransform env var dmd | otherwise -- Local non-letrec-bound thing = unitVarDmd var (mkOnceUsedDmd dmd) - \end{code} %************************************************************************ @@ -698,7 +697,7 @@ addVarDmd (DmdType fv ds res) var dmd addLazyFVs :: DmdType -> DmdEnv -> DmdType addLazyFVs dmd_ty lazy_fvs - = dmd_ty `bothDmdType` mkDmdType lazy_fvs [] topRes + = dmd_ty `bothDmdType` mkBothDmdArg lazy_fvs -- Using bothDmdType (rather than just both'ing the envs) -- is vital. Consider -- let f = \x -> (x,y) From git at git.haskell.org Sun Dec 15 16:23:36 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 15 Dec 2013 16:23:36 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Add Converges to DmdResult (659c628) Message-ID: <20131215162336.36A572406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/659c62885432bc60b634141fc81166f2c8e3b1e5/ghc >--------------------------------------------------------------- commit 659c62885432bc60b634141fc81166f2c8e3b1e5 Author: Joachim Breitner Date: Thu Dec 12 15:45:19 2013 +0000 Add Converges to DmdResult to detect definite convergence (required for nested CPR). >--------------------------------------------------------------- 659c62885432bc60b634141fc81166f2c8e3b1e5 compiler/basicTypes/Demand.lhs | 41 ++++++++++++++++++++++++++++------------ 1 file changed, 29 insertions(+), 12 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 2b69b4d..fc6a81a 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -691,8 +691,8 @@ splitProdDmd_maybe (JD {strd = s, absd = u}) DmdResult: Dunno CPRResult - / - Diverges + / \ + Diverges Converges CPRResult CPRResult: NoCPR @@ -700,7 +700,7 @@ CPRResult: NoCPR RetProd RetSum ConTag -Product contructors return (Dunno (RetProd rs)) +Product contructors return (Converges (RetProd rs)) In a fixpoint iteration, start from Diverges We have lubs, but not glbs; but that is ok. @@ -711,6 +711,7 @@ We have lubs, but not glbs; but that is ok. ------------------------------------------------------------------------ data Termination r = Diverges -- Definitely diverges + | Converges r -- Definitely converges | Dunno r -- Might diverge or converge deriving( Eq, Show ) @@ -729,7 +730,11 @@ lubCPR _ _ = NoCPR lubDmdResult :: DmdResult -> DmdResult -> DmdResult lubDmdResult Diverges r = r +lubDmdResult (Converges c1) Diverges = Converges c1 +lubDmdResult (Converges c1) (Converges c2) = Converges (c1 `lubCPR` c2) +lubDmdResult (Converges c1) (Dunno c2) = Dunno (c1 `lubCPR` c2) lubDmdResult (Dunno c1) Diverges = Dunno c1 +lubDmdResult (Dunno c1) (Converges c2) = Dunno (c1 `lubCPR` c2) lubDmdResult (Dunno c1) (Dunno c2) = Dunno (c1 `lubCPR` c2) -- This needs to commute with defaultDmd, i.e. -- defaultDmd (r1 `lubDmdResult` r2) = defaultDmd r1 `lubDmd` defaultDmd r2 @@ -738,6 +743,7 @@ lubDmdResult (Dunno c1) (Dunno c2) = Dunno (c1 `lubCPR` c2) bothDmdResult :: DmdResult -> Termination () -> DmdResult -- See Note [Asymmetry of 'both' for DmdType and DmdResult] bothDmdResult _ Diverges = Diverges +bothDmdResult (Converges c1) (Dunno {}) = Dunno c1 bothDmdResult r _ = r -- This needs to commute with defaultDmd, i.e. -- defaultDmd (r1 `bothDmdResult` r2) = defaultDmd r1 `bothDmd` defaultDmd r2 @@ -745,6 +751,7 @@ bothDmdResult r _ = r instance Outputable DmdResult where ppr Diverges = char 'b' + ppr (Converges c) = char 't' <> ppr c ppr (Dunno c) = ppr c instance Outputable CPRResult where @@ -754,6 +761,7 @@ instance Outputable CPRResult where seqDmdResult :: DmdResult -> () seqDmdResult Diverges = () +seqDmdResult (Converges c) = seqCPRResult c seqDmdResult (Dunno c) = seqCPRResult c seqCPRResult :: CPRResult -> () @@ -774,17 +782,17 @@ botRes = Diverges cprSumRes :: ConTag -> DmdResult cprSumRes tag | opt_CprOff = topRes - | otherwise = Dunno $ RetSum tag + | otherwise = Converges $ RetSum tag cprProdRes :: [DmdType] -> DmdResult cprProdRes _arg_tys | opt_CprOff = topRes - | otherwise = Dunno $ RetProd + | otherwise = Converges $ RetProd vanillaCprProdRes :: Arity -> DmdResult vanillaCprProdRes _arity | opt_CprOff = topRes - | otherwise = Dunno $ RetProd + | otherwise = Converges $ RetProd isTopRes :: DmdResult -> Bool isTopRes (Dunno NoCPR) = True @@ -798,6 +806,7 @@ trimCPRInfo :: Bool -> Bool -> DmdResult -> DmdResult trimCPRInfo trim_all trim_sums res = trimR res where + trimR (Converges c) = Converges (trimC c) trimR (Dunno c) = Dunno (trimC c) trimR Diverges = Diverges @@ -811,6 +820,7 @@ returnsCPR :: DmdResult -> Bool returnsCPR dr = isJust (returnsCPR_maybe dr) returnsCPR_maybe :: DmdResult -> Maybe ConTag +returnsCPR_maybe (Converges c) = retCPR_maybe c returnsCPR_maybe (Dunno c) = retCPR_maybe c returnsCPR_maybe Diverges = Nothing @@ -1036,6 +1046,7 @@ toBothDmdArg :: DmdType -> BothDmdArg toBothDmdArg (DmdType fv _ r) = (fv, go r) where go (Dunno {}) = Dunno () + go (Converges {}) = Converges () go Diverges = Diverges bothDmdType :: DmdType -> BothDmdArg -> DmdType @@ -1069,7 +1080,7 @@ botDmdType = DmdType emptyDmdEnv [] botRes cprProdDmdType :: Arity -> DmdType cprProdDmdType _arity - = DmdType emptyDmdEnv [] (Dunno RetProd) + = DmdType emptyDmdEnv [] (Converges RetProd) isNopDmdType :: DmdType -> Bool isNopDmdType (DmdType env [] res) @@ -1098,7 +1109,7 @@ splitDmdTy ty@(DmdType _ [] res_ty) = (resTypeArgDmd res_ty, ty) -- exit? -- * We have to kill all strictness demands (i.e. lub with a lazy demand) -- * We can keep demand information (i.e. lub with an absent deman) --- * We have to kill definite divergence +-- * We have to kill definite divergence and definite convergence -- * We can keep CPR information. -- See Note [IO hack in the demand analyser] deferAfterIO :: DmdType -> DmdType @@ -1107,6 +1118,7 @@ deferAfterIO d@(DmdType _ _ res) = DmdType fv ds _ -> DmdType fv ds (defer_res res) where defer_res Diverges = topRes + defer_res (Converges r) = Dunno r defer_res r = r strictenDmd :: JointDmd -> CleanDemand @@ -1149,9 +1161,12 @@ postProcessDmdTypeM (Just du) (DmdType fv _ res_ty) = (postProcessDmdEnv du fv, postProcessDmdResult du res_ty) postProcessDmdResult :: DeferAndUse -> DmdResult -> Termination () -postProcessDmdResult (True,_) _ = Dunno () -postProcessDmdResult (False,_) (Dunno {}) = Dunno () -postProcessDmdResult (False,_) Diverges = Diverges + -- if we use it lazily, there cannot be divergence worrying us + -- (Otherwise we'd lose the termination information of constructors in in dmdAnalVarApp, for example) +postProcessDmdResult (True,_) _ = Converges () +postProcessDmdResult (False,_) (Dunno {}) = Dunno () +postProcessDmdResult (False,_) (Converges {}) = Converges () +postProcessDmdResult (False,_) Diverges = Diverges postProcessDmdEnv :: DeferAndUse -> DmdEnv -> DmdEnv postProcessDmdEnv (True, Many) env = deferReuseEnv env @@ -1720,11 +1735,13 @@ instance Binary DmdType where instance Binary DmdResult where put_ bh (Dunno c) = do { putByte bh 0; put_ bh c } - put_ bh Diverges = putByte bh 2 + put_ bh (Converges c) = do { putByte bh 1; put_ bh c } + put_ bh Diverges = putByte bh 3 get bh = do { h <- getByte bh ; case h of 0 -> do { c <- get bh; return (Dunno c) } + 1 -> do { c <- get bh; return (Converges c) } _ -> return Diverges } instance Binary CPRResult where From git at git.haskell.org Sun Dec 15 16:23:38 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 15 Dec 2013 16:23:38 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Unify RetProd and RetSum to RetCon in CPRResult (d58b354) Message-ID: <20131215162338.79BC62406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/d58b354d617567c0670f72835e3023d4f8c34d01/ghc >--------------------------------------------------------------- commit d58b354d617567c0670f72835e3023d4f8c34d01 Author: Joachim Breitner Date: Thu Dec 5 16:13:41 2013 +0000 Unify RetProd and RetSum to RetCon in CPRResult >--------------------------------------------------------------- d58b354d617567c0670f72835e3023d4f8c34d01 compiler/basicTypes/Demand.lhs | 102 ++++++++++++++++++++++------------------ compiler/basicTypes/MkId.lhs | 4 +- compiler/stranal/DmdAnal.lhs | 4 +- 3 files changed, 59 insertions(+), 51 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 d58b354d617567c0670f72835e3023d4f8c34d01 From git at git.haskell.org Sun Dec 15 16:23:40 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 15 Dec 2013 16:23:40 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Fix a lubDmdResult equation (12f88bb) Message-ID: <20131215162341.C2E852406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/12f88bb9aabcc29b890e98be939cd8f591e48c09/ghc >--------------------------------------------------------------- commit 12f88bb9aabcc29b890e98be939cd8f591e48c09 Author: Joachim Breitner Date: Tue Nov 26 10:17:57 2013 +0000 Fix a lubDmdResult equation >--------------------------------------------------------------- 12f88bb9aabcc29b890e98be939cd8f591e48c09 compiler/basicTypes/Demand.lhs | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index b68c10b..06d6c82 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -750,8 +750,10 @@ lubCPR (RetProd ds1) (RetProd ds2) lubCPR _ _ = NoCPR lubDmdResult :: DmdResult -> DmdResult -> DmdResult -lubDmdResult Diverges r = r -lubDmdResult (Converges c1) Diverges = Converges c1 +lubDmdResult Diverges (Dunno c2) = Dunno c2 +lubDmdResult Diverges Diverges = Diverges +lubDmdResult Diverges (Converges c2) = Dunno c2 +lubDmdResult (Converges c1) Diverges = Dunno c1 lubDmdResult (Converges c1) (Converges c2) = Converges (c1 `lubCPR` c2) lubDmdResult (Converges c1) (Dunno c2) = Dunno (c1 `lubCPR` c2) lubDmdResult (Dunno c1) Diverges = Dunno c1 From git at git.haskell.org Sun Dec 15 16:23:42 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 15 Dec 2013 16:23:42 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: In deferType, return convRes = Converges NoCPR (5a5c8de) Message-ID: <20131215162343.09CB42406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/5a5c8de79441857a4c169992bddec22476d54c3b/ghc >--------------------------------------------------------------- commit 5a5c8de79441857a4c169992bddec22476d54c3b Author: Joachim Breitner Date: Wed Dec 4 16:55:18 2013 +0000 In deferType, return convRes = Converges NoCPR because this is the right-identity to `bothDmdResult`, and this is the right thing to do in a lazy context. >--------------------------------------------------------------- 5a5c8de79441857a4c169992bddec22476d54c3b compiler/basicTypes/Demand.lhs | 7 ++++--- 1 file changed, 4 insertions(+), 3 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index fc6a81a..717f5ed 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -776,8 +776,9 @@ seqCPRResult RetProd = () -- [cprRes] lets us switch off CPR analysis -- by making sure that everything uses TopRes -topRes, botRes :: DmdResult +topRes, convRes, botRes :: DmdResult topRes = Dunno NoCPR +convRes = Converges NoCPR botRes = Diverges cprSumRes :: ConTag -> DmdResult @@ -1182,9 +1183,9 @@ postProcessUnsat (True, One) ty = deferType ty postProcessUnsat (False, One) ty = ty deferType, reuseType, deferReuse :: DmdType -> DmdType -deferType (DmdType fv ds _) = DmdType (deferEnv fv) (map deferDmd ds) topRes +deferType (DmdType fv ds _) = DmdType (deferEnv fv) (map deferDmd ds) convRes reuseType (DmdType fv ds res_ty) = DmdType (reuseEnv fv) (map reuseDmd ds) res_ty -deferReuse (DmdType fv ds _) = DmdType (deferReuseEnv fv) (map deferReuseDmd ds) topRes +deferReuse (DmdType fv ds _) = DmdType (deferReuseEnv fv) (map deferReuseDmd ds) convRes deferEnv, reuseEnv, deferReuseEnv :: DmdEnv -> DmdEnv deferEnv fv = mapVarEnv deferDmd fv From git at git.haskell.org Sun Dec 15 16:23:45 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 15 Dec 2013 16:23:45 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Comments and small refactor (4bf062e) Message-ID: <20131215162345.388122406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/4bf062eaee65fceaaad4bdcc196a9ef0d4bc23b8/ghc >--------------------------------------------------------------- commit 4bf062eaee65fceaaad4bdcc196a9ef0d4bc23b8 Author: Simon Peyton Jones Date: Wed Dec 4 16:00:24 2013 +0000 Comments and small refactor >--------------------------------------------------------------- 4bf062eaee65fceaaad4bdcc196a9ef0d4bc23b8 compiler/basicTypes/Demand.lhs | 2 +- compiler/stranal/DmdAnal.lhs | 9 ++++++--- 2 files changed, 7 insertions(+), 4 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index f75dc46..b68c10b 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -559,7 +559,7 @@ splitFVs is_thunk rhs_fvs %* * %************************************************************************ -This domain differst from JointDemand in the sense that pure absence +This domain differs from JointDemand in the sense that pure absence is taken away, i.e., we deal *only* with non-absent demands. Note [Strict demands] diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index 897b5b4..f94d53d 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -530,9 +530,6 @@ dmdAnalVarApp env dmd fun args -- , ppr arg_tys, ppr cpr_info, ppr res_ty]) $ ( res_ty , foldl App (Var fun) args') - - | otherwise - = completeApp env (dmdTransform env fun (mkCallDmdN n_val_args dmd), Var fun) args where n_val_args = valArgCount args cxt_ds = splitProdCleanDmd n_val_args dmd @@ -552,6 +549,12 @@ dmdAnalVarApp env dmd fun args , (arg_tys, arg_rets, args') <- anal_con_args ds args = (arg_ty:arg_tys, arg_ret:arg_rets, arg':args') anal_con_args ds args = pprPanic "anal_con_args" (ppr args $$ ppr ds) + +dmdAnalVarApp env dmd fun args + = --pprTrace "dmdAnalVarApp" (vcat [ ppr fun, ppr args + -- , ppr $ completeApp env (dmdTransform env fun (mkCallDmdN n_val_args dmd), Var fun) args + -- ]) + completeApp env (dmdTransform env fun (mkCallDmdN (valArgCount args) dmd), Var fun) args \end{code} %************************************************************************ From git at git.haskell.org Sun Dec 15 16:23:47 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 15 Dec 2013 16:23:47 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Initial work on Nested CPR (5864cbe) Message-ID: <20131215162347.7377C2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/5864cbe8ebd17915be6b2eba703efdbfc42b8cec/ghc >--------------------------------------------------------------- commit 5864cbe8ebd17915be6b2eba703efdbfc42b8cec Author: Simon Peyton Jones Date: Mon Nov 25 09:59:16 2013 +0000 Initial work on Nested CPR >--------------------------------------------------------------- 5864cbe8ebd17915be6b2eba703efdbfc42b8cec compiler/basicTypes/Demand.lhs | 137 ++++++++++++++++++++++++---------------- compiler/stranal/DmdAnal.lhs | 111 ++++++++++++++++++++++---------- 2 files changed, 160 insertions(+), 88 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 5864cbe8ebd17915be6b2eba703efdbfc42b8cec From git at git.haskell.org Sun Dec 15 16:23:50 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 15 Dec 2013 16:23:50 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Check mAX_CPR_SIZE in dmdAnalVarApp (80e8556) Message-ID: <20131215162350.2A51A2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/80e8556a3c0fdbe75d77dd42a3e062a7e422b019/ghc >--------------------------------------------------------------- commit 80e8556a3c0fdbe75d77dd42a3e062a7e422b019 Author: Joachim Breitner Date: Thu Dec 5 18:01:34 2013 +0000 Check mAX_CPR_SIZE in dmdAnalVarApp >--------------------------------------------------------------- 80e8556a3c0fdbe75d77dd42a3e062a7e422b019 compiler/stranal/DmdAnal.lhs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index d5bf8a0..3c613b2 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -522,6 +522,8 @@ dmdAnalVarApp env dmd fun args | Just con <- isDataConWorkId_maybe fun -- Data constructor , isVanillaDataCon con , n_val_args == dataConRepArity con -- Saturated + , dataConRepArity con > 0 + , dataConRepArity con < 10 -- TODO: Sync with mAX_CPR_SIZE in MkId , let cpr_info = cprConRes (dataConTag con) arg_rets res_ty = foldl bothDmdType (DmdType emptyDmdEnv [] cpr_info) arg_tys = -- pprTrace "dmdAnalVarApp" (vcat [ ppr con, ppr args, ppr n_val_args, ppr cxt_ds From git at git.haskell.org Sun Dec 15 16:23:52 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 15 Dec 2013 16:23:52 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: in Demand.lhs, remember what is a sum type (aef12c5) Message-ID: <20131215162352.B95092406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/aef12c56e468497c8c911a46c6b61c0d0c031107/ghc >--------------------------------------------------------------- commit aef12c56e468497c8c911a46c6b61c0d0c031107 Author: Joachim Breitner Date: Tue Dec 10 09:15:09 2013 +0000 in Demand.lhs, remember what is a sum type because we want to zap CPR information for sum types not only on the outermost level, but also nested. See Note [CPR for sum types] This comes up in sublist in Listplikefns in nofib?s boyer2. >--------------------------------------------------------------- aef12c56e468497c8c911a46c6b61c0d0c031107 compiler/basicTypes/DataCon.lhs | 4 +++ compiler/basicTypes/Demand.lhs | 76 ++++++++++++++++++++++++--------------- compiler/basicTypes/MkId.lhs | 2 +- compiler/stranal/DmdAnal.lhs | 39 ++++++++++++-------- 4 files changed, 77 insertions(+), 44 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 aef12c56e468497c8c911a46c6b61c0d0c031107 From git at git.haskell.org Sun Dec 15 16:23:55 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 15 Dec 2013 16:23:55 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Loop breakers are not allowed to have a Converges DmdResult (3777b8d) Message-ID: <20131215162355.3A2562406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/3777b8d0df200d96331d85ef165908df52225117/ghc >--------------------------------------------------------------- commit 3777b8d0df200d96331d85ef165908df52225117 Author: Joachim Breitner Date: Tue Nov 26 10:18:35 2013 +0000 Loop breakers are not allowed to have a Converges DmdResult >--------------------------------------------------------------- 3777b8d0df200d96331d85ef165908df52225117 compiler/basicTypes/Demand.lhs | 19 +++++++++++-------- compiler/stranal/DmdAnal.lhs | 5 ++++- 2 files changed, 15 insertions(+), 9 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index d129a9a..2fe9236 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -33,6 +33,7 @@ module Demand ( returnsCPR, returnsCPR_maybe, forgetCPR, StrictSig(..), mkStrictSig, mkClosedStrictSig, nopSig, botSig, cprProdSig, isNopSig, splitStrictSig, increaseStrictSigArity, + sigMayConverge, seqDemand, seqDemandList, seqDmdType, seqStrictSig, evalDmd, cleanEvalDmd, cleanEvalProdDmd, isStrictDmd, @@ -806,15 +807,10 @@ getDmdResult _ = topRes maxCPRDepth :: Int maxCPRDepth = 3 --- With nested CPR, DmdResult can be arbitrarily deep; consider --- data Rec1 = Foo Rec2 Rec2 --- data Rec2 = Bar Rec1 Rec1 --- --- x = Foo y y --- y = Bar x x --- +-- With nested CPR, DmdResult can be arbitrarily deep; consider e.g. the +-- DmdResult of repeat -- So we need to forget information at a certain depth. We do that at all points --- where we are constructing new RetCon constructors. +-- where we are building RetCon constructors. cutDmdResult :: Int -> DmdResult -> DmdResult cutDmdResult 0 _ = topRes cutDmdResult _ Diverges = Diverges @@ -825,6 +821,10 @@ cutCPRResult :: Int -> CPRResult -> CPRResult cutCPRResult _ NoCPR = NoCPR cutCPRResult n (RetCon tag rs) = RetCon tag (map (cutDmdResult (n-1)) rs) +-- Forget that something might converge for sure +divergeDmdResult :: DmdResult -> DmdResult +divergeDmdResult r = r `lubDmdResult` botRes + -- Forget the CPR information, but remember if it converges or diverges -- Used for non-strict thunks and non-top-level things with sum type forgetCPR :: DmdResult -> DmdResult @@ -1445,6 +1445,9 @@ botSig = StrictSig botDmdType cprProdSig :: Arity -> StrictSig cprProdSig arity = StrictSig (cprProdDmdType arity) +sigMayConverge :: StrictSig -> StrictSig +sigMayConverge (StrictSig (DmdType env ds res)) = (StrictSig (DmdType env ds (divergeDmdResult res))) + argsOneShots :: StrictSig -> Arity -> [[OneShotInfo]] argsOneShots (StrictSig (DmdType _ arg_ds _)) n_val_args = go arg_ds diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index ea1a588..d5bf8a0 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -1084,7 +1084,10 @@ updSigEnv env sigs = env { ae_sigs = sigs } extendAnalEnv :: TopLevelFlag -> AnalEnv -> Id -> StrictSig -> AnalEnv extendAnalEnv top_lvl env var sig - = env { ae_sigs = extendSigEnv top_lvl (ae_sigs env) var sig } + = env { ae_sigs = extendSigEnv top_lvl (ae_sigs env) var sig' } + where + sig' | isWeakLoopBreaker (idOccInfo var) = sigMayConverge sig + | otherwise = sig extendSigEnv :: TopLevelFlag -> SigEnv -> Id -> StrictSig -> SigEnv extendSigEnv top_lvl sigs var sig = extendVarEnv sigs var (sig, top_lvl) From git at git.haskell.org Sun Dec 15 16:23:57 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 15 Dec 2013 16:23:57 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Recover [CPR for sum types] (slightly differently) (f9d4d76) Message-ID: <20131215162357.819C62406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/f9d4d761dd01e83fd80a83460cf25b75c7c6f8ed/ghc >--------------------------------------------------------------- commit f9d4d761dd01e83fd80a83460cf25b75c7c6f8ed Author: Joachim Breitner Date: Thu Nov 28 11:17:16 2013 +0000 Recover [CPR for sum types] (slightly differently) >--------------------------------------------------------------- f9d4d761dd01e83fd80a83460cf25b75c7c6f8ed compiler/basicTypes/Demand.lhs | 24 ++++++++---------------- compiler/stranal/DmdAnal.lhs | 14 ++++++++------ 2 files changed, 16 insertions(+), 22 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index c193c18..d129a9a 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -30,10 +30,9 @@ module Demand ( isBotRes, isTopRes, getDmdResult, resTypeArgDmd, topRes, botRes, cprConRes, vanillaCprConRes, appIsBottom, isBottomingSig, pprIfaceStrictSig, - trimCPRInfo, returnsCPR, returnsCPR_maybe, + returnsCPR, returnsCPR_maybe, forgetCPR, StrictSig(..), mkStrictSig, mkClosedStrictSig, nopSig, botSig, cprProdSig, isNopSig, splitStrictSig, increaseStrictSigArity, - seqDemand, seqDemandList, seqDmdType, seqStrictSig, evalDmd, cleanEvalDmd, cleanEvalProdDmd, isStrictDmd, @@ -826,6 +825,13 @@ cutCPRResult :: Int -> CPRResult -> CPRResult cutCPRResult _ NoCPR = NoCPR cutCPRResult n (RetCon tag rs) = RetCon tag (map (cutDmdResult (n-1)) rs) +-- Forget the CPR information, but remember if it converges or diverges +-- Used for non-strict thunks and non-top-level things with sum type +forgetCPR :: DmdResult -> DmdResult +forgetCPR Diverges = Diverges +forgetCPR (Converges _) = Converges NoCPR +forgetCPR (Dunno _) = Dunno NoCPR + cprConRes :: ConTag -> [DmdResult] -> DmdResult cprConRes tag arg_ress | opt_CprOff = topRes @@ -844,20 +850,6 @@ isBotRes :: DmdResult -> Bool isBotRes Diverges = True isBotRes _ = False --- TODO: This currently ignores trim_sums. Evaluate if still required, and fix --- Note [CPR for sum types] -trimCPRInfo :: Bool -> Bool -> DmdResult -> DmdResult -trimCPRInfo trim_all _trim_sums res - = trimR res - where - trimR (Converges c) = Converges (trimC c) - trimR (Dunno c) = Dunno (trimC c) - trimR Diverges = Diverges - - trimC (RetCon n rs) | trim_all = NoCPR - | otherwise = RetCon n (map trimR rs) - trimC NoCPR = NoCPR - returnsCPR :: DmdResult -> Bool returnsCPR dr = isJust (returnsCPR_maybe dr) diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index 0da1085..ea1a588 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -655,9 +655,10 @@ dmdAnalRhs top_lvl rec_flag env id rhs -- See Note [NOINLINE and strictness] -- See Note [Product demands for function body] - body_dmd = case deepSplitProductType_maybe (exprType body) of - Nothing -> cleanEvalDmd - Just (dc, _, _, _) -> cleanEvalProdDmd (dataConRepArity dc) + (is_sum_type, body_dmd) + = case deepSplitProductType_maybe (exprType body) of + Nothing -> (True, cleanEvalDmd) + Just (dc, _, _, _) -> (False, cleanEvalProdDmd (dataConRepArity dc)) -- See Note [Lazy and unleashable free variables] -- See Note [Aggregated demand for cardinality] @@ -667,9 +668,10 @@ dmdAnalRhs top_lvl rec_flag env id rhs (lazy_fv, sig_fv) = splitFVs is_thunk rhs_fv1 - rhs_res' = trimCPRInfo trim_all trim_sums rhs_res - trim_all = is_thunk && not_strict - trim_sums = not (isTopLevel top_lvl) -- See Note [CPR for sum types] + -- Note [CPR for sum types] + rhs_res' | (is_sum_type && not (isTopLevel top_lvl)) || + (is_thunk && not_strict) = forgetCPR rhs_res + | otherwise = rhs_res -- See Note [CPR for thunks] is_thunk = not (exprIsHNF rhs) From git at git.haskell.org Sun Dec 15 16:23:59 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 15 Dec 2013 16:23:59 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Use isTypeArg instead of isTyCoArg (forgot why) (a92ab58) Message-ID: <20131215162359.BE92E2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/a92ab58bb330c8cc6ec24e9b96565ab38dd2ad92/ghc >--------------------------------------------------------------- commit a92ab58bb330c8cc6ec24e9b96565ab38dd2ad92 Author: Joachim Breitner Date: Thu Dec 5 16:14:07 2013 +0000 Use isTypeArg instead of isTyCoArg (forgot why) >--------------------------------------------------------------- a92ab58bb330c8cc6ec24e9b96565ab38dd2ad92 compiler/stranal/DmdAnal.lhs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index cb5aa4a..0da1085 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -509,7 +509,7 @@ completeApp :: AnalEnv completeApp _ fun_ty_fun [] = fun_ty_fun completeApp env (fun_ty, fun') (arg:args) - | isTyCoArg arg = completeApp env (fun_ty, App fun' arg) args + | isTypeArg arg = completeApp env (fun_ty, App fun' arg) args | otherwise = completeApp env (res_ty `bothDmdType` arg_ty, App fun' arg') args where (arg_dmd, res_ty) = splitDmdTy fun_ty From git at git.haskell.org Sun Dec 15 16:24:02 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 15 Dec 2013 16:24:02 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Allow the CPR w/w to take unboxed tuples apart (a87439e) Message-ID: <20131215162402.428752406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/a87439e026cdd30da1f90a4bdaaeb10634222831/ghc >--------------------------------------------------------------- commit a87439e026cdd30da1f90a4bdaaeb10634222831 Author: Joachim Breitner Date: Thu Nov 28 10:29:47 2013 +0000 Allow the CPR w/w to take unboxed tuples apart >--------------------------------------------------------------- a87439e026cdd30da1f90a4bdaaeb10634222831 compiler/stranal/WwLib.lhs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/stranal/WwLib.lhs b/compiler/stranal/WwLib.lhs index ce4112c..5168d8f 100644 --- a/compiler/stranal/WwLib.lhs +++ b/compiler/stranal/WwLib.lhs @@ -502,7 +502,7 @@ deepSplitCprType_maybe :: ConTag -> Type -> Maybe (DataCon, [Type], [Type], Coer deepSplitCprType_maybe con_tag ty | let (co, ty1) = topNormaliseNewType_maybe ty `orElse` (mkReflCo Representational ty, ty) , Just (tc, tc_args) <- splitTyConApp_maybe ty1 - , isDataTyCon tc + , isDataTyCon tc || isUnboxedTupleTyCon tc , let cons = tyConDataCons tc con = ASSERT( cons `lengthAtLeast` con_tag ) cons !! (con_tag - fIRST_TAG) = Just (con, tc_args, dataConInstArgTys con tc_args, co) From git at git.haskell.org Sun Dec 15 16:24:04 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 15 Dec 2013 16:24:04 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Temporarily disable nested CPR inside sum types (7fcc7b8) Message-ID: <20131215162404.9C0442406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/7fcc7b8080d408ec59ffd7e6b95e51fc0463d86a/ghc >--------------------------------------------------------------- commit 7fcc7b8080d408ec59ffd7e6b95e51fc0463d86a Author: Joachim Breitner Date: Tue Dec 10 10:12:46 2013 +0000 Temporarily disable nested CPR inside sum types >--------------------------------------------------------------- 7fcc7b8080d408ec59ffd7e6b95e51fc0463d86a compiler/basicTypes/Demand.lhs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 521c32b..2f03484 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -865,7 +865,7 @@ cprConRes isProd tag arg_ress | opt_NestedCprOff = Converges $ cutCPRResult flatCPRDepth $ retCon arg_ress | otherwise = Converges $ cutCPRResult maxCPRDepth $ retCon arg_ress where retCon | isProd = RetProd - | otherwise = RetSum tag + | otherwise = RetSum tag . map (const topRes) vanillaCprConRes :: Bool -> ConTag -> Arity -> DmdResult vanillaCprConRes isProd tag arity = cprConRes isProd tag (replicate arity topRes) From git at git.haskell.org Sun Dec 15 16:24:06 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 15 Dec 2013 16:24:06 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Actually create a nested CPR worker-wrapper (17581ef) Message-ID: <20131215162406.D2D392406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/17581efaa4b200b4a382d211db40153b65ca580f/ghc >--------------------------------------------------------------- commit 17581efaa4b200b4a382d211db40153b65ca580f Author: Joachim Breitner Date: Thu Dec 5 18:58:07 2013 +0000 Actually create a nested CPR worker-wrapper >--------------------------------------------------------------- 17581efaa4b200b4a382d211db40153b65ca580f compiler/basicTypes/Demand.lhs | 15 +++-- compiler/stranal/WwLib.lhs | 141 +++++++++++++++++++++++++--------------- 2 files changed, 95 insertions(+), 61 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 17581efaa4b200b4a382d211db40153b65ca580f From git at git.haskell.org Sun Dec 15 16:24:09 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 15 Dec 2013 16:24:09 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Add a warning to dmdTransformDataConSig (which I believe is dead code) (44842aa) Message-ID: <20131215162409.138502406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/44842aaad5419f9c6b2dd461a481f9991c16d6aa/ghc >--------------------------------------------------------------- commit 44842aaad5419f9c6b2dd461a481f9991c16d6aa Author: Joachim Breitner Date: Tue Dec 10 13:56:08 2013 +0000 Add a warning to dmdTransformDataConSig (which I believe is dead code) >--------------------------------------------------------------- 44842aaad5419f9c6b2dd461a481f9991c16d6aa compiler/basicTypes/Demand.lhs | 1 + 1 file changed, 1 insertion(+) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 2f03484..b0b9092 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -1519,6 +1519,7 @@ dmdTransformDataConSig arity (StrictSig (DmdType _ _ con_res)) (CD { sd = str, ud = abs }) | Just str_dmds <- go_str arity str , Just abs_dmds <- go_abs arity abs + , WARN( True, text "dmdTransformDataConSig indeed still in use" ) True = DmdType emptyDmdEnv (mkJointDmds str_dmds abs_dmds) con_res -- Must remember whether it's a product, hence con_res, not TopRes From git at git.haskell.org Sun Dec 15 16:24:11 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 15 Dec 2013 16:24:11 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Add a flag -fnested-cpr-off to conveniently test the effect of nested CPR (95b939b) Message-ID: <20131215162411.72B482406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/95b939bc005170a8ee7639831fd2c0a2f63dee97/ghc >--------------------------------------------------------------- commit 95b939bc005170a8ee7639831fd2c0a2f63dee97 Author: Joachim Breitner Date: Wed Dec 4 09:14:26 2013 +0000 Add a flag -fnested-cpr-off to conveniently test the effect of nested CPR >--------------------------------------------------------------- 95b939bc005170a8ee7639831fd2c0a2f63dee97 compiler/basicTypes/Demand.lhs | 29 ++++++++++++++++++++--------- compiler/main/StaticFlags.hs | 9 +++++++-- 2 files changed, 27 insertions(+), 11 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 2fe9236..b816841 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -807,19 +807,29 @@ getDmdResult _ = topRes maxCPRDepth :: Int maxCPRDepth = 3 +-- This is the depth we use with -fnested-cpr-off, in order +-- to get precisely the same behaviour as before introduction of nested cpr +-- -fnested-cpr-off can eventually be removed if nested cpr is deemd to be +-- a good thing always. +flatCPRDepth :: Int +flatCPRDepth = 1 + -- With nested CPR, DmdResult can be arbitrarily deep; consider e.g. the -- DmdResult of repeat +-- -- So we need to forget information at a certain depth. We do that at all points -- where we are building RetCon constructors. -cutDmdResult :: Int -> DmdResult -> DmdResult -cutDmdResult 0 _ = topRes -cutDmdResult _ Diverges = Diverges -cutDmdResult n (Converges c) = Converges (cutCPRResult n c) -cutDmdResult n (Dunno c) = Dunno (cutCPRResult n c) - cutCPRResult :: Int -> CPRResult -> CPRResult -cutCPRResult _ NoCPR = NoCPR +cutCPRResult 0 _ = NoCPR +cutCPRResult _ NoCPR = NoCPR cutCPRResult n (RetCon tag rs) = RetCon tag (map (cutDmdResult (n-1)) rs) + where + cutDmdResult :: Int -> DmdResult -> DmdResult + cutDmdResult 0 _ = topRes + cutDmdResult _ Diverges = Diverges + cutDmdResult n (Converges c) = Converges (cutCPRResult n c) + cutDmdResult n (Dunno c) = Dunno (cutCPRResult n c) + -- Forget that something might converge for sure divergeDmdResult :: DmdResult -> DmdResult @@ -834,8 +844,9 @@ forgetCPR (Dunno _) = Dunno NoCPR cprConRes :: ConTag -> [DmdResult] -> DmdResult cprConRes tag arg_ress - | opt_CprOff = topRes - | otherwise = Converges $ cutCPRResult maxCPRDepth $ RetCon tag arg_ress + | opt_CprOff = topRes + | opt_NestedCprOff = Converges $ cutCPRResult flatCPRDepth $ RetCon tag arg_ress + | otherwise = Converges $ cutCPRResult maxCPRDepth $ RetCon tag arg_ress vanillaCprConRes :: ConTag -> Arity -> DmdResult vanillaCprConRes tag arity diff --git a/compiler/main/StaticFlags.hs b/compiler/main/StaticFlags.hs index 01dc3b7..feb7235 100644 --- a/compiler/main/StaticFlags.hs +++ b/compiler/main/StaticFlags.hs @@ -27,6 +27,7 @@ module StaticFlags ( -- optimisation opts opt_NoStateHack, opt_CprOff, + opt_NestedCprOff, opt_NoOptCoercion, -- For the parser @@ -140,7 +141,8 @@ flagsStaticNames :: [String] flagsStaticNames = [ "fno-state-hack", "fno-opt-coercion", - "fcpr-off" + "fcpr-off", + "fnested-cpr-off" ] -- We specifically need to discard static flags for clients of the @@ -195,10 +197,13 @@ opt_NoDebugOutput = lookUp (fsLit "-dno-debug-output") opt_NoStateHack :: Bool opt_NoStateHack = lookUp (fsLit "-fno-state-hack") --- Switch off CPR analysis in the new demand analyser +-- Switch off CPR analysis in the demand analyser opt_CprOff :: Bool opt_CprOff = lookUp (fsLit "-fcpr-off") +opt_NestedCprOff :: Bool +opt_NestedCprOff = lookUp (fsLit "-fnested-cpr-off") + opt_NoOptCoercion :: Bool opt_NoOptCoercion = lookUp (fsLit "-fno-opt-coercion") From git at git.haskell.org Mon Dec 16 20:59:12 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Dec 2013 20:59:12 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Unify RetProd and RetSum to RetCon in CPRResult (4a3a7c7) Message-ID: <20131216205912.549242406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/4a3a7c7006dbf9aad2cd83550d9c450bad6275d3/ghc >--------------------------------------------------------------- commit 4a3a7c7006dbf9aad2cd83550d9c450bad6275d3 Author: Joachim Breitner Date: Thu Dec 5 16:13:41 2013 +0000 Unify RetProd and RetSum to RetCon in CPRResult >--------------------------------------------------------------- 4a3a7c7006dbf9aad2cd83550d9c450bad6275d3 compiler/basicTypes/Demand.lhs | 102 ++++++++++++++++++++++------------------ compiler/basicTypes/MkId.lhs | 4 +- compiler/stranal/DmdAnal.lhs | 4 +- 3 files changed, 59 insertions(+), 51 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 4a3a7c7006dbf9aad2cd83550d9c450bad6275d3 From git at git.haskell.org Mon Dec 16 20:59:14 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Dec 2013 20:59:14 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Rename postProcessDmdType to postProcessUnsat and use* to reuse* (779dca7) Message-ID: <20131216205914.9ADDF2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/779dca75eb383c057dc6a8b065727265f0ec1401/ghc >--------------------------------------------------------------- commit 779dca75eb383c057dc6a8b065727265f0ec1401 Author: Joachim Breitner Date: Thu Dec 12 16:12:00 2013 +0000 Rename postProcessDmdType to postProcessUnsat and use* to reuse* >--------------------------------------------------------------- 779dca75eb383c057dc6a8b065727265f0ec1401 compiler/basicTypes/Demand.lhs | 81 ++++++++++++++++++++++------------------ compiler/stranal/DmdAnal.lhs | 4 +- 2 files changed, 46 insertions(+), 39 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 3ca8466..cdb60af 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -38,13 +38,13 @@ module Demand ( evalDmd, cleanEvalDmd, cleanEvalProdDmd, isStrictDmd, splitDmdTy, splitFVs, deferAfterIO, - postProcessDmdType, postProcessDmdTypeM, + postProcessUnsat, postProcessDmdTypeM, splitProdDmd, splitProdDmd_maybe, peelCallDmd, mkCallDmd, dmdTransformSig, dmdTransformDataConSig, dmdTransformDictSelSig, argOneShots, argsOneShots, - isSingleUsed, useEnv, zapDemand, zapStrictSig, + isSingleUsed, reuseEnv, zapDemand, zapStrictSig, worthSplittingArgDmd, worthSplittingThunkDmd, @@ -400,23 +400,25 @@ Compare with: (C) making Used win for both, but UProd win for lub \begin{code} -markAsUsedDmd :: MaybeUsed -> MaybeUsed -markAsUsedDmd Abs = Abs -markAsUsedDmd (Use _ a) = Use Many (markUsed a) +-- If a demand is used multiple times (i.e. reused), than any use-once +-- mentioned there, that is not protected by a UCall, can happen many times. +markReusedDmd :: MaybeUsed -> MaybeUsed +markReusedDmd Abs = Abs +markReusedDmd (Use _ a) = Use Many (markReused a) -markUsed :: UseDmd -> UseDmd -markUsed (UCall _ u) = UCall Many u -- No need to recurse here -markUsed (UProd ux) = UProd (map markAsUsedDmd ux) -markUsed u = u +markReused :: UseDmd -> UseDmd +markReused (UCall _ u) = UCall Many u -- No need to recurse here +markReused (UProd ux) = UProd (map markReusedDmd ux) +markReused u = u isUsedMU :: MaybeUsed -> Bool --- True <=> markAsUsedDmd d = d +-- True <=> markReusedDmd d = d isUsedMU Abs = True isUsedMU (Use One _) = False isUsedMU (Use Many u) = isUsedU u isUsedU :: UseDmd -> Bool --- True <=> markUsed d = d +-- True <=> markReused d = d isUsedU Used = True isUsedU UHead = True isUsedU (UProd us) = all isUsedMU us @@ -1121,34 +1123,39 @@ toCleanDmd (JD { strd = s, absd = u }) (Lazy, Use c u') -> (CD { sd = HeadStr, ud = u' }, Just (True, c)) (_, Abs) -> (CD { sd = HeadStr, ud = Used }, Nothing) +-- This is used in dmdAnalStar when post-processing +-- a function's argument demand. So we only care about what +-- does to free variables, and whether it terminates. postProcessDmdTypeM :: DeferAndUseM -> DmdType -> DmdType postProcessDmdTypeM Nothing _ = nopDmdType -- Incoming demand was Absent, so just discard all usage information -- We only processed the thing at all to analyse the body -- See Note [Always analyse in virgin pass] -postProcessDmdTypeM (Just du) ty = postProcessDmdType du ty - -postProcessDmdType :: DeferAndUse -> DmdType -> DmdType -postProcessDmdType (True, Many) ty = deferAndUse ty -postProcessDmdType (False, Many) ty = useType ty -postProcessDmdType (True, One) ty = deferType ty -postProcessDmdType (False, One) ty = ty - -deferType, useType, deferAndUse :: DmdType -> DmdType -deferType (DmdType fv ds _) = DmdType (deferEnv fv) (map deferDmd ds) topRes -useType (DmdType fv ds res_ty) = DmdType (useEnv fv) (map useDmd ds) res_ty -deferAndUse (DmdType fv ds _) = DmdType (deferUseEnv fv) (map deferUseDmd ds) topRes - -deferEnv, useEnv, deferUseEnv :: DmdEnv -> DmdEnv -deferEnv fv = mapVarEnv deferDmd fv -useEnv fv = mapVarEnv useDmd fv -deferUseEnv fv = mapVarEnv deferUseDmd fv - -deferDmd, useDmd, deferUseDmd :: JointDmd -> JointDmd -deferDmd (JD {strd=_, absd=a}) = mkJointDmd Lazy a -useDmd (JD {strd=d, absd=a}) = mkJointDmd d (markAsUsedDmd a) -deferUseDmd (JD {strd=_, absd=a}) = mkJointDmd Lazy (markAsUsedDmd a) - +postProcessDmdTypeM (Just du) ty = postProcessUnsat du ty + +postProcessUnsat :: DeferAndUse -> DmdType -> DmdType +postProcessUnsat (True, Many) ty = deferReuse ty +postProcessUnsat (False, Many) ty = reuseType ty +postProcessUnsat (True, One) ty = deferType ty +postProcessUnsat (False, One) ty = ty + +deferType, reuseType, deferReuse :: DmdType -> DmdType +deferType (DmdType fv ds _) = DmdType (deferEnv fv) (map deferDmd ds) topRes +reuseType (DmdType fv ds res_ty) = DmdType (reuseEnv fv) (map reuseDmd ds) res_ty +deferReuse (DmdType fv ds _) = DmdType (deferReuseEnv fv) (map deferReuseDmd ds) topRes + +deferEnv, reuseEnv, deferReuseEnv :: DmdEnv -> DmdEnv +deferEnv fv = mapVarEnv deferDmd fv +reuseEnv fv = mapVarEnv reuseDmd fv +deferReuseEnv fv = mapVarEnv deferReuseDmd fv + +deferDmd, reuseDmd, deferReuseDmd :: JointDmd -> JointDmd +deferDmd (JD {strd=_, absd=a}) = mkJointDmd Lazy a +reuseDmd (JD {strd=d, absd=a}) = mkJointDmd d (markReusedDmd a) +deferReuseDmd (JD {strd=_, absd=a}) = mkJointDmd Lazy (markReusedDmd a) + +-- Peels one call level from the demand, and also returns +-- whether it was unsaturated (separately for strictness and usage) peelCallDmd :: CleanDemand -> (CleanDemand, DeferAndUse) -- Exploiting the fact that -- on the strictness side C(B) = B @@ -1352,8 +1359,8 @@ dmdTransformSig :: StrictSig -> CleanDemand -> DmdType -- signature is fun_sig, with demand dmd. We return the demand -- that the function places on its context (eg its args) dmdTransformSig (StrictSig dmd_ty@(DmdType _ arg_ds _)) cd - = postProcessDmdType (peelManyCalls arg_ds cd) dmd_ty - -- NB: it's important to use postProcessDmdType, and not + = postProcessUnsat (peelManyCalls arg_ds cd) dmd_ty + -- NB: it's important to use postProcessUnsat, and not -- just return nopDmdType for unsaturated calls -- Consider let { f x y = p + x } in f 1 -- The application isn't saturated, but we must nevertheless propagate @@ -1391,7 +1398,7 @@ dmdTransformDictSelSig :: StrictSig -> CleanDemand -> DmdType dmdTransformDictSelSig (StrictSig (DmdType _ [dict_dmd] _)) cd | (cd',defer_use) <- peelCallDmd cd , Just jds <- splitProdDmd_maybe dict_dmd - = postProcessDmdType defer_use $ + = postProcessUnsat defer_use $ DmdType emptyDmdEnv [mkOnceUsedDmd $ mkProdDmd $ map (enhance cd') jds] topRes | otherwise = nopDmdType -- See Note [Demand transformer for a dictionary selector] diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index 01c990a..cbdcc67 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -206,7 +206,7 @@ dmdAnal env dmd (Lam var body) (body_ty, body') = dmdAnal env' body_dmd body (lam_ty, var') = annotateLamIdBndr env notArgOfDfun body_ty one_shot var in - (postProcessDmdType defer_and_use lam_ty, Lam var' body') + (postProcessUnsat defer_and_use lam_ty, Lam var' body') dmdAnal env dmd (Case scrut case_bndr ty [alt@(DataAlt dc, _, _)]) -- Only one alternative with a product constructor @@ -619,7 +619,7 @@ dmdAnalRhs top_lvl rec_flag env id rhs -- See Note [Lazy and unleashable free variables] -- See Note [Aggregated demand for cardinality] rhs_fv1 = case rec_flag of - Just bs -> useEnv (delVarEnvList rhs_fv bs) + Just bs -> reuseEnv (delVarEnvList rhs_fv bs) Nothing -> rhs_fv (lazy_fv, sig_fv) = splitFVs is_thunk rhs_fv1 From git at git.haskell.org Mon Dec 16 20:59:17 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Dec 2013 20:59:17 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Disentangle postProcessDmdTypeM and postProcessUnsat (919ae13) Message-ID: <20131216205917.24DEB2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/919ae137eaf79d938d6321bc83bc5ca950c6df0c/ghc >--------------------------------------------------------------- commit 919ae137eaf79d938d6321bc83bc5ca950c6df0c Author: Joachim Breitner Date: Mon Dec 9 18:40:09 2013 +0000 Disentangle postProcessDmdTypeM and postProcessUnsat Make different postProcess code paths for function arguments (which are post-processed just to be both'ed) and unsaturated functions (which are post-processed for other reasons.) >--------------------------------------------------------------- 919ae137eaf79d938d6321bc83bc5ca950c6df0c compiler/basicTypes/Demand.lhs | 14 +++++++++++++- 1 file changed, 13 insertions(+), 1 deletion(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index bb88e40..09b6f60 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -1131,7 +1131,19 @@ postProcessDmdTypeM Nothing _ = nopDmdType -- Incoming demand was Absent, so just discard all usage information -- We only processed the thing at all to analyse the body -- See Note [Always analyse in virgin pass] -postProcessDmdTypeM (Just du) ty = postProcessUnsat du ty +postProcessDmdTypeM (Just du) (DmdType fv _ res_ty) + = DmdType (postProcessDmdEnv du fv) [] (postProcessDmdResult du res_ty) + +postProcessDmdResult :: DeferAndUse -> DmdResult -> DmdResult +postProcessDmdResult (True,_) r = topRes +postProcessDmdResult (False,_) r = r + +postProcessDmdEnv :: DeferAndUse -> DmdEnv -> DmdEnv +postProcessDmdEnv (True, Many) env = deferReuseEnv env +postProcessDmdEnv (False, Many) env = reuseEnv env +postProcessDmdEnv (True, One) env = deferEnv env +postProcessDmdEnv (False, One) env = env + postProcessUnsat :: DeferAndUse -> DmdType -> DmdType postProcessUnsat (True, Many) ty = deferReuse ty From git at git.haskell.org Mon Dec 16 20:59:19 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Dec 2013 20:59:19 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Clarify the default demand on demand environments (fbe14a8) Message-ID: <20131216205919.763342406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/fbe14a8e8861403c207dddd6c496096924293bef/ghc >--------------------------------------------------------------- commit fbe14a8e8861403c207dddd6c496096924293bef Author: Joachim Breitner Date: Wed Dec 4 17:59:09 2013 +0000 Clarify the default demand on demand environments by adding Notes and using easier to understand combinators. >--------------------------------------------------------------- fbe14a8e8861403c207dddd6c496096924293bef compiler/basicTypes/Demand.lhs | 83 ++++++++++++++++++---------------------- compiler/basicTypes/VarEnv.lhs | 4 +- compiler/stranal/DmdAnal.lhs | 10 ----- compiler/utils/UniqFM.lhs | 28 ++++++++++++++ 4 files changed, 69 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 fbe14a8e8861403c207dddd6c496096924293bef From git at git.haskell.org Mon Dec 16 20:59:21 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Dec 2013 20:59:21 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Use isTypeArg instead of isTyCoArg (forgot why) (d7caef1) Message-ID: <20131216205921.B11832406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/d7caef11e80818938e20c471010acf785c496703/ghc >--------------------------------------------------------------- commit d7caef11e80818938e20c471010acf785c496703 Author: Joachim Breitner Date: Thu Dec 5 16:14:07 2013 +0000 Use isTypeArg instead of isTyCoArg (forgot why) >--------------------------------------------------------------- d7caef11e80818938e20c471010acf785c496703 compiler/stranal/DmdAnal.lhs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index cb5aa4a..0da1085 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -509,7 +509,7 @@ completeApp :: AnalEnv completeApp _ fun_ty_fun [] = fun_ty_fun completeApp env (fun_ty, fun') (arg:args) - | isTyCoArg arg = completeApp env (fun_ty, App fun' arg) args + | isTypeArg arg = completeApp env (fun_ty, App fun' arg) args | otherwise = completeApp env (res_ty `bothDmdType` arg_ty, App fun' arg') args where (arg_dmd, res_ty) = splitDmdTy fun_ty From git at git.haskell.org Mon Dec 16 20:59:23 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Dec 2013 20:59:23 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Add Converges to DmdResult (0d4246a) Message-ID: <20131216205923.E69492406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/0d4246a1a16a9b374a4a012a1ed98061e399a9a4/ghc >--------------------------------------------------------------- commit 0d4246a1a16a9b374a4a012a1ed98061e399a9a4 Author: Joachim Breitner Date: Thu Dec 12 15:45:19 2013 +0000 Add Converges to DmdResult to detect definite convergence (required for nested CPR). >--------------------------------------------------------------- 0d4246a1a16a9b374a4a012a1ed98061e399a9a4 compiler/basicTypes/Demand.lhs | 41 ++++++++++++++++++++++++++++------------ 1 file changed, 29 insertions(+), 12 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 2b69b4d..fc6a81a 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -691,8 +691,8 @@ splitProdDmd_maybe (JD {strd = s, absd = u}) DmdResult: Dunno CPRResult - / - Diverges + / \ + Diverges Converges CPRResult CPRResult: NoCPR @@ -700,7 +700,7 @@ CPRResult: NoCPR RetProd RetSum ConTag -Product contructors return (Dunno (RetProd rs)) +Product contructors return (Converges (RetProd rs)) In a fixpoint iteration, start from Diverges We have lubs, but not glbs; but that is ok. @@ -711,6 +711,7 @@ We have lubs, but not glbs; but that is ok. ------------------------------------------------------------------------ data Termination r = Diverges -- Definitely diverges + | Converges r -- Definitely converges | Dunno r -- Might diverge or converge deriving( Eq, Show ) @@ -729,7 +730,11 @@ lubCPR _ _ = NoCPR lubDmdResult :: DmdResult -> DmdResult -> DmdResult lubDmdResult Diverges r = r +lubDmdResult (Converges c1) Diverges = Converges c1 +lubDmdResult (Converges c1) (Converges c2) = Converges (c1 `lubCPR` c2) +lubDmdResult (Converges c1) (Dunno c2) = Dunno (c1 `lubCPR` c2) lubDmdResult (Dunno c1) Diverges = Dunno c1 +lubDmdResult (Dunno c1) (Converges c2) = Dunno (c1 `lubCPR` c2) lubDmdResult (Dunno c1) (Dunno c2) = Dunno (c1 `lubCPR` c2) -- This needs to commute with defaultDmd, i.e. -- defaultDmd (r1 `lubDmdResult` r2) = defaultDmd r1 `lubDmd` defaultDmd r2 @@ -738,6 +743,7 @@ lubDmdResult (Dunno c1) (Dunno c2) = Dunno (c1 `lubCPR` c2) bothDmdResult :: DmdResult -> Termination () -> DmdResult -- See Note [Asymmetry of 'both' for DmdType and DmdResult] bothDmdResult _ Diverges = Diverges +bothDmdResult (Converges c1) (Dunno {}) = Dunno c1 bothDmdResult r _ = r -- This needs to commute with defaultDmd, i.e. -- defaultDmd (r1 `bothDmdResult` r2) = defaultDmd r1 `bothDmd` defaultDmd r2 @@ -745,6 +751,7 @@ bothDmdResult r _ = r instance Outputable DmdResult where ppr Diverges = char 'b' + ppr (Converges c) = char 't' <> ppr c ppr (Dunno c) = ppr c instance Outputable CPRResult where @@ -754,6 +761,7 @@ instance Outputable CPRResult where seqDmdResult :: DmdResult -> () seqDmdResult Diverges = () +seqDmdResult (Converges c) = seqCPRResult c seqDmdResult (Dunno c) = seqCPRResult c seqCPRResult :: CPRResult -> () @@ -774,17 +782,17 @@ botRes = Diverges cprSumRes :: ConTag -> DmdResult cprSumRes tag | opt_CprOff = topRes - | otherwise = Dunno $ RetSum tag + | otherwise = Converges $ RetSum tag cprProdRes :: [DmdType] -> DmdResult cprProdRes _arg_tys | opt_CprOff = topRes - | otherwise = Dunno $ RetProd + | otherwise = Converges $ RetProd vanillaCprProdRes :: Arity -> DmdResult vanillaCprProdRes _arity | opt_CprOff = topRes - | otherwise = Dunno $ RetProd + | otherwise = Converges $ RetProd isTopRes :: DmdResult -> Bool isTopRes (Dunno NoCPR) = True @@ -798,6 +806,7 @@ trimCPRInfo :: Bool -> Bool -> DmdResult -> DmdResult trimCPRInfo trim_all trim_sums res = trimR res where + trimR (Converges c) = Converges (trimC c) trimR (Dunno c) = Dunno (trimC c) trimR Diverges = Diverges @@ -811,6 +820,7 @@ returnsCPR :: DmdResult -> Bool returnsCPR dr = isJust (returnsCPR_maybe dr) returnsCPR_maybe :: DmdResult -> Maybe ConTag +returnsCPR_maybe (Converges c) = retCPR_maybe c returnsCPR_maybe (Dunno c) = retCPR_maybe c returnsCPR_maybe Diverges = Nothing @@ -1036,6 +1046,7 @@ toBothDmdArg :: DmdType -> BothDmdArg toBothDmdArg (DmdType fv _ r) = (fv, go r) where go (Dunno {}) = Dunno () + go (Converges {}) = Converges () go Diverges = Diverges bothDmdType :: DmdType -> BothDmdArg -> DmdType @@ -1069,7 +1080,7 @@ botDmdType = DmdType emptyDmdEnv [] botRes cprProdDmdType :: Arity -> DmdType cprProdDmdType _arity - = DmdType emptyDmdEnv [] (Dunno RetProd) + = DmdType emptyDmdEnv [] (Converges RetProd) isNopDmdType :: DmdType -> Bool isNopDmdType (DmdType env [] res) @@ -1098,7 +1109,7 @@ splitDmdTy ty@(DmdType _ [] res_ty) = (resTypeArgDmd res_ty, ty) -- exit? -- * We have to kill all strictness demands (i.e. lub with a lazy demand) -- * We can keep demand information (i.e. lub with an absent deman) --- * We have to kill definite divergence +-- * We have to kill definite divergence and definite convergence -- * We can keep CPR information. -- See Note [IO hack in the demand analyser] deferAfterIO :: DmdType -> DmdType @@ -1107,6 +1118,7 @@ deferAfterIO d@(DmdType _ _ res) = DmdType fv ds _ -> DmdType fv ds (defer_res res) where defer_res Diverges = topRes + defer_res (Converges r) = Dunno r defer_res r = r strictenDmd :: JointDmd -> CleanDemand @@ -1149,9 +1161,12 @@ postProcessDmdTypeM (Just du) (DmdType fv _ res_ty) = (postProcessDmdEnv du fv, postProcessDmdResult du res_ty) postProcessDmdResult :: DeferAndUse -> DmdResult -> Termination () -postProcessDmdResult (True,_) _ = Dunno () -postProcessDmdResult (False,_) (Dunno {}) = Dunno () -postProcessDmdResult (False,_) Diverges = Diverges + -- if we use it lazily, there cannot be divergence worrying us + -- (Otherwise we'd lose the termination information of constructors in in dmdAnalVarApp, for example) +postProcessDmdResult (True,_) _ = Converges () +postProcessDmdResult (False,_) (Dunno {}) = Dunno () +postProcessDmdResult (False,_) (Converges {}) = Converges () +postProcessDmdResult (False,_) Diverges = Diverges postProcessDmdEnv :: DeferAndUse -> DmdEnv -> DmdEnv postProcessDmdEnv (True, Many) env = deferReuseEnv env @@ -1720,11 +1735,13 @@ instance Binary DmdType where instance Binary DmdResult where put_ bh (Dunno c) = do { putByte bh 0; put_ bh c } - put_ bh Diverges = putByte bh 2 + put_ bh (Converges c) = do { putByte bh 1; put_ bh c } + put_ bh Diverges = putByte bh 3 get bh = do { h <- getByte bh ; case h of 0 -> do { c <- get bh; return (Dunno c) } + 1 -> do { c <- get bh; return (Converges c) } _ -> return Diverges } instance Binary CPRResult where From git at git.haskell.org Mon Dec 16 20:59:26 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Dec 2013 20:59:26 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Add Note [non-algebraic or open body type warning] (b1561d1) Message-ID: <20131216205926.2D6EE2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/b1561d1250f0006ba5a4f0f6e265cb7081451f3e/ghc >--------------------------------------------------------------- commit b1561d1250f0006ba5a4f0f6e265cb7081451f3e Author: Joachim Breitner Date: Wed Dec 4 17:12:07 2013 +0000 Add Note [non-algebraic or open body type warning] >--------------------------------------------------------------- b1561d1250f0006ba5a4f0f6e265cb7081451f3e compiler/stranal/WwLib.lhs | 20 ++++++++++++++++++++ 1 file changed, 20 insertions(+) diff --git a/compiler/stranal/WwLib.lhs b/compiler/stranal/WwLib.lhs index fc94c9b..4acf255 100644 --- a/compiler/stranal/WwLib.lhs +++ b/compiler/stranal/WwLib.lhs @@ -540,6 +540,7 @@ mkWWcpr body_ty res Just con_tag | Just stuff <- deepSplitCprType_maybe con_tag body_ty -> mkWWcpr_help stuff | otherwise + -- See Note [non-algebraic or open body type warning] -> WARN( True, text "mkWWcpr: non-algebraic or open body type" <+> ppr body_ty ) return (id, id, body_ty) @@ -590,6 +591,25 @@ mkUnpackCase scrut co uniq boxing_con unpk_args body bndr = mk_ww_local uniq (exprType casted_scrut) \end{code} +Note [non-algebraic or open body type warning] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + +There are a few cases where the W/W transformation is told that something +returns a constructor, but the type at hand doesn't really match this. One +real-world example involves unsafeCoerce: + foo = IO a + foo = unsafeCoere c_exit + foreign import ccall "c_exit" c_exit :: IO () +Here CPR will tell you that `foo` returns a () constructor for sure, but trying +to create a worker/wrapper for type `a` obviously fails. +(This was a real example until ee8e792 in libraries/base.) + +It does not seem feasilbe to avoid all such cases already in the analyser (and +after all, the analysis is not really wrong), so we simply do nothing here in +mkWWcpr. But we still want to emit warning with -DDEBUG, to hopefully catch +other cases where something went avoidably wrong. + + Note [Profiling and unpacking] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ If the original function looked like From git at git.haskell.org Mon Dec 16 20:59:28 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Dec 2013 20:59:28 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: In deferType, return convRes = Converges NoCPR (be1a52b) Message-ID: <20131216205929.38E512406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/be1a52ba67db67c671ab9ba963f2338b02e7c67e/ghc >--------------------------------------------------------------- commit be1a52ba67db67c671ab9ba963f2338b02e7c67e Author: Joachim Breitner Date: Wed Dec 4 16:55:18 2013 +0000 In deferType, return convRes = Converges NoCPR because this is the right-identity to `bothDmdResult`, and this is the right thing to do in a lazy context. >--------------------------------------------------------------- be1a52ba67db67c671ab9ba963f2338b02e7c67e compiler/basicTypes/Demand.lhs | 7 ++++--- 1 file changed, 4 insertions(+), 3 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index fc6a81a..717f5ed 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -776,8 +776,9 @@ seqCPRResult RetProd = () -- [cprRes] lets us switch off CPR analysis -- by making sure that everything uses TopRes -topRes, botRes :: DmdResult +topRes, convRes, botRes :: DmdResult topRes = Dunno NoCPR +convRes = Converges NoCPR botRes = Diverges cprSumRes :: ConTag -> DmdResult @@ -1182,9 +1183,9 @@ postProcessUnsat (True, One) ty = deferType ty postProcessUnsat (False, One) ty = ty deferType, reuseType, deferReuse :: DmdType -> DmdType -deferType (DmdType fv ds _) = DmdType (deferEnv fv) (map deferDmd ds) topRes +deferType (DmdType fv ds _) = DmdType (deferEnv fv) (map deferDmd ds) convRes reuseType (DmdType fv ds res_ty) = DmdType (reuseEnv fv) (map reuseDmd ds) res_ty -deferReuse (DmdType fv ds _) = DmdType (deferReuseEnv fv) (map deferReuseDmd ds) topRes +deferReuse (DmdType fv ds _) = DmdType (deferReuseEnv fv) (map deferReuseDmd ds) convRes deferEnv, reuseEnv, deferReuseEnv :: DmdEnv -> DmdEnv deferEnv fv = mapVarEnv deferDmd fv From git at git.haskell.org Mon Dec 16 20:59:30 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Dec 2013 20:59:30 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Make types of bothDmdType more precise (5e5cbb4) Message-ID: <20131216205930.AFA242406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/5e5cbb4e2961ace7d4a7c8d47022c01727bcd725/ghc >--------------------------------------------------------------- commit 5e5cbb4e2961ace7d4a7c8d47022c01727bcd725 Author: Joachim Breitner Date: Mon Dec 9 18:40:09 2013 +0000 Make types of bothDmdType more precise by only passing the demand on the free variables, and whether the argument (resp. scrunitee) may or will diverge. >--------------------------------------------------------------- 5e5cbb4e2961ace7d4a7c8d47022c01727bcd725 compiler/basicTypes/Demand.lhs | 55 +++++++++++++++++++++++++--------------- compiler/stranal/DmdAnal.lhs | 9 +++---- 2 files changed, 39 insertions(+), 25 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 09b6f60..2b69b4d 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -21,6 +21,7 @@ module Demand ( DmdType(..), dmdTypeDepth, lubDmdType, bothDmdType, nopDmdType, botDmdType, mkDmdType, addDemand, + BothDmdArg, mkBothDmdArg, toBothDmdArg, DmdEnv, emptyDmdEnv, peelFV, @@ -709,14 +710,15 @@ We have lubs, but not glbs; but that is ok. -- Constructed Product Result ------------------------------------------------------------------------ -data CPRResult = NoCPR -- Top of the lattice - | RetProd -- Returns a constructor from a product type - | RetSum ConTag -- Returns a constructor from a sum type with this tag +data Termination r = Diverges -- Definitely diverges + | Dunno r -- Might diverge or converge deriving( Eq, Show ) -data DmdResult = Diverges -- Definitely diverges - | Dunno CPRResult -- Might diverge or converge, but in the latter case the - -- result shape is described by CPRResult +type DmdResult = Termination CPRResult + +data CPRResult = NoCPR -- Top of the lattice + | RetProd -- Returns a constructor from a product type + | RetSum ConTag -- Returns a constructor from a data type deriving( Eq, Show ) lubCPR :: CPRResult -> CPRResult -> CPRResult @@ -733,7 +735,7 @@ lubDmdResult (Dunno c1) (Dunno c2) = Dunno (c1 `lubCPR` c2) -- defaultDmd (r1 `lubDmdResult` r2) = defaultDmd r1 `lubDmd` defaultDmd r2 -- (See Note [Default demand on free variables] for why) -bothDmdResult :: DmdResult -> DmdResult -> DmdResult +bothDmdResult :: DmdResult -> Termination () -> DmdResult -- See Note [Asymmetry of 'both' for DmdType and DmdResult] bothDmdResult _ Diverges = Diverges bothDmdResult r _ = r @@ -1024,13 +1026,25 @@ lubDmdType (DmdType fv1 ds1 r1) (DmdType fv2 ds2 r2) lub_ds ds1 [] = map (`lubDmd` resTypeArgDmd r2) ds1 lub_ds [] ds2 = map (resTypeArgDmd r1 `lubDmd`) ds2 -bothDmdType :: DmdType -> DmdType -> DmdType -bothDmdType (DmdType fv1 ds1 r1) (DmdType fv2 _ r2) + +type BothDmdArg = (DmdEnv, Termination ()) + +mkBothDmdArg :: DmdEnv -> BothDmdArg +mkBothDmdArg env = (env, Dunno ()) + +toBothDmdArg :: DmdType -> BothDmdArg +toBothDmdArg (DmdType fv _ r) = (fv, go r) + where + go (Dunno {}) = Dunno () + go Diverges = Diverges + +bothDmdType :: DmdType -> BothDmdArg -> DmdType +bothDmdType (DmdType fv1 ds1 r1) (fv2, t2) -- See Note [Asymmetry of 'both' for DmdType and DmdResult] -- 'both' takes the argument/result info from its *first* arg, -- using its second arg just for its free-var info. - = DmdType both_fv ds1 (r1 `bothDmdResult` r2) - where both_fv = plusVarEnv_CD bothDmd fv1 (defaultDmd r1) fv2 (defaultDmd r2) + = DmdType both_fv ds1 (r1 `bothDmdResult` t2) + where both_fv = plusVarEnv_CD bothDmd fv1 (defaultDmd r1) fv2 (defaultDmd t2) instance Outputable DmdType where ppr (DmdType fv ds res) @@ -1126,17 +1140,18 @@ toCleanDmd (JD { strd = s, absd = u }) -- This is used in dmdAnalStar when post-processing -- a function's argument demand. So we only care about what -- does to free variables, and whether it terminates. -postProcessDmdTypeM :: DeferAndUseM -> DmdType -> DmdType -postProcessDmdTypeM Nothing _ = nopDmdType +postProcessDmdTypeM :: DeferAndUseM -> DmdType -> BothDmdArg +postProcessDmdTypeM Nothing _ = (emptyDmdEnv, Dunno ()) -- Incoming demand was Absent, so just discard all usage information -- We only processed the thing at all to analyse the body -- See Note [Always analyse in virgin pass] postProcessDmdTypeM (Just du) (DmdType fv _ res_ty) - = DmdType (postProcessDmdEnv du fv) [] (postProcessDmdResult du res_ty) + = (postProcessDmdEnv du fv, postProcessDmdResult du res_ty) -postProcessDmdResult :: DeferAndUse -> DmdResult -> DmdResult -postProcessDmdResult (True,_) r = topRes -postProcessDmdResult (False,_) r = r +postProcessDmdResult :: DeferAndUse -> DmdResult -> Termination () +postProcessDmdResult (True,_) _ = Dunno () +postProcessDmdResult (False,_) (Dunno {}) = Dunno () +postProcessDmdResult (False,_) Diverges = Diverges postProcessDmdEnv :: DeferAndUse -> DmdEnv -> DmdEnv postProcessDmdEnv (True, Many) env = deferReuseEnv env @@ -1246,9 +1261,9 @@ peelFV (DmdType fv ds res) id = -- pprTrace "rfv" (ppr id <+> ppr dmd $$ ppr fv) -- See note [Default demand on free variables] dmd = lookupVarEnv fv id `orElse` defaultDmd res -defaultDmd :: DmdResult -> Demand -defaultDmd res | isBotRes res = botDmd - | otherwise = absDmd +defaultDmd :: Termination r -> Demand +defaultDmd Diverges = botDmd +defaultDmd _ = absDmd addDemand :: Demand -> DmdType -> DmdType addDemand dmd (DmdType fv ds res) = DmdType fv (dmd:ds) res diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index cbdcc67..a942c4e 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -115,7 +115,7 @@ dmdTransformThunkDmd e -- See |-* relation in the companion paper dmdAnalStar :: AnalEnv -> Demand -- This one takes a *Demand* - -> CoreExpr -> (DmdType, CoreExpr) + -> CoreExpr -> (BothDmdArg, CoreExpr) dmdAnalStar env dmd e | (cd, defer_and_use) <- toCleanDmd dmd , (dmd_ty, e') <- dmdAnal env cd e @@ -255,7 +255,7 @@ dmdAnal env dmd (Case scrut case_bndr ty [alt@(DataAlt dc, _, _)]) scrut_dmd = scrut_dmd1 `bothCleanDmd` scrut_dmd2 (scrut_ty, scrut') = dmdAnal env scrut_dmd scrut - res_ty = alt_ty1 `bothDmdType` scrut_ty + res_ty = alt_ty1 `bothDmdType` toBothDmdArg scrut_ty in -- pprTrace "dmdAnal:Case1" (vcat [ text "scrut" <+> ppr scrut -- , text "dmd" <+> ppr dmd @@ -271,7 +271,7 @@ dmdAnal env dmd (Case scrut case_bndr ty alts) (alt_tys, alts') = mapAndUnzip (dmdAnalAlt env dmd) alts (scrut_ty, scrut') = dmdAnal env cleanEvalDmd scrut (alt_ty, case_bndr') = annotateBndr env (foldr lubDmdType botDmdType alt_tys) case_bndr - res_ty = alt_ty `bothDmdType` scrut_ty + res_ty = alt_ty `bothDmdType` toBothDmdArg scrut_ty in -- pprTrace "dmdAnal:Case2" (vcat [ text "scrut" <+> ppr scrut -- , text "scrut_ty" <+> ppr scrut_ty @@ -509,7 +509,6 @@ dmdTransform env var dmd | otherwise -- Local non-letrec-bound thing = unitVarDmd var (mkOnceUsedDmd dmd) - \end{code} %************************************************************************ @@ -698,7 +697,7 @@ addVarDmd (DmdType fv ds res) var dmd addLazyFVs :: DmdType -> DmdEnv -> DmdType addLazyFVs dmd_ty lazy_fvs - = dmd_ty `bothDmdType` mkDmdType lazy_fvs [] topRes + = dmd_ty `bothDmdType` mkBothDmdArg lazy_fvs -- Using bothDmdType (rather than just both'ing the envs) -- is vital. Consider -- let f = \x -> (x,y) From git at git.haskell.org Mon Dec 16 20:59:32 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Dec 2013 20:59:32 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Remove dmdAnalArg and replace by easier to understand code (59d4a8e) Message-ID: <20131216205932.D4F602406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/59d4a8eb5fa34bdad8f4fa48f4679cf85a8e4b0d/ghc >--------------------------------------------------------------- commit 59d4a8eb5fa34bdad8f4fa48f4679cf85a8e4b0d Author: Joachim Breitner Date: Wed Dec 4 17:38:25 2013 +0000 Remove dmdAnalArg and replace by easier to understand code >--------------------------------------------------------------- 59d4a8eb5fa34bdad8f4fa48f4679cf85a8e4b0d compiler/stranal/DmdAnal.lhs | 16 ++++++++-------- 1 file changed, 8 insertions(+), 8 deletions(-) diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index 3b805d9..a377bf5 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -103,13 +103,12 @@ c) The application rule wouldn't be right either evaluation of f in a C(L) demand! \begin{code} -dmdAnalArg :: AnalEnv - -> Demand -- This one takes a *Demand* - -> CoreExpr -> (DmdType, CoreExpr) --- Used for function arguments -dmdAnalArg env dmd e - | exprIsTrivial e = dmdAnalStar env dmd e - | otherwise = dmdAnalStar env (oneifyDmd dmd) e +-- If e is complicated enough to become a thunk, its contents will be evaluated +-- at most once, so oneify it. +dmdTransformThunkDmd :: CoreExpr -> Demand -> Demand +dmdTransformThunkDmd e + | exprIsTrivial e = id + | otherwise = oneifyDmd -- Do not process absent demands -- Otherwise act like in a normal demand analysis @@ -177,7 +176,7 @@ dmdAnal env dmd (App fun arg) -- Non-type arguments call_dmd = mkCallDmd dmd (fun_ty, fun') = dmdAnal env call_dmd fun (arg_dmd, res_ty) = splitDmdTy fun_ty - (arg_ty, arg') = dmdAnalArg env arg_dmd arg + (arg_ty, arg') = dmdAnalStar env (dmdTransformThunkDmd arg arg_dmd) arg in -- pprTrace "dmdAnal:app" (vcat -- [ text "dmd =" <+> ppr dmd @@ -510,6 +509,7 @@ dmdTransform env var dmd | otherwise -- Local non-letrec-bound thing = unitVarDmd var (mkOnceUsedDmd dmd) + \end{code} %************************************************************************ From git at git.haskell.org Mon Dec 16 20:59:35 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Dec 2013 20:59:35 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Comments and small refactor (40586d2) Message-ID: <20131216205935.227632406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/40586d2288d4eabfe5e31cace30d0de1a4358aee/ghc >--------------------------------------------------------------- commit 40586d2288d4eabfe5e31cace30d0de1a4358aee Author: Simon Peyton Jones Date: Wed Dec 4 16:00:24 2013 +0000 Comments and small refactor >--------------------------------------------------------------- 40586d2288d4eabfe5e31cace30d0de1a4358aee compiler/basicTypes/Demand.lhs | 2 +- compiler/stranal/DmdAnal.lhs | 9 ++++++--- 2 files changed, 7 insertions(+), 4 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index f75dc46..b68c10b 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -559,7 +559,7 @@ splitFVs is_thunk rhs_fvs %* * %************************************************************************ -This domain differst from JointDemand in the sense that pure absence +This domain differs from JointDemand in the sense that pure absence is taken away, i.e., we deal *only* with non-absent demands. Note [Strict demands] diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index 897b5b4..f94d53d 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -530,9 +530,6 @@ dmdAnalVarApp env dmd fun args -- , ppr arg_tys, ppr cpr_info, ppr res_ty]) $ ( res_ty , foldl App (Var fun) args') - - | otherwise - = completeApp env (dmdTransform env fun (mkCallDmdN n_val_args dmd), Var fun) args where n_val_args = valArgCount args cxt_ds = splitProdCleanDmd n_val_args dmd @@ -552,6 +549,12 @@ dmdAnalVarApp env dmd fun args , (arg_tys, arg_rets, args') <- anal_con_args ds args = (arg_ty:arg_tys, arg_ret:arg_rets, arg':args') anal_con_args ds args = pprPanic "anal_con_args" (ppr args $$ ppr ds) + +dmdAnalVarApp env dmd fun args + = --pprTrace "dmdAnalVarApp" (vcat [ ppr fun, ppr args + -- , ppr $ completeApp env (dmdTransform env fun (mkCallDmdN n_val_args dmd), Var fun) args + -- ]) + completeApp env (dmdTransform env fun (mkCallDmdN (valArgCount args) dmd), Var fun) args \end{code} %************************************************************************ From git at git.haskell.org Mon Dec 16 20:59:37 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Dec 2013 20:59:37 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Refactor peelManyCalls (16d9078) Message-ID: <20131216205937.5C06B2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/16d9078a86eacf5eb1769b31cd6f622f829cbc41/ghc >--------------------------------------------------------------- commit 16d9078a86eacf5eb1769b31cd6f622f829cbc41 Author: Joachim Breitner Date: Sat Dec 14 22:07:04 2013 +0100 Refactor peelManyCalls its first argument is just used for its length (the arity of the call). So changing the type to Int to reflect that. Also add a note [Demands from unsaturated function calls] that hopefully comprehensively and comprehensibly explains what is going on here. >--------------------------------------------------------------- 16d9078a86eacf5eb1769b31cd6f622f829cbc41 compiler/basicTypes/Demand.lhs | 71 ++++++++++++++++++++++++++++++---------- 1 file changed, 53 insertions(+), 18 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index cdb60af..bb88e40 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -1172,21 +1172,60 @@ peelCallDmd (CD {sd = s, ud = u}) -- because the body isn't used at all! -- c.f. the Abs case in toCleanDmd -peelManyCalls :: [Demand] -> CleanDemand -> DeferAndUse -peelManyCalls arg_ds (CD { sd = str, ud = abs }) - = (go_str arg_ds str, go_abs arg_ds abs) +-- Peels that multiple nestings of calls clean demand and also returns +-- whether it was unsaturated (separately for strictness and usage +-- see Note [Demands from unsaturated function calls] +peelManyCalls :: Int -> CleanDemand -> DeferAndUse +peelManyCalls n (CD { sd = str, ud = abs }) + = (go_str n str, go_abs n abs) where - go_str :: [Demand] -> StrDmd -> Bool -- True <=> unsaturated, defer - go_str [] _ = False - go_str (_:_) HyperStr = False -- HyperStr = Call(HyperStr) - go_str (_:as) (SCall d') = go_str as d' - go_str _ _ = True + go_str :: Int -> StrDmd -> Bool -- True <=> unsaturated, defer + go_str 0 _ = False + go_str _ HyperStr = False -- == go_str (n-1) HyperStr, as HyperStr = Call(HyperStr) + go_str n (SCall d') = go_str (n-1) d' + go_str _ _ = True + + go_abs :: Int -> UseDmd -> Count -- Many <=> unsaturated, or at least + go_abs 0 _ = One -- one UCall Many in the demand + go_abs n (UCall One d') = go_abs (n-1) d' + go_abs _ _ = Many +\end{code} - go_abs :: [Demand] -> UseDmd -> Count -- Many <=> unsaturated, or at least - go_abs [] _ = One -- one UCall Many in the demand - go_abs (_:as) (UCall One d') = go_abs as d' - go_abs _ _ = Many +Note [Demands from unsaturated function calls] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + +Consider a demand transformer d1 -> d2 -> r for f. +If a sufficiently detailed demand is fed into this transformer, +e.g arising from "f x1 x2" in a strict, use-once context, +then d1 and d2 is precisely the demand unleashed onto x1 and x2 (similar for +the free variable environment) and furthermore the result information r is the +one we want to use. + +But the demand fed into f might be less than . There are a few cases: + * Not enough demand on the strictness side: + - In that case, we need to zap all strictness in the demand on arguments and + free variables. + - Furthermore, we need to remove CPR information (after all, "f x1" surely + does not return a constructor). + - And finally, if r said that f would (possible or definitely) diverge when + called with two arguments, then "f x1" may diverge. So we use topRes here. + (We could return "Converges NoCPR" if f would converge for sure, but that + information would currently not be useful in any way.) + * Not enough demand from the usage side: The missing usage can expanded using + UCall Many, therefore this is subsumed by the third case: + * At least one of the uses has a cardinality of Many. + - Even if f puts a One demand on any of its argument or free variables, if + we call f multiple times, we may evaluate this argument or free variable + multiple times. So forget about any occurrence of "One" in the demand. + +In dmdTransformSig, we call peelManyCalls to find out if we are in any of these +cases, and then call postProcessUnsat to reduce the demand appropriately. + +Similarly, dmdTransformDictSelSig and dmdAnal, when analyzing a Lambda, use +peelCallDmd, which peels only one level, but also returns the demand put on the +body of the function. +\begin{code} peelFV :: DmdType -> Var -> (DmdType, Demand) peelFV (DmdType fv ds res) id = -- pprTrace "rfv" (ppr id <+> ppr dmd $$ ppr fv) (DmdType fv' ds res, dmd) @@ -1359,12 +1398,8 @@ dmdTransformSig :: StrictSig -> CleanDemand -> DmdType -- signature is fun_sig, with demand dmd. We return the demand -- that the function places on its context (eg its args) dmdTransformSig (StrictSig dmd_ty@(DmdType _ arg_ds _)) cd - = postProcessUnsat (peelManyCalls arg_ds cd) dmd_ty - -- NB: it's important to use postProcessUnsat, and not - -- just return nopDmdType for unsaturated calls - -- Consider let { f x y = p + x } in f 1 - -- The application isn't saturated, but we must nevertheless propagate - -- a lazy demand for p! + = postProcessUnsat (peelManyCalls (length arg_ds) cd) dmd_ty + -- see Note [Demands from unsaturated function calls] dmdTransformDataConSig :: Arity -> StrictSig -> CleanDemand -> DmdType -- Same as dmdTransformSig but for a data constructor (worker), From git at git.haskell.org Mon Dec 16 20:59:39 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Dec 2013 20:59:39 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Split DmdResult into DmdResult and CPRResult (de62d2c) Message-ID: <20131216205939.8CD152406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/de62d2ce257302f0a99149fa6d8db89477ad3b4b/ghc >--------------------------------------------------------------- commit de62d2ce257302f0a99149fa6d8db89477ad3b4b Author: Joachim Breitner Date: Thu Dec 12 15:39:30 2013 +0000 Split DmdResult into DmdResult and CPRResult this is a small-step-refactoring patch and not very interesting on its own. >--------------------------------------------------------------- de62d2ce257302f0a99149fa6d8db89477ad3b4b compiler/basicTypes/Demand.lhs | 170 ++++++++++++++++++++++++++-------------- compiler/basicTypes/MkId.lhs | 4 +- compiler/stranal/DmdAnal.lhs | 16 ++-- 3 files changed, 119 insertions(+), 71 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 de62d2ce257302f0a99149fa6d8db89477ad3b4b From git at git.haskell.org Mon Dec 16 20:59:41 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Dec 2013 20:59:41 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Recover [CPR for sum types] (slightly differently) (5c3c865) Message-ID: <20131216205941.CDE3C2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/5c3c8654fa0f1bedac1aac41d79991538ee20505/ghc >--------------------------------------------------------------- commit 5c3c8654fa0f1bedac1aac41d79991538ee20505 Author: Joachim Breitner Date: Thu Nov 28 11:17:16 2013 +0000 Recover [CPR for sum types] (slightly differently) >--------------------------------------------------------------- 5c3c8654fa0f1bedac1aac41d79991538ee20505 compiler/basicTypes/Demand.lhs | 24 ++++++++---------------- compiler/stranal/DmdAnal.lhs | 14 ++++++++------ 2 files changed, 16 insertions(+), 22 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index c193c18..d129a9a 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -30,10 +30,9 @@ module Demand ( isBotRes, isTopRes, getDmdResult, resTypeArgDmd, topRes, botRes, cprConRes, vanillaCprConRes, appIsBottom, isBottomingSig, pprIfaceStrictSig, - trimCPRInfo, returnsCPR, returnsCPR_maybe, + returnsCPR, returnsCPR_maybe, forgetCPR, StrictSig(..), mkStrictSig, mkClosedStrictSig, nopSig, botSig, cprProdSig, isNopSig, splitStrictSig, increaseStrictSigArity, - seqDemand, seqDemandList, seqDmdType, seqStrictSig, evalDmd, cleanEvalDmd, cleanEvalProdDmd, isStrictDmd, @@ -826,6 +825,13 @@ cutCPRResult :: Int -> CPRResult -> CPRResult cutCPRResult _ NoCPR = NoCPR cutCPRResult n (RetCon tag rs) = RetCon tag (map (cutDmdResult (n-1)) rs) +-- Forget the CPR information, but remember if it converges or diverges +-- Used for non-strict thunks and non-top-level things with sum type +forgetCPR :: DmdResult -> DmdResult +forgetCPR Diverges = Diverges +forgetCPR (Converges _) = Converges NoCPR +forgetCPR (Dunno _) = Dunno NoCPR + cprConRes :: ConTag -> [DmdResult] -> DmdResult cprConRes tag arg_ress | opt_CprOff = topRes @@ -844,20 +850,6 @@ isBotRes :: DmdResult -> Bool isBotRes Diverges = True isBotRes _ = False --- TODO: This currently ignores trim_sums. Evaluate if still required, and fix --- Note [CPR for sum types] -trimCPRInfo :: Bool -> Bool -> DmdResult -> DmdResult -trimCPRInfo trim_all _trim_sums res - = trimR res - where - trimR (Converges c) = Converges (trimC c) - trimR (Dunno c) = Dunno (trimC c) - trimR Diverges = Diverges - - trimC (RetCon n rs) | trim_all = NoCPR - | otherwise = RetCon n (map trimR rs) - trimC NoCPR = NoCPR - returnsCPR :: DmdResult -> Bool returnsCPR dr = isJust (returnsCPR_maybe dr) diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index 0da1085..ea1a588 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -655,9 +655,10 @@ dmdAnalRhs top_lvl rec_flag env id rhs -- See Note [NOINLINE and strictness] -- See Note [Product demands for function body] - body_dmd = case deepSplitProductType_maybe (exprType body) of - Nothing -> cleanEvalDmd - Just (dc, _, _, _) -> cleanEvalProdDmd (dataConRepArity dc) + (is_sum_type, body_dmd) + = case deepSplitProductType_maybe (exprType body) of + Nothing -> (True, cleanEvalDmd) + Just (dc, _, _, _) -> (False, cleanEvalProdDmd (dataConRepArity dc)) -- See Note [Lazy and unleashable free variables] -- See Note [Aggregated demand for cardinality] @@ -667,9 +668,10 @@ dmdAnalRhs top_lvl rec_flag env id rhs (lazy_fv, sig_fv) = splitFVs is_thunk rhs_fv1 - rhs_res' = trimCPRInfo trim_all trim_sums rhs_res - trim_all = is_thunk && not_strict - trim_sums = not (isTopLevel top_lvl) -- See Note [CPR for sum types] + -- Note [CPR for sum types] + rhs_res' | (is_sum_type && not (isTopLevel top_lvl)) || + (is_thunk && not_strict) = forgetCPR rhs_res + | otherwise = rhs_res -- See Note [CPR for thunks] is_thunk = not (exprIsHNF rhs) From git at git.haskell.org Mon Dec 16 20:59:44 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Dec 2013 20:59:44 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Fix a lubDmdResult equation (e85ee1b) Message-ID: <20131216205944.0DE3B2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/e85ee1baa9a1320fd2b7933a017f7f7bbe45d219/ghc >--------------------------------------------------------------- commit e85ee1baa9a1320fd2b7933a017f7f7bbe45d219 Author: Joachim Breitner Date: Tue Nov 26 10:17:57 2013 +0000 Fix a lubDmdResult equation >--------------------------------------------------------------- e85ee1baa9a1320fd2b7933a017f7f7bbe45d219 compiler/basicTypes/Demand.lhs | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index b68c10b..06d6c82 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -750,8 +750,10 @@ lubCPR (RetProd ds1) (RetProd ds2) lubCPR _ _ = NoCPR lubDmdResult :: DmdResult -> DmdResult -> DmdResult -lubDmdResult Diverges r = r -lubDmdResult (Converges c1) Diverges = Converges c1 +lubDmdResult Diverges (Dunno c2) = Dunno c2 +lubDmdResult Diverges Diverges = Diverges +lubDmdResult Diverges (Converges c2) = Dunno c2 +lubDmdResult (Converges c1) Diverges = Dunno c1 lubDmdResult (Converges c1) (Converges c2) = Converges (c1 `lubCPR` c2) lubDmdResult (Converges c1) (Dunno c2) = Dunno (c1 `lubCPR` c2) lubDmdResult (Dunno c1) Diverges = Dunno c1 From git at git.haskell.org Mon Dec 16 20:59:46 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Dec 2013 20:59:46 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Initial work on Nested CPR (c7104a8) Message-ID: <20131216205946.6B6CA2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/c7104a8d4b419346cbc95fabcadcfc7cc0f0ae0a/ghc >--------------------------------------------------------------- commit c7104a8d4b419346cbc95fabcadcfc7cc0f0ae0a Author: Simon Peyton Jones Date: Mon Nov 25 09:59:16 2013 +0000 Initial work on Nested CPR >--------------------------------------------------------------- c7104a8d4b419346cbc95fabcadcfc7cc0f0ae0a compiler/basicTypes/Demand.lhs | 137 ++++++++++++++++++++++++---------------- compiler/stranal/DmdAnal.lhs | 111 ++++++++++++++++++++++---------- 2 files changed, 160 insertions(+), 88 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 c7104a8d4b419346cbc95fabcadcfc7cc0f0ae0a From git at git.haskell.org Mon Dec 16 20:59:48 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Dec 2013 20:59:48 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Do not export DmdResult constructors in Demand.lhs (8f25170) Message-ID: <20131216205948.96E722406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/8f25170ddab14efe5124deaf811f0600c95b4ab8/ghc >--------------------------------------------------------------- commit 8f25170ddab14efe5124deaf811f0600c95b4ab8 Author: Joachim Breitner Date: Mon Dec 9 16:56:32 2013 +0000 Do not export DmdResult constructors in Demand.lhs >--------------------------------------------------------------- 8f25170ddab14efe5124deaf811f0600c95b4ab8 compiler/basicTypes/Demand.lhs | 20 ++++++++++---------- compiler/basicTypes/MkId.lhs | 4 ++-- 2 files changed, 12 insertions(+), 12 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 3d393f1..3ca8466 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -25,7 +25,7 @@ module Demand ( DmdEnv, emptyDmdEnv, peelFV, - DmdResult(..), CPRResult(..), + DmdResult, CPRResult, isBotRes, isTopRes, resTypeArgDmd, topRes, botRes, cprProdRes, vanillaCprProdRes, cprSumRes, appIsBottom, isBottomingSig, pprIfaceStrictSig, @@ -768,19 +768,19 @@ topRes, botRes :: DmdResult topRes = Dunno NoCPR botRes = Diverges -cprSumRes :: ConTag -> CPRResult -cprSumRes tag | opt_CprOff = NoCPR - | otherwise = RetSum tag +cprSumRes :: ConTag -> DmdResult +cprSumRes tag | opt_CprOff = topRes + | otherwise = Dunno $ RetSum tag -cprProdRes :: [DmdType] -> CPRResult +cprProdRes :: [DmdType] -> DmdResult cprProdRes _arg_tys - | opt_CprOff = NoCPR - | otherwise = RetProd + | opt_CprOff = topRes + | otherwise = Dunno $ RetProd -vanillaCprProdRes :: Arity -> CPRResult +vanillaCprProdRes :: Arity -> DmdResult vanillaCprProdRes _arity - | opt_CprOff = NoCPR - | otherwise = RetProd + | opt_CprOff = topRes + | otherwise = Dunno $ RetProd isTopRes :: DmdResult -> Bool isTopRes (Dunno NoCPR) = True diff --git a/compiler/basicTypes/MkId.lhs b/compiler/basicTypes/MkId.lhs index 6120b56..604163f 100644 --- a/compiler/basicTypes/MkId.lhs +++ b/compiler/basicTypes/MkId.lhs @@ -434,8 +434,8 @@ dataConCPR con , isVanillaDataCon con -- No existentials , wkr_arity > 0 , wkr_arity <= mAX_CPR_SIZE - = if is_prod then Dunno (vanillaCprProdRes (dataConRepArity con)) - else Dunno (cprSumRes (dataConTag con)) + = if is_prod then vanillaCprProdRes (dataConRepArity con) + else cprSumRes (dataConTag con) | otherwise = topRes where From git at git.haskell.org Mon Dec 16 20:59:50 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Dec 2013 20:59:50 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Check mAX_CPR_SIZE in dmdAnalVarApp (d37e646) Message-ID: <20131216205951.09BC32406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/d37e6466ce1986a60a08c7604370e8bbe6a44c36/ghc >--------------------------------------------------------------- commit d37e6466ce1986a60a08c7604370e8bbe6a44c36 Author: Joachim Breitner Date: Thu Dec 5 18:01:34 2013 +0000 Check mAX_CPR_SIZE in dmdAnalVarApp >--------------------------------------------------------------- d37e6466ce1986a60a08c7604370e8bbe6a44c36 compiler/stranal/DmdAnal.lhs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index d5bf8a0..3c613b2 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -522,6 +522,8 @@ dmdAnalVarApp env dmd fun args | Just con <- isDataConWorkId_maybe fun -- Data constructor , isVanillaDataCon con , n_val_args == dataConRepArity con -- Saturated + , dataConRepArity con > 0 + , dataConRepArity con < 10 -- TODO: Sync with mAX_CPR_SIZE in MkId , let cpr_info = cprConRes (dataConTag con) arg_rets res_ty = foldl bothDmdType (DmdType emptyDmdEnv [] cpr_info) arg_tys = -- pprTrace "dmdAnalVarApp" (vcat [ ppr con, ppr args, ppr n_val_args, ppr cxt_ds From git at git.haskell.org Mon Dec 16 20:59:52 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Dec 2013 20:59:52 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Allow the CPR w/w to take unboxed tuples apart (61c15f2) Message-ID: <20131216205953.702972406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/61c15f22dbc9ea30a9fd0d9e2d9e8ad49c9f9b99/ghc >--------------------------------------------------------------- commit 61c15f22dbc9ea30a9fd0d9e2d9e8ad49c9f9b99 Author: Joachim Breitner Date: Thu Nov 28 10:29:47 2013 +0000 Allow the CPR w/w to take unboxed tuples apart >--------------------------------------------------------------- 61c15f22dbc9ea30a9fd0d9e2d9e8ad49c9f9b99 compiler/stranal/WwLib.lhs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/stranal/WwLib.lhs b/compiler/stranal/WwLib.lhs index ce4112c..5168d8f 100644 --- a/compiler/stranal/WwLib.lhs +++ b/compiler/stranal/WwLib.lhs @@ -502,7 +502,7 @@ deepSplitCprType_maybe :: ConTag -> Type -> Maybe (DataCon, [Type], [Type], Coer deepSplitCprType_maybe con_tag ty | let (co, ty1) = topNormaliseNewType_maybe ty `orElse` (mkReflCo Representational ty, ty) , Just (tc, tc_args) <- splitTyConApp_maybe ty1 - , isDataTyCon tc + , isDataTyCon tc || isUnboxedTupleTyCon tc , let cons = tyConDataCons tc con = ASSERT( cons `lengthAtLeast` con_tag ) cons !! (con_tag - fIRST_TAG) = Just (con, tc_args, dataConInstArgTys con tc_args, co) From git at git.haskell.org Mon Dec 16 20:59:55 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Dec 2013 20:59:55 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Loop breakers are not allowed to have a Converges DmdResult (e6f1bf9) Message-ID: <20131216205955.539F52406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/e6f1bf96275bb2ca7b35bddc41534e7a774c1b75/ghc >--------------------------------------------------------------- commit e6f1bf96275bb2ca7b35bddc41534e7a774c1b75 Author: Joachim Breitner Date: Tue Nov 26 10:18:35 2013 +0000 Loop breakers are not allowed to have a Converges DmdResult >--------------------------------------------------------------- e6f1bf96275bb2ca7b35bddc41534e7a774c1b75 compiler/basicTypes/Demand.lhs | 19 +++++++++++-------- compiler/stranal/DmdAnal.lhs | 5 ++++- 2 files changed, 15 insertions(+), 9 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index d129a9a..2fe9236 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -33,6 +33,7 @@ module Demand ( returnsCPR, returnsCPR_maybe, forgetCPR, StrictSig(..), mkStrictSig, mkClosedStrictSig, nopSig, botSig, cprProdSig, isNopSig, splitStrictSig, increaseStrictSigArity, + sigMayConverge, seqDemand, seqDemandList, seqDmdType, seqStrictSig, evalDmd, cleanEvalDmd, cleanEvalProdDmd, isStrictDmd, @@ -806,15 +807,10 @@ getDmdResult _ = topRes maxCPRDepth :: Int maxCPRDepth = 3 --- With nested CPR, DmdResult can be arbitrarily deep; consider --- data Rec1 = Foo Rec2 Rec2 --- data Rec2 = Bar Rec1 Rec1 --- --- x = Foo y y --- y = Bar x x --- +-- With nested CPR, DmdResult can be arbitrarily deep; consider e.g. the +-- DmdResult of repeat -- So we need to forget information at a certain depth. We do that at all points --- where we are constructing new RetCon constructors. +-- where we are building RetCon constructors. cutDmdResult :: Int -> DmdResult -> DmdResult cutDmdResult 0 _ = topRes cutDmdResult _ Diverges = Diverges @@ -825,6 +821,10 @@ cutCPRResult :: Int -> CPRResult -> CPRResult cutCPRResult _ NoCPR = NoCPR cutCPRResult n (RetCon tag rs) = RetCon tag (map (cutDmdResult (n-1)) rs) +-- Forget that something might converge for sure +divergeDmdResult :: DmdResult -> DmdResult +divergeDmdResult r = r `lubDmdResult` botRes + -- Forget the CPR information, but remember if it converges or diverges -- Used for non-strict thunks and non-top-level things with sum type forgetCPR :: DmdResult -> DmdResult @@ -1445,6 +1445,9 @@ botSig = StrictSig botDmdType cprProdSig :: Arity -> StrictSig cprProdSig arity = StrictSig (cprProdDmdType arity) +sigMayConverge :: StrictSig -> StrictSig +sigMayConverge (StrictSig (DmdType env ds res)) = (StrictSig (DmdType env ds (divergeDmdResult res))) + argsOneShots :: StrictSig -> Arity -> [[OneShotInfo]] argsOneShots (StrictSig (DmdType _ arg_ds _)) n_val_args = go arg_ds diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index ea1a588..d5bf8a0 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -1084,7 +1084,10 @@ updSigEnv env sigs = env { ae_sigs = sigs } extendAnalEnv :: TopLevelFlag -> AnalEnv -> Id -> StrictSig -> AnalEnv extendAnalEnv top_lvl env var sig - = env { ae_sigs = extendSigEnv top_lvl (ae_sigs env) var sig } + = env { ae_sigs = extendSigEnv top_lvl (ae_sigs env) var sig' } + where + sig' | isWeakLoopBreaker (idOccInfo var) = sigMayConverge sig + | otherwise = sig extendSigEnv :: TopLevelFlag -> SigEnv -> Id -> StrictSig -> SigEnv extendSigEnv top_lvl sigs var sig = extendVarEnv sigs var (sig, top_lvl) From git at git.haskell.org Mon Dec 16 20:59:57 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Dec 2013 20:59:57 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Add a flag -fnested-cpr-off to conveniently test the effect of nested CPR (2af8008) Message-ID: <20131216205958.43C8B2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/2af80081537ef96011f8a04b5633156b269d708b/ghc >--------------------------------------------------------------- commit 2af80081537ef96011f8a04b5633156b269d708b Author: Joachim Breitner Date: Wed Dec 4 09:14:26 2013 +0000 Add a flag -fnested-cpr-off to conveniently test the effect of nested CPR >--------------------------------------------------------------- 2af80081537ef96011f8a04b5633156b269d708b compiler/basicTypes/Demand.lhs | 29 ++++++++++++++++++++--------- compiler/main/StaticFlags.hs | 9 +++++++-- 2 files changed, 27 insertions(+), 11 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 2fe9236..b816841 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -807,19 +807,29 @@ getDmdResult _ = topRes maxCPRDepth :: Int maxCPRDepth = 3 +-- This is the depth we use with -fnested-cpr-off, in order +-- to get precisely the same behaviour as before introduction of nested cpr +-- -fnested-cpr-off can eventually be removed if nested cpr is deemd to be +-- a good thing always. +flatCPRDepth :: Int +flatCPRDepth = 1 + -- With nested CPR, DmdResult can be arbitrarily deep; consider e.g. the -- DmdResult of repeat +-- -- So we need to forget information at a certain depth. We do that at all points -- where we are building RetCon constructors. -cutDmdResult :: Int -> DmdResult -> DmdResult -cutDmdResult 0 _ = topRes -cutDmdResult _ Diverges = Diverges -cutDmdResult n (Converges c) = Converges (cutCPRResult n c) -cutDmdResult n (Dunno c) = Dunno (cutCPRResult n c) - cutCPRResult :: Int -> CPRResult -> CPRResult -cutCPRResult _ NoCPR = NoCPR +cutCPRResult 0 _ = NoCPR +cutCPRResult _ NoCPR = NoCPR cutCPRResult n (RetCon tag rs) = RetCon tag (map (cutDmdResult (n-1)) rs) + where + cutDmdResult :: Int -> DmdResult -> DmdResult + cutDmdResult 0 _ = topRes + cutDmdResult _ Diverges = Diverges + cutDmdResult n (Converges c) = Converges (cutCPRResult n c) + cutDmdResult n (Dunno c) = Dunno (cutCPRResult n c) + -- Forget that something might converge for sure divergeDmdResult :: DmdResult -> DmdResult @@ -834,8 +844,9 @@ forgetCPR (Dunno _) = Dunno NoCPR cprConRes :: ConTag -> [DmdResult] -> DmdResult cprConRes tag arg_ress - | opt_CprOff = topRes - | otherwise = Converges $ cutCPRResult maxCPRDepth $ RetCon tag arg_ress + | opt_CprOff = topRes + | opt_NestedCprOff = Converges $ cutCPRResult flatCPRDepth $ RetCon tag arg_ress + | otherwise = Converges $ cutCPRResult maxCPRDepth $ RetCon tag arg_ress vanillaCprConRes :: ConTag -> Arity -> DmdResult vanillaCprConRes tag arity diff --git a/compiler/main/StaticFlags.hs b/compiler/main/StaticFlags.hs index 01dc3b7..feb7235 100644 --- a/compiler/main/StaticFlags.hs +++ b/compiler/main/StaticFlags.hs @@ -27,6 +27,7 @@ module StaticFlags ( -- optimisation opts opt_NoStateHack, opt_CprOff, + opt_NestedCprOff, opt_NoOptCoercion, -- For the parser @@ -140,7 +141,8 @@ flagsStaticNames :: [String] flagsStaticNames = [ "fno-state-hack", "fno-opt-coercion", - "fcpr-off" + "fcpr-off", + "fnested-cpr-off" ] -- We specifically need to discard static flags for clients of the @@ -195,10 +197,13 @@ opt_NoDebugOutput = lookUp (fsLit "-dno-debug-output") opt_NoStateHack :: Bool opt_NoStateHack = lookUp (fsLit "-fno-state-hack") --- Switch off CPR analysis in the new demand analyser +-- Switch off CPR analysis in the demand analyser opt_CprOff :: Bool opt_CprOff = lookUp (fsLit "-fcpr-off") +opt_NestedCprOff :: Bool +opt_NestedCprOff = lookUp (fsLit "-fnested-cpr-off") + opt_NoOptCoercion :: Bool opt_NoOptCoercion = lookUp (fsLit "-fno-opt-coercion") From git at git.haskell.org Mon Dec 16 21:00:00 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Dec 2013 21:00:00 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Add a warning to dmdTransformDataConSig (which I believe is dead code) (6c1885d) Message-ID: <20131216210000.15A7F2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/6c1885dfa8307897e6e27be9efd9a766996e2274/ghc >--------------------------------------------------------------- commit 6c1885dfa8307897e6e27be9efd9a766996e2274 Author: Joachim Breitner Date: Tue Dec 10 13:56:08 2013 +0000 Add a warning to dmdTransformDataConSig (which I believe is dead code) >--------------------------------------------------------------- 6c1885dfa8307897e6e27be9efd9a766996e2274 compiler/basicTypes/Demand.lhs | 1 + 1 file changed, 1 insertion(+) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 2f03484..b0b9092 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -1519,6 +1519,7 @@ dmdTransformDataConSig arity (StrictSig (DmdType _ _ con_res)) (CD { sd = str, ud = abs }) | Just str_dmds <- go_str arity str , Just abs_dmds <- go_abs arity abs + , WARN( True, text "dmdTransformDataConSig indeed still in use" ) True = DmdType emptyDmdEnv (mkJointDmds str_dmds abs_dmds) con_res -- Must remember whether it's a product, hence con_res, not TopRes From git at git.haskell.org Mon Dec 16 21:00:02 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Dec 2013 21:00:02 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: in Demand.lhs, remember what is a sum type (2ef1052) Message-ID: <20131216210002.4751B2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/2ef1052f21add13af780fc0fa7967a3ba48b8b62/ghc >--------------------------------------------------------------- commit 2ef1052f21add13af780fc0fa7967a3ba48b8b62 Author: Joachim Breitner Date: Tue Dec 10 09:15:09 2013 +0000 in Demand.lhs, remember what is a sum type because we want to zap CPR information for sum types not only on the outermost level, but also nested. See Note [CPR for sum types] This comes up in sublist in Listplikefns in nofib?s boyer2. >--------------------------------------------------------------- 2ef1052f21add13af780fc0fa7967a3ba48b8b62 compiler/basicTypes/DataCon.lhs | 4 +++ compiler/basicTypes/Demand.lhs | 76 ++++++++++++++++++++++++--------------- compiler/basicTypes/MkId.lhs | 2 +- compiler/stranal/DmdAnal.lhs | 39 ++++++++++++-------- 4 files changed, 77 insertions(+), 44 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 2ef1052f21add13af780fc0fa7967a3ba48b8b62 From git at git.haskell.org Mon Dec 16 21:00:04 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Dec 2013 21:00:04 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Temporarily disable nested CPR inside sum types (dbd0e03) Message-ID: <20131216210004.A617F2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/dbd0e038f5c3155374b4adb4273d5c6c447ee4f9/ghc >--------------------------------------------------------------- commit dbd0e038f5c3155374b4adb4273d5c6c447ee4f9 Author: Joachim Breitner Date: Tue Dec 10 10:12:46 2013 +0000 Temporarily disable nested CPR inside sum types >--------------------------------------------------------------- dbd0e038f5c3155374b4adb4273d5c6c447ee4f9 compiler/basicTypes/Demand.lhs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 521c32b..2f03484 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -865,7 +865,7 @@ cprConRes isProd tag arg_ress | opt_NestedCprOff = Converges $ cutCPRResult flatCPRDepth $ retCon arg_ress | otherwise = Converges $ cutCPRResult maxCPRDepth $ retCon arg_ress where retCon | isProd = RetProd - | otherwise = RetSum tag + | otherwise = RetSum tag . map (const topRes) vanillaCprConRes :: Bool -> ConTag -> Arity -> DmdResult vanillaCprConRes isProd tag arity = cprConRes isProd tag (replicate arity topRes) From git at git.haskell.org Mon Dec 16 21:00:06 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Dec 2013 21:00:06 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Actually create a nested CPR worker-wrapper (30f013d) Message-ID: <20131216210006.D5A4A2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/30f013d6698217d8885451c7185a408eb71b67e6/ghc >--------------------------------------------------------------- commit 30f013d6698217d8885451c7185a408eb71b67e6 Author: Joachim Breitner Date: Thu Dec 5 18:58:07 2013 +0000 Actually create a nested CPR worker-wrapper >--------------------------------------------------------------- 30f013d6698217d8885451c7185a408eb71b67e6 compiler/basicTypes/Demand.lhs | 15 +++-- compiler/stranal/WwLib.lhs | 141 +++++++++++++++++++++++++--------------- 2 files changed, 95 insertions(+), 61 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 30f013d6698217d8885451c7185a408eb71b67e6 From git at git.haskell.org Mon Dec 16 21:09:45 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Dec 2013 21:09:45 +0000 (UTC) Subject: [commit: ghc] master: Refactor peelManyCalls (24eafd2) Message-ID: <20131216210945.3B1A72406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/24eafd2032e167ef40c07a15b59eba44173609a6/ghc >--------------------------------------------------------------- commit 24eafd2032e167ef40c07a15b59eba44173609a6 Author: Joachim Breitner Date: Sat Dec 14 22:07:04 2013 +0100 Refactor peelManyCalls its first argument is just used for its length (the arity of the call). So changing the type to Int to reflect that. Also add a note [Demands from unsaturated function calls] that hopefully comprehensively and comprehensibly explains what is going on here. >--------------------------------------------------------------- 24eafd2032e167ef40c07a15b59eba44173609a6 compiler/basicTypes/Demand.lhs | 71 ++++++++++++++++++++++++++++++---------- 1 file changed, 53 insertions(+), 18 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index cdb60af..f44437d 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -1172,21 +1172,60 @@ peelCallDmd (CD {sd = s, ud = u}) -- because the body isn't used at all! -- c.f. the Abs case in toCleanDmd -peelManyCalls :: [Demand] -> CleanDemand -> DeferAndUse -peelManyCalls arg_ds (CD { sd = str, ud = abs }) - = (go_str arg_ds str, go_abs arg_ds abs) +-- Peels that multiple nestings of calls clean demand and also returns +-- whether it was unsaturated (separately for strictness and usage +-- see Note [Demands from unsaturated function calls] +peelManyCalls :: Int -> CleanDemand -> DeferAndUse +peelManyCalls n (CD { sd = str, ud = abs }) + = (go_str n str, go_abs n abs) where - go_str :: [Demand] -> StrDmd -> Bool -- True <=> unsaturated, defer - go_str [] _ = False - go_str (_:_) HyperStr = False -- HyperStr = Call(HyperStr) - go_str (_:as) (SCall d') = go_str as d' - go_str _ _ = True + go_str :: Int -> StrDmd -> Bool -- True <=> unsaturated, defer + go_str 0 _ = False + go_str _ HyperStr = False -- == go_str (n-1) HyperStr, as HyperStr = Call(HyperStr) + go_str n (SCall d') = go_str (n-1) d' + go_str _ _ = True + + go_abs :: Int -> UseDmd -> Count -- Many <=> unsaturated, or at least + go_abs 0 _ = One -- one UCall Many in the demand + go_abs n (UCall One d') = go_abs (n-1) d' + go_abs _ _ = Many +\end{code} - go_abs :: [Demand] -> UseDmd -> Count -- Many <=> unsaturated, or at least - go_abs [] _ = One -- one UCall Many in the demand - go_abs (_:as) (UCall One d') = go_abs as d' - go_abs _ _ = Many +Note [Demands from unsaturated function calls] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + +Consider a demand transformer d1 -> d2 -> r for f. +If a sufficiently detailed demand is fed into this transformer, +e.g arising from "f x1 x2" in a strict, use-once context, +then d1 and d2 is precisely the demand unleashed onto x1 and x2 (similar for +the free variable environment) and furthermore the result information r is the +one we want to use. + +But the demand fed into f might be less than . There are a few cases: + * Not enough demand on the strictness side: + - In that case, we need to zap all strictness in the demand on arguments and + free variables. + - Furthermore, we need to remove CPR information (after all, "f x1" surely + does not return a constructor). + - And finally, if r said that f would (possible or definitely) diverge when + called with two arguments, then "f x1" may diverge. So we use topRes here. + (We could return "Converges NoCPR" if f would converge for sure, but that + information would currently not be useful in any way.) + * Not enough demand from the usage side: The missing usage can be expanded + using UCall Many, therefore this is subsumed by the third case: + * At least one of the uses has a cardinality of Many. + - Even if f puts a One demand on any of its argument or free variables, if + we call f multiple times, we may evaluate this argument or free variable + multiple times. So forget about any occurrence of "One" in the demand. + +In dmdTransformSig, we call peelManyCalls to find out if we are in any of these +cases, and then call postProcessUnsat to reduce the demand appropriately. + +Similarly, dmdTransformDictSelSig and dmdAnal, when analyzing a Lambda, use +peelCallDmd, which peels only one level, but also returns the demand put on the +body of the function. +\begin{code} peelFV :: DmdType -> Var -> (DmdType, Demand) peelFV (DmdType fv ds res) id = -- pprTrace "rfv" (ppr id <+> ppr dmd $$ ppr fv) (DmdType fv' ds res, dmd) @@ -1359,12 +1398,8 @@ dmdTransformSig :: StrictSig -> CleanDemand -> DmdType -- signature is fun_sig, with demand dmd. We return the demand -- that the function places on its context (eg its args) dmdTransformSig (StrictSig dmd_ty@(DmdType _ arg_ds _)) cd - = postProcessUnsat (peelManyCalls arg_ds cd) dmd_ty - -- NB: it's important to use postProcessUnsat, and not - -- just return nopDmdType for unsaturated calls - -- Consider let { f x y = p + x } in f 1 - -- The application isn't saturated, but we must nevertheless propagate - -- a lazy demand for p! + = postProcessUnsat (peelManyCalls (length arg_ds) cd) dmd_ty + -- see Note [Demands from unsaturated function calls] dmdTransformDataConSig :: Arity -> StrictSig -> CleanDemand -> DmdType -- Same as dmdTransformSig but for a data constructor (worker), From git at git.haskell.org Mon Dec 16 21:09:47 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Dec 2013 21:09:47 +0000 (UTC) Subject: [commit: ghc] master: Disentangle postProcessDmdTypeM and postProcessUnsat (72b6224) Message-ID: <20131216210947.964152406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/72b62242288d23299d77245faed8c5fc4dab1d4f/ghc >--------------------------------------------------------------- commit 72b62242288d23299d77245faed8c5fc4dab1d4f Author: Joachim Breitner Date: Mon Dec 9 18:40:09 2013 +0000 Disentangle postProcessDmdTypeM and postProcessUnsat Make different postProcess code paths for function arguments (which are post-processed just to be both'ed) and unsaturated functions (which are post-processed for other reasons.) >--------------------------------------------------------------- 72b62242288d23299d77245faed8c5fc4dab1d4f compiler/basicTypes/Demand.lhs | 14 +++++++++++++- 1 file changed, 13 insertions(+), 1 deletion(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index f44437d..3281332 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -1131,7 +1131,19 @@ postProcessDmdTypeM Nothing _ = nopDmdType -- Incoming demand was Absent, so just discard all usage information -- We only processed the thing at all to analyse the body -- See Note [Always analyse in virgin pass] -postProcessDmdTypeM (Just du) ty = postProcessUnsat du ty +postProcessDmdTypeM (Just du) (DmdType fv _ res_ty) + = DmdType (postProcessDmdEnv du fv) [] (postProcessDmdResult du res_ty) + +postProcessDmdResult :: DeferAndUse -> DmdResult -> DmdResult +postProcessDmdResult (True,_) r = topRes +postProcessDmdResult (False,_) r = r + +postProcessDmdEnv :: DeferAndUse -> DmdEnv -> DmdEnv +postProcessDmdEnv (True, Many) env = deferReuseEnv env +postProcessDmdEnv (False, Many) env = reuseEnv env +postProcessDmdEnv (True, One) env = deferEnv env +postProcessDmdEnv (False, One) env = env + postProcessUnsat :: DeferAndUse -> DmdType -> DmdType postProcessUnsat (True, Many) ty = deferReuse ty From git at git.haskell.org Mon Dec 16 21:09:49 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Dec 2013 21:09:49 +0000 (UTC) Subject: [commit: ghc] master: Make types of bothDmdType more precise (0e2fd36) Message-ID: <20131216210949.A7C322406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0e2fd365301748ac7535ed15f46d159814b71438/ghc >--------------------------------------------------------------- commit 0e2fd365301748ac7535ed15f46d159814b71438 Author: Joachim Breitner Date: Mon Dec 9 18:40:09 2013 +0000 Make types of bothDmdType more precise by only passing the demand on the free variables, and whether the argument (resp. scrunitee) may or will diverge. >--------------------------------------------------------------- 0e2fd365301748ac7535ed15f46d159814b71438 compiler/basicTypes/Demand.lhs | 55 +++++++++++++++++++++++++--------------- compiler/stranal/DmdAnal.lhs | 9 +++---- 2 files changed, 39 insertions(+), 25 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 3281332..d408e6d 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -21,6 +21,7 @@ module Demand ( DmdType(..), dmdTypeDepth, lubDmdType, bothDmdType, nopDmdType, botDmdType, mkDmdType, addDemand, + BothDmdArg, mkBothDmdArg, toBothDmdArg, DmdEnv, emptyDmdEnv, peelFV, @@ -709,14 +710,15 @@ We have lubs, but not glbs; but that is ok. -- Constructed Product Result ------------------------------------------------------------------------ -data CPRResult = NoCPR -- Top of the lattice - | RetProd -- Returns a constructor from a product type - | RetSum ConTag -- Returns a constructor from a sum type with this tag +data Termination r = Diverges -- Definitely diverges + | Dunno r -- Might diverge or converge deriving( Eq, Show ) -data DmdResult = Diverges -- Definitely diverges - | Dunno CPRResult -- Might diverge or converge, but in the latter case the - -- result shape is described by CPRResult +type DmdResult = Termination CPRResult + +data CPRResult = NoCPR -- Top of the lattice + | RetProd -- Returns a constructor from a product type + | RetSum ConTag -- Returns a constructor from a data type deriving( Eq, Show ) lubCPR :: CPRResult -> CPRResult -> CPRResult @@ -733,7 +735,7 @@ lubDmdResult (Dunno c1) (Dunno c2) = Dunno (c1 `lubCPR` c2) -- defaultDmd (r1 `lubDmdResult` r2) = defaultDmd r1 `lubDmd` defaultDmd r2 -- (See Note [Default demand on free variables] for why) -bothDmdResult :: DmdResult -> DmdResult -> DmdResult +bothDmdResult :: DmdResult -> Termination () -> DmdResult -- See Note [Asymmetry of 'both' for DmdType and DmdResult] bothDmdResult _ Diverges = Diverges bothDmdResult r _ = r @@ -1024,13 +1026,25 @@ lubDmdType (DmdType fv1 ds1 r1) (DmdType fv2 ds2 r2) lub_ds ds1 [] = map (`lubDmd` resTypeArgDmd r2) ds1 lub_ds [] ds2 = map (resTypeArgDmd r1 `lubDmd`) ds2 -bothDmdType :: DmdType -> DmdType -> DmdType -bothDmdType (DmdType fv1 ds1 r1) (DmdType fv2 _ r2) + +type BothDmdArg = (DmdEnv, Termination ()) + +mkBothDmdArg :: DmdEnv -> BothDmdArg +mkBothDmdArg env = (env, Dunno ()) + +toBothDmdArg :: DmdType -> BothDmdArg +toBothDmdArg (DmdType fv _ r) = (fv, go r) + where + go (Dunno {}) = Dunno () + go Diverges = Diverges + +bothDmdType :: DmdType -> BothDmdArg -> DmdType +bothDmdType (DmdType fv1 ds1 r1) (fv2, t2) -- See Note [Asymmetry of 'both' for DmdType and DmdResult] -- 'both' takes the argument/result info from its *first* arg, -- using its second arg just for its free-var info. - = DmdType both_fv ds1 (r1 `bothDmdResult` r2) - where both_fv = plusVarEnv_CD bothDmd fv1 (defaultDmd r1) fv2 (defaultDmd r2) + = DmdType both_fv ds1 (r1 `bothDmdResult` t2) + where both_fv = plusVarEnv_CD bothDmd fv1 (defaultDmd r1) fv2 (defaultDmd t2) instance Outputable DmdType where ppr (DmdType fv ds res) @@ -1126,17 +1140,18 @@ toCleanDmd (JD { strd = s, absd = u }) -- This is used in dmdAnalStar when post-processing -- a function's argument demand. So we only care about what -- does to free variables, and whether it terminates. -postProcessDmdTypeM :: DeferAndUseM -> DmdType -> DmdType -postProcessDmdTypeM Nothing _ = nopDmdType +postProcessDmdTypeM :: DeferAndUseM -> DmdType -> BothDmdArg +postProcessDmdTypeM Nothing _ = (emptyDmdEnv, Dunno ()) -- Incoming demand was Absent, so just discard all usage information -- We only processed the thing at all to analyse the body -- See Note [Always analyse in virgin pass] postProcessDmdTypeM (Just du) (DmdType fv _ res_ty) - = DmdType (postProcessDmdEnv du fv) [] (postProcessDmdResult du res_ty) + = (postProcessDmdEnv du fv, postProcessDmdResult du res_ty) -postProcessDmdResult :: DeferAndUse -> DmdResult -> DmdResult -postProcessDmdResult (True,_) r = topRes -postProcessDmdResult (False,_) r = r +postProcessDmdResult :: DeferAndUse -> DmdResult -> Termination () +postProcessDmdResult (True,_) _ = Dunno () +postProcessDmdResult (False,_) (Dunno {}) = Dunno () +postProcessDmdResult (False,_) Diverges = Diverges postProcessDmdEnv :: DeferAndUse -> DmdEnv -> DmdEnv postProcessDmdEnv (True, Many) env = deferReuseEnv env @@ -1246,9 +1261,9 @@ peelFV (DmdType fv ds res) id = -- pprTrace "rfv" (ppr id <+> ppr dmd $$ ppr fv) -- See note [Default demand on free variables] dmd = lookupVarEnv fv id `orElse` defaultDmd res -defaultDmd :: DmdResult -> Demand -defaultDmd res | isBotRes res = botDmd - | otherwise = absDmd +defaultDmd :: Termination r -> Demand +defaultDmd Diverges = botDmd +defaultDmd _ = absDmd addDemand :: Demand -> DmdType -> DmdType addDemand dmd (DmdType fv ds res) = DmdType fv (dmd:ds) res diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index cbdcc67..a942c4e 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -115,7 +115,7 @@ dmdTransformThunkDmd e -- See |-* relation in the companion paper dmdAnalStar :: AnalEnv -> Demand -- This one takes a *Demand* - -> CoreExpr -> (DmdType, CoreExpr) + -> CoreExpr -> (BothDmdArg, CoreExpr) dmdAnalStar env dmd e | (cd, defer_and_use) <- toCleanDmd dmd , (dmd_ty, e') <- dmdAnal env cd e @@ -255,7 +255,7 @@ dmdAnal env dmd (Case scrut case_bndr ty [alt@(DataAlt dc, _, _)]) scrut_dmd = scrut_dmd1 `bothCleanDmd` scrut_dmd2 (scrut_ty, scrut') = dmdAnal env scrut_dmd scrut - res_ty = alt_ty1 `bothDmdType` scrut_ty + res_ty = alt_ty1 `bothDmdType` toBothDmdArg scrut_ty in -- pprTrace "dmdAnal:Case1" (vcat [ text "scrut" <+> ppr scrut -- , text "dmd" <+> ppr dmd @@ -271,7 +271,7 @@ dmdAnal env dmd (Case scrut case_bndr ty alts) (alt_tys, alts') = mapAndUnzip (dmdAnalAlt env dmd) alts (scrut_ty, scrut') = dmdAnal env cleanEvalDmd scrut (alt_ty, case_bndr') = annotateBndr env (foldr lubDmdType botDmdType alt_tys) case_bndr - res_ty = alt_ty `bothDmdType` scrut_ty + res_ty = alt_ty `bothDmdType` toBothDmdArg scrut_ty in -- pprTrace "dmdAnal:Case2" (vcat [ text "scrut" <+> ppr scrut -- , text "scrut_ty" <+> ppr scrut_ty @@ -509,7 +509,6 @@ dmdTransform env var dmd | otherwise -- Local non-letrec-bound thing = unitVarDmd var (mkOnceUsedDmd dmd) - \end{code} %************************************************************************ @@ -698,7 +697,7 @@ addVarDmd (DmdType fv ds res) var dmd addLazyFVs :: DmdType -> DmdEnv -> DmdType addLazyFVs dmd_ty lazy_fvs - = dmd_ty `bothDmdType` mkDmdType lazy_fvs [] topRes + = dmd_ty `bothDmdType` mkBothDmdArg lazy_fvs -- Using bothDmdType (rather than just both'ing the envs) -- is vital. Consider -- let f = \x -> (x,y) From git at git.haskell.org Mon Dec 16 21:09:51 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Dec 2013 21:09:51 +0000 (UTC) Subject: [commit: ghc] master's head updated: Make types of bothDmdType more precise (0e2fd36) Message-ID: <20131216210951.D0F0F2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'master' now includes: 6b6a30d Move peelFV from DmdAnal to Demand fbe14a8 Clarify the default demand on demand environments 59d4a8e Remove dmdAnalArg and replace by easier to understand code b1561d1 Add Note [non-algebraic or open body type warning] de62d2c Split DmdResult into DmdResult and CPRResult 8f25170 Do not export DmdResult constructors in Demand.lhs 779dca7 Rename postProcessDmdType to postProcessUnsat and use* to reuse* 24eafd2 Refactor peelManyCalls 72b6224 Disentangle postProcessDmdTypeM and postProcessUnsat 0e2fd36 Make types of bothDmdType more precise From git at git.haskell.org Mon Dec 16 22:20:33 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 16 Dec 2013 22:20:33 +0000 (UTC) Subject: [commit: ghc] master: Update comments: Void# instead of State# RealWorld# (7eabd56) Message-ID: <20131216222033.5FBB12406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7eabd5685b4d764934da5e00824128d310cd82e8/ghc >--------------------------------------------------------------- commit 7eabd5685b4d764934da5e00824128d310cd82e8 Author: Joachim Breitner Date: Mon Dec 16 23:20:24 2013 +0100 Update comments: Void# instead of State# RealWorld# >--------------------------------------------------------------- 7eabd5685b4d764934da5e00824128d310cd82e8 compiler/simplCore/Simplify.lhs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/compiler/simplCore/Simplify.lhs b/compiler/simplCore/Simplify.lhs index 03150c6..3873ed3 100644 --- a/compiler/simplCore/Simplify.lhs +++ b/compiler/simplCore/Simplify.lhs @@ -1780,7 +1780,7 @@ Consider: test :: Integer -> IO () Turns out that this compiles to: Print.test = \ eta :: Integer - eta1 :: State# RealWorld -> + eta1 :: Void# -> case PrelNum.< eta PrelNum.zeroInteger of wild { __DEFAULT -> case hPutStr stdout (PrelNum.jtos eta ($w[] @ Char)) @@ -2620,8 +2620,8 @@ for several reasons for let-binding-purposes, we will *caseify* it (!), with potentially-disastrous strictness results. So instead we turn it into a function: \v -> e - where v::State# RealWorld#. The value passed to this function - is realworld#, which generates (almost) no code. + where v::Void#. The value passed to this function is void, + which generates (almost) no code. * CPR. We used to say "&& isUnLiftedType rhs_ty'" here, but now we make the join point into a function whenever used_bndrs' From git at git.haskell.org Tue Dec 17 11:19:58 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 17 Dec 2013 11:19:58 +0000 (UTC) Subject: [commit: ghc] master: Copy-pasto. (39c55a3) Message-ID: <20131217111958.80E6D2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/39c55a3653dd1a3f2adfa4a50fe249ffc60c2ffd/ghc >--------------------------------------------------------------- commit 39c55a3653dd1a3f2adfa4a50fe249ffc60c2ffd Author: Mikhail Glushenkov Date: Tue Dec 17 06:33:17 2013 +0100 Copy-pasto. >--------------------------------------------------------------- 39c55a3653dd1a3f2adfa4a50fe249ffc60c2ffd docs/users_guide/using.xml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/docs/users_guide/using.xml b/docs/users_guide/using.xml index 8ce96a8..0d5881f 100644 --- a/docs/users_guide/using.xml +++ b/docs/users_guide/using.xml @@ -2138,7 +2138,7 @@ f "2" = 2 - + Worker-wrapper removes unused arguments, but usually we do From git at git.haskell.org Tue Dec 17 11:20:00 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 17 Dec 2013 11:20:00 +0000 (UTC) Subject: [commit: ghc] master: Mention '-fno-ignore-asserts' in documentation. (ddd1c82) Message-ID: <20131217112000.F0A922406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ddd1c8209a69b9ed1cdad2a9b47a7e47bbd4bc96/ghc >--------------------------------------------------------------- commit ddd1c8209a69b9ed1cdad2a9b47a7e47bbd4bc96 Author: Mikhail Glushenkov Date: Tue Dec 17 07:51:02 2013 +0100 Mention '-fno-ignore-asserts' in documentation. (Closes: #8617) >--------------------------------------------------------------- ddd1c8209a69b9ed1cdad2a9b47a7e47bbd4bc96 docs/users_guide/glasgow_exts.xml | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/docs/users_guide/glasgow_exts.xml b/docs/users_guide/glasgow_exts.xml index 99a3f21..e97faf1 100644 --- a/docs/users_guide/glasgow_exts.xml +++ b/docs/users_guide/glasgow_exts.xml @@ -9220,7 +9220,9 @@ GHC ignores assertions when optimisation is turned on with the e. You can also disable assertions using the option - . + . The option allows +enabling assertions even when optimisation is turned on. + Assertion failures can be caught, see the documentation for the From git at git.haskell.org Tue Dec 17 15:58:38 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 17 Dec 2013 15:58:38 +0000 (UTC) Subject: [commit: ghc] master: Remove unused eqExprX (82dfe08) Message-ID: <20131217155838.8C5562406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/82dfe08d43e5cb9617fbc056fd3359b514414413/ghc >--------------------------------------------------------------- commit 82dfe08d43e5cb9617fbc056fd3359b514414413 Author: Joachim Breitner Date: Tue Dec 17 16:34:28 2013 +0100 Remove unused eqExprX >--------------------------------------------------------------- 82dfe08d43e5cb9617fbc056fd3359b514414413 compiler/coreSyn/CoreUtils.lhs | 44 +++++----------------------------------- 1 file changed, 5 insertions(+), 39 deletions(-) diff --git a/compiler/coreSyn/CoreUtils.lhs b/compiler/coreSyn/CoreUtils.lhs index bb7b3e2..ea2e17f 100644 --- a/compiler/coreSyn/CoreUtils.lhs +++ b/compiler/coreSyn/CoreUtils.lhs @@ -31,7 +31,7 @@ module CoreUtils ( CoreStats(..), coreBindsStats, -- * Equality - cheapEqExpr, eqExpr, eqExprX, + cheapEqExpr, eqExpr, -- * Eta reduction tryEtaReduce, @@ -1330,43 +1330,18 @@ exprIsBig _ = True eqExpr :: InScopeSet -> CoreExpr -> CoreExpr -> Bool -- Compares for equality, modulo alpha eqExpr in_scope e1 e2 - = eqExprX id_unf (mkRnEnv2 in_scope) e1 e2 - where - id_unf _ = noUnfolding -- Don't expand -\end{code} - -\begin{code} -eqExprX :: IdUnfoldingFun -> RnEnv2 -> CoreExpr -> CoreExpr -> Bool --- ^ Compares expressions for equality, modulo alpha. --- Does /not/ look through newtypes or predicate types --- Used in rule matching, and also CSE - -eqExprX id_unfolding_fun env e1 e2 - = go env e1 e2 + = go (mkRnEnv2 in_scope) e1 e2 where go env (Var v1) (Var v2) | rnOccL env v1 == rnOccR env v2 = True - -- The next two rules expand non-local variables - -- C.f. Note [Expanding variables] in Rules.lhs - -- and Note [Do not expand locally-bound variables] in Rules.lhs - go env (Var v1) e2 - | not (locallyBoundL env v1) - , Just e1' <- expandUnfolding_maybe (id_unfolding_fun (lookupRnInScope env v1)) - = go (nukeRnEnvL env) e1' e2 - - go env e1 (Var v2) - | not (locallyBoundR env v2) - , Just e2' <- expandUnfolding_maybe (id_unfolding_fun (lookupRnInScope env v2)) - = go (nukeRnEnvR env) e1 e2' - go _ (Lit lit1) (Lit lit2) = lit1 == lit2 go env (Type t1) (Type t2) = eqTypeX env t1 t2 go env (Coercion co1) (Coercion co2) = coreEqCoercion2 env co1 co2 go env (Cast e1 co1) (Cast e2 co2) = coreEqCoercion2 env co1 co2 && go env e1 e2 go env (App f1 a1) (App f2 a2) = go env f1 f2 && go env a1 a2 - go env (Tick n1 e1) (Tick n2 e2) = go_tickish n1 n2 && go env e1 e2 + go env (Tick n1 e1) (Tick n2 e2) = go_tickish env n1 n2 && go env e1 e2 go env (Lam b1 e1) (Lam b2 e2) = eqTypeX env (varType b1) (varType b2) -- False for Id/TyVar combination @@ -1396,20 +1371,11 @@ eqExprX id_unfolding_fun env e1 e2 = c1 == c2 && go (rnBndrs2 env bs1 bs2) e1 e2 ----------- - go_tickish (Breakpoint lid lids) (Breakpoint rid rids) + go_tickish env (Breakpoint lid lids) (Breakpoint rid rids) = lid == rid && map (rnOccL env) lids == map (rnOccR env) rids - go_tickish l r = l == r -\end{code} - -Auxiliary functions - -\begin{code} -locallyBoundL, locallyBoundR :: RnEnv2 -> Var -> Bool -locallyBoundL rn_env v = inRnEnvL rn_env v -locallyBoundR rn_env v = inRnEnvR rn_env v + go_tickish _ l r = l == r \end{code} - %************************************************************************ %* * \subsection{The size of an expression} From git at git.haskell.org Tue Dec 17 23:42:28 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 17 Dec 2013 23:42:28 +0000 (UTC) Subject: [commit: ghc] branch 'wip/common-context' created Message-ID: <20131217234228.D45442406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/common-context Referencing: e009b4f1676c3ae080b59cb1e0914409e0c4660c From git at git.haskell.org Tue Dec 17 23:42:31 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 17 Dec 2013 23:42:31 +0000 (UTC) Subject: [commit: ghc] wip/common-context: New optimizaiton Common Context (95f5aac) Message-ID: <20131217234231.491282406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/common-context Link : http://ghc.haskell.org/trac/ghc/changeset/95f5aac36296bbe1583dd106fa41a1c2b855895c/ghc >--------------------------------------------------------------- commit 95f5aac36296bbe1583dd106fa41a1c2b855895c Author: Joachim Breitner Date: Tue Dec 17 22:50:03 2013 +0100 New optimizaiton Common Context with a very rouch sketch of working code, but enough to assess the consequences. >--------------------------------------------------------------- 95f5aac36296bbe1583dd106fa41a1c2b855895c compiler/ghc.cabal.in | 1 + compiler/main/DynFlags.hs | 2 + compiler/simplCore/CommonContext.lhs | 236 ++++++++++++++++++++++++++++++++++ compiler/simplCore/CoreMonad.lhs | 3 + compiler/simplCore/SimplCore.lhs | 6 + 5 files changed, 248 insertions(+) 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 95f5aac36296bbe1583dd106fa41a1c2b855895c From git at git.haskell.org Tue Dec 17 23:42:33 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 17 Dec 2013 23:42:33 +0000 (UTC) Subject: [commit: ghc] wip/common-context: Do not do common context for polymorphic functions (043af4d) Message-ID: <20131217234233.8A2512406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/common-context Link : http://ghc.haskell.org/trac/ghc/changeset/043af4d88ecfa2857519f035dea6f8dd7d0133ef/ghc >--------------------------------------------------------------- commit 043af4d88ecfa2857519f035dea6f8dd7d0133ef Author: Joachim Breitner Date: Tue Dec 17 23:27:34 2013 +0100 Do not do common context for polymorphic functions >--------------------------------------------------------------- 043af4d88ecfa2857519f035dea6f8dd7d0133ef compiler/simplCore/CommonContext.lhs | 7 +++---- 1 file changed, 3 insertions(+), 4 deletions(-) diff --git a/compiler/simplCore/CommonContext.lhs b/compiler/simplCore/CommonContext.lhs index d884cb1..9199e70 100644 --- a/compiler/simplCore/CommonContext.lhs +++ b/compiler/simplCore/CommonContext.lhs @@ -60,7 +60,7 @@ process v e body e' = mkLams bndrs fun_body' v' = setIdType v (exprType e') body' = replaceContext v v' cts body - in -- pprTrace "findInterestingLet" (vcat [ppr v, ppr (idArity v), pprConts cts, ppr body]) + in -- pprTrace "findInterestingLet" (vcat [ppr v, ppr (idArity v), pprConts cts]) (v', mkLams bndrs fun_body', body') _ -> (v, e, body) @@ -85,7 +85,6 @@ contextOf v (Var v') = NeedsArgs (idArity v) | otherwise = NoUse ---contextOf v (App f (Type _)) = finish $ contextOf v f contextOf v (App f a) = case (contextOf v f, contextOf v a) of (NoUse, NoUse) -> NoUse @@ -93,8 +92,8 @@ contextOf v (App f a) = (NoUse, Building cts) -> Building (PassTo f : cts) (NoUse, OneUse cts) -> OneUse cts (NoUse, MultiUse) -> MultiUse - (NeedsArgs 1, NoUse) -> Building [] - (NeedsArgs i, NoUse) -> NeedsArgs (i-1) + (NeedsArgs 1, NoUse) | isValArg a -> Building [] + (NeedsArgs i, NoUse) | isValArg a -> NeedsArgs (i-1) (NeedsArgs _, _) -> MultiUse (Building cts, NoUse) -> Building (AppTo a : cts) (Building _, _) -> MultiUse From git at git.haskell.org Tue Dec 17 23:42:35 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 17 Dec 2013 23:42:35 +0000 (UTC) Subject: [commit: ghc] wip/common-context: Move Common Context after CSE (e009b4f) Message-ID: <20131217234235.C726F2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/common-context Link : http://ghc.haskell.org/trac/ghc/changeset/e009b4f1676c3ae080b59cb1e0914409e0c4660c/ghc >--------------------------------------------------------------- commit e009b4f1676c3ae080b59cb1e0914409e0c4660c Author: Joachim Breitner Date: Wed Dec 18 00:11:25 2013 +0100 Move Common Context after CSE We had something like let $j = ... in case foo of ... -> case $j a b c of ... -> case foo of and moving the inner "case foo" into $j prevented CSE from happening here. (Although presumably the "let $j" could be moved inside the outer case before CSE, to give CSE a greater scope here.) >--------------------------------------------------------------- e009b4f1676c3ae080b59cb1e0914409e0c4660c compiler/simplCore/CommonContext.lhs | 2 ++ compiler/simplCore/SimplCore.lhs | 5 +++-- 2 files changed, 5 insertions(+), 2 deletions(-) diff --git a/compiler/simplCore/CommonContext.lhs b/compiler/simplCore/CommonContext.lhs index 9199e70..1cfcbe9 100644 --- a/compiler/simplCore/CommonContext.lhs +++ b/compiler/simplCore/CommonContext.lhs @@ -52,6 +52,8 @@ findInterestingLet (Let (Rec pairs) body) = process :: Var -> CoreExpr -> CoreExpr -> (Var, CoreExpr, CoreExpr) process v e body | idArity v <= 0 = (v, e, body) + -- TODO: check for non value args here. For now, ignore this let then + -- Possibly later: Check if all uses have the same type argument | otherwise = case contextOf v body of OneUse cts | not (null cts) -> diff --git a/compiler/simplCore/SimplCore.lhs b/compiler/simplCore/SimplCore.lhs index 92784d3..110c461 100644 --- a/compiler/simplCore/SimplCore.lhs +++ b/compiler/simplCore/SimplCore.lhs @@ -190,8 +190,6 @@ getCoreToDo dflags demand_analyser = (CoreDoPasses ([ CoreDoStrictness, CoreDoWorkerWrapper, - simpl_phase 0 ["post-worker-wrapper"] max_iter, - CoreCommonContext, simpl_phase 0 ["post-worker-wrapper"] max_iter ])) @@ -293,6 +291,9 @@ getCoreToDo dflags -- reduce the possiblility of shadowing -- Reason: see Note [Shadowing] in SpecConstr.lhs + CoreCommonContext, + simpl_phase 0 ["post-common-context"] max_iter, + runWhen spec_constr CoreDoSpecConstr, maybe_rule_check (Phase 0), From git at git.haskell.org Wed Dec 18 15:44:53 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 18 Dec 2013 15:44:53 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: In deferType, return convRes = Converges NoCPR (0d34150) Message-ID: <20131218154453.92E272406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/0d341509f90920d23d719ff422da41a75ac9a500/ghc >--------------------------------------------------------------- commit 0d341509f90920d23d719ff422da41a75ac9a500 Author: Joachim Breitner Date: Wed Dec 4 16:55:18 2013 +0000 In deferType, return convRes = Converges NoCPR because this is the right-identity to `bothDmdResult`, and this is the right thing to do in a lazy context. >--------------------------------------------------------------- 0d341509f90920d23d719ff422da41a75ac9a500 compiler/basicTypes/Demand.lhs | 7 ++++--- 1 file changed, 4 insertions(+), 3 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 1ece37e..2da8a2e 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -776,8 +776,9 @@ seqCPRResult RetProd = () -- [cprRes] lets us switch off CPR analysis -- by making sure that everything uses TopRes -topRes, botRes :: DmdResult +topRes, convRes, botRes :: DmdResult topRes = Dunno NoCPR +convRes = Converges NoCPR botRes = Diverges cprSumRes :: ConTag -> DmdResult @@ -1182,9 +1183,9 @@ postProcessUnsat (True, One) ty = deferType ty postProcessUnsat (False, One) ty = ty deferType, reuseType, deferReuse :: DmdType -> DmdType -deferType (DmdType fv ds _) = DmdType (deferEnv fv) (map deferDmd ds) topRes +deferType (DmdType fv ds _) = DmdType (deferEnv fv) (map deferDmd ds) convRes reuseType (DmdType fv ds res_ty) = DmdType (reuseEnv fv) (map reuseDmd ds) res_ty -deferReuse (DmdType fv ds _) = DmdType (deferReuseEnv fv) (map deferReuseDmd ds) topRes +deferReuse (DmdType fv ds _) = DmdType (deferReuseEnv fv) (map deferReuseDmd ds) convRes deferEnv, reuseEnv, deferReuseEnv :: DmdEnv -> DmdEnv deferEnv fv = mapVarEnv deferDmd fv From git at git.haskell.org Wed Dec 18 15:44:56 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 18 Dec 2013 15:44:56 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Unify RetProd and RetSum to RetCon in CPRResult (cf6f809) Message-ID: <20131218154456.3ED502406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/cf6f809e0087a0fafbfa254baf12b012d1d2261f/ghc >--------------------------------------------------------------- commit cf6f809e0087a0fafbfa254baf12b012d1d2261f Author: Joachim Breitner Date: Thu Dec 5 16:13:41 2013 +0000 Unify RetProd and RetSum to RetCon in CPRResult >--------------------------------------------------------------- cf6f809e0087a0fafbfa254baf12b012d1d2261f compiler/basicTypes/Demand.lhs | 102 ++++++++++++++++++++++------------------ compiler/basicTypes/MkId.lhs | 4 +- compiler/stranal/DmdAnal.lhs | 4 +- 3 files changed, 59 insertions(+), 51 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 cf6f809e0087a0fafbfa254baf12b012d1d2261f From git at git.haskell.org Wed Dec 18 15:44:58 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 18 Dec 2013 15:44:58 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Fix a lubDmdResult equation (1cca81a) Message-ID: <20131218154458.9A5032406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/1cca81a647fa60f1510f086c1565963d84af95e7/ghc >--------------------------------------------------------------- commit 1cca81a647fa60f1510f086c1565963d84af95e7 Author: Joachim Breitner Date: Tue Nov 26 10:17:57 2013 +0000 Fix a lubDmdResult equation >--------------------------------------------------------------- 1cca81a647fa60f1510f086c1565963d84af95e7 compiler/basicTypes/Demand.lhs | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 2548c22..5a3bbaa 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -750,8 +750,10 @@ lubCPR (RetProd ds1) (RetProd ds2) lubCPR _ _ = NoCPR lubDmdResult :: DmdResult -> DmdResult -> DmdResult -lubDmdResult Diverges r = r -lubDmdResult (Converges c1) Diverges = Converges c1 +lubDmdResult Diverges (Dunno c2) = Dunno c2 +lubDmdResult Diverges Diverges = Diverges +lubDmdResult Diverges (Converges c2) = Dunno c2 +lubDmdResult (Converges c1) Diverges = Dunno c1 lubDmdResult (Converges c1) (Converges c2) = Converges (c1 `lubCPR` c2) lubDmdResult (Converges c1) (Dunno c2) = Dunno (c1 `lubCPR` c2) lubDmdResult (Dunno c1) Diverges = Dunno c1 From git at git.haskell.org Wed Dec 18 15:45:00 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 18 Dec 2013 15:45:00 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Comments and small refactor (73c42ac) Message-ID: <20131218154500.D54022406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/73c42ac48cc1703d497f8f5704a59066978c9fe0/ghc >--------------------------------------------------------------- commit 73c42ac48cc1703d497f8f5704a59066978c9fe0 Author: Simon Peyton Jones Date: Wed Dec 4 16:00:24 2013 +0000 Comments and small refactor >--------------------------------------------------------------- 73c42ac48cc1703d497f8f5704a59066978c9fe0 compiler/basicTypes/Demand.lhs | 2 +- compiler/stranal/DmdAnal.lhs | 9 ++++++--- 2 files changed, 7 insertions(+), 4 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index a65430b..2548c22 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -559,7 +559,7 @@ splitFVs is_thunk rhs_fvs %* * %************************************************************************ -This domain differst from JointDemand in the sense that pure absence +This domain differs from JointDemand in the sense that pure absence is taken away, i.e., we deal *only* with non-absent demands. Note [Strict demands] diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index 897b5b4..f94d53d 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -530,9 +530,6 @@ dmdAnalVarApp env dmd fun args -- , ppr arg_tys, ppr cpr_info, ppr res_ty]) $ ( res_ty , foldl App (Var fun) args') - - | otherwise - = completeApp env (dmdTransform env fun (mkCallDmdN n_val_args dmd), Var fun) args where n_val_args = valArgCount args cxt_ds = splitProdCleanDmd n_val_args dmd @@ -552,6 +549,12 @@ dmdAnalVarApp env dmd fun args , (arg_tys, arg_rets, args') <- anal_con_args ds args = (arg_ty:arg_tys, arg_ret:arg_rets, arg':args') anal_con_args ds args = pprPanic "anal_con_args" (ppr args $$ ppr ds) + +dmdAnalVarApp env dmd fun args + = --pprTrace "dmdAnalVarApp" (vcat [ ppr fun, ppr args + -- , ppr $ completeApp env (dmdTransform env fun (mkCallDmdN n_val_args dmd), Var fun) args + -- ]) + completeApp env (dmdTransform env fun (mkCallDmdN (valArgCount args) dmd), Var fun) args \end{code} %************************************************************************ From git at git.haskell.org Wed Dec 18 15:45:02 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 18 Dec 2013 15:45:02 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Initial work on Nested CPR (185c459) Message-ID: <20131218154503.1C1782406F@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/185c459d6d1f434069e7bcdf00d26f9d482fb3b6/ghc >--------------------------------------------------------------- commit 185c459d6d1f434069e7bcdf00d26f9d482fb3b6 Author: Simon Peyton Jones Date: Mon Nov 25 09:59:16 2013 +0000 Initial work on Nested CPR >--------------------------------------------------------------- 185c459d6d1f434069e7bcdf00d26f9d482fb3b6 compiler/basicTypes/Demand.lhs | 137 ++++++++++++++++++++++++---------------- compiler/stranal/DmdAnal.lhs | 111 ++++++++++++++++++++++---------- 2 files changed, 160 insertions(+), 88 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 185c459d6d1f434069e7bcdf00d26f9d482fb3b6 From git at git.haskell.org Wed Dec 18 15:45:05 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 18 Dec 2013 15:45:05 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Add Converges to DmdResult (d11e3d2) Message-ID: <20131218154505.AA87C2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/d11e3d24872e2fbd37f7507e252b4d1611cfcb79/ghc >--------------------------------------------------------------- commit d11e3d24872e2fbd37f7507e252b4d1611cfcb79 Author: Joachim Breitner Date: Thu Dec 12 15:45:19 2013 +0000 Add Converges to DmdResult to detect definite convergence (required for nested CPR). >--------------------------------------------------------------- d11e3d24872e2fbd37f7507e252b4d1611cfcb79 compiler/basicTypes/Demand.lhs | 41 ++++++++++++++++++++++++++++------------ 1 file changed, 29 insertions(+), 12 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index d408e6d..1ece37e 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -691,8 +691,8 @@ splitProdDmd_maybe (JD {strd = s, absd = u}) DmdResult: Dunno CPRResult - / - Diverges + / \ + Diverges Converges CPRResult CPRResult: NoCPR @@ -700,7 +700,7 @@ CPRResult: NoCPR RetProd RetSum ConTag -Product contructors return (Dunno (RetProd rs)) +Product contructors return (Converges (RetProd rs)) In a fixpoint iteration, start from Diverges We have lubs, but not glbs; but that is ok. @@ -711,6 +711,7 @@ We have lubs, but not glbs; but that is ok. ------------------------------------------------------------------------ data Termination r = Diverges -- Definitely diverges + | Converges r -- Definitely converges | Dunno r -- Might diverge or converge deriving( Eq, Show ) @@ -729,7 +730,11 @@ lubCPR _ _ = NoCPR lubDmdResult :: DmdResult -> DmdResult -> DmdResult lubDmdResult Diverges r = r +lubDmdResult (Converges c1) Diverges = Converges c1 +lubDmdResult (Converges c1) (Converges c2) = Converges (c1 `lubCPR` c2) +lubDmdResult (Converges c1) (Dunno c2) = Dunno (c1 `lubCPR` c2) lubDmdResult (Dunno c1) Diverges = Dunno c1 +lubDmdResult (Dunno c1) (Converges c2) = Dunno (c1 `lubCPR` c2) lubDmdResult (Dunno c1) (Dunno c2) = Dunno (c1 `lubCPR` c2) -- This needs to commute with defaultDmd, i.e. -- defaultDmd (r1 `lubDmdResult` r2) = defaultDmd r1 `lubDmd` defaultDmd r2 @@ -738,6 +743,7 @@ lubDmdResult (Dunno c1) (Dunno c2) = Dunno (c1 `lubCPR` c2) bothDmdResult :: DmdResult -> Termination () -> DmdResult -- See Note [Asymmetry of 'both' for DmdType and DmdResult] bothDmdResult _ Diverges = Diverges +bothDmdResult (Converges c1) (Dunno {}) = Dunno c1 bothDmdResult r _ = r -- This needs to commute with defaultDmd, i.e. -- defaultDmd (r1 `bothDmdResult` r2) = defaultDmd r1 `bothDmd` defaultDmd r2 @@ -745,6 +751,7 @@ bothDmdResult r _ = r instance Outputable DmdResult where ppr Diverges = char 'b' + ppr (Converges c) = char 't' <> ppr c ppr (Dunno c) = ppr c instance Outputable CPRResult where @@ -754,6 +761,7 @@ instance Outputable CPRResult where seqDmdResult :: DmdResult -> () seqDmdResult Diverges = () +seqDmdResult (Converges c) = seqCPRResult c seqDmdResult (Dunno c) = seqCPRResult c seqCPRResult :: CPRResult -> () @@ -774,17 +782,17 @@ botRes = Diverges cprSumRes :: ConTag -> DmdResult cprSumRes tag | opt_CprOff = topRes - | otherwise = Dunno $ RetSum tag + | otherwise = Converges $ RetSum tag cprProdRes :: [DmdType] -> DmdResult cprProdRes _arg_tys | opt_CprOff = topRes - | otherwise = Dunno $ RetProd + | otherwise = Converges $ RetProd vanillaCprProdRes :: Arity -> DmdResult vanillaCprProdRes _arity | opt_CprOff = topRes - | otherwise = Dunno $ RetProd + | otherwise = Converges $ RetProd isTopRes :: DmdResult -> Bool isTopRes (Dunno NoCPR) = True @@ -798,6 +806,7 @@ trimCPRInfo :: Bool -> Bool -> DmdResult -> DmdResult trimCPRInfo trim_all trim_sums res = trimR res where + trimR (Converges c) = Converges (trimC c) trimR (Dunno c) = Dunno (trimC c) trimR Diverges = Diverges @@ -811,6 +820,7 @@ returnsCPR :: DmdResult -> Bool returnsCPR dr = isJust (returnsCPR_maybe dr) returnsCPR_maybe :: DmdResult -> Maybe ConTag +returnsCPR_maybe (Converges c) = retCPR_maybe c returnsCPR_maybe (Dunno c) = retCPR_maybe c returnsCPR_maybe Diverges = Nothing @@ -1036,6 +1046,7 @@ toBothDmdArg :: DmdType -> BothDmdArg toBothDmdArg (DmdType fv _ r) = (fv, go r) where go (Dunno {}) = Dunno () + go (Converges {}) = Converges () go Diverges = Diverges bothDmdType :: DmdType -> BothDmdArg -> DmdType @@ -1069,7 +1080,7 @@ botDmdType = DmdType emptyDmdEnv [] botRes cprProdDmdType :: Arity -> DmdType cprProdDmdType _arity - = DmdType emptyDmdEnv [] (Dunno RetProd) + = DmdType emptyDmdEnv [] (Converges RetProd) isNopDmdType :: DmdType -> Bool isNopDmdType (DmdType env [] res) @@ -1098,7 +1109,7 @@ splitDmdTy ty@(DmdType _ [] res_ty) = (resTypeArgDmd res_ty, ty) -- exit? -- * We have to kill all strictness demands (i.e. lub with a lazy demand) -- * We can keep demand information (i.e. lub with an absent deman) --- * We have to kill definite divergence +-- * We have to kill definite divergence and definite convergence -- * We can keep CPR information. -- See Note [IO hack in the demand analyser] deferAfterIO :: DmdType -> DmdType @@ -1107,6 +1118,7 @@ deferAfterIO d@(DmdType _ _ res) = DmdType fv ds _ -> DmdType fv ds (defer_res res) where defer_res Diverges = topRes + defer_res (Converges r) = Dunno r defer_res r = r strictenDmd :: JointDmd -> CleanDemand @@ -1149,9 +1161,12 @@ postProcessDmdTypeM (Just du) (DmdType fv _ res_ty) = (postProcessDmdEnv du fv, postProcessDmdResult du res_ty) postProcessDmdResult :: DeferAndUse -> DmdResult -> Termination () -postProcessDmdResult (True,_) _ = Dunno () -postProcessDmdResult (False,_) (Dunno {}) = Dunno () -postProcessDmdResult (False,_) Diverges = Diverges + -- if we use it lazily, there cannot be divergence worrying us + -- (Otherwise we'd lose the termination information of constructors in in dmdAnalVarApp, for example) +postProcessDmdResult (True,_) _ = Converges () +postProcessDmdResult (False,_) (Dunno {}) = Dunno () +postProcessDmdResult (False,_) (Converges {}) = Converges () +postProcessDmdResult (False,_) Diverges = Diverges postProcessDmdEnv :: DeferAndUse -> DmdEnv -> DmdEnv postProcessDmdEnv (True, Many) env = deferReuseEnv env @@ -1720,11 +1735,13 @@ instance Binary DmdType where instance Binary DmdResult where put_ bh (Dunno c) = do { putByte bh 0; put_ bh c } - put_ bh Diverges = putByte bh 2 + put_ bh (Converges c) = do { putByte bh 1; put_ bh c } + put_ bh Diverges = putByte bh 3 get bh = do { h <- getByte bh ; case h of 0 -> do { c <- get bh; return (Dunno c) } + 1 -> do { c <- get bh; return (Converges c) } _ -> return Diverges } instance Binary CPRResult where From git at git.haskell.org Wed Dec 18 15:45:08 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 18 Dec 2013 15:45:08 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Use isTypeArg instead of isTyCoArg (forgot why) (29a140a) Message-ID: <20131218154508.A7D962406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/29a140ad2aa6ed33ed1b940bbbec756a822e487f/ghc >--------------------------------------------------------------- commit 29a140ad2aa6ed33ed1b940bbbec756a822e487f Author: Joachim Breitner Date: Thu Dec 5 16:14:07 2013 +0000 Use isTypeArg instead of isTyCoArg (forgot why) >--------------------------------------------------------------- 29a140ad2aa6ed33ed1b940bbbec756a822e487f compiler/stranal/DmdAnal.lhs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index cb5aa4a..0da1085 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -509,7 +509,7 @@ completeApp :: AnalEnv completeApp _ fun_ty_fun [] = fun_ty_fun completeApp env (fun_ty, fun') (arg:args) - | isTyCoArg arg = completeApp env (fun_ty, App fun' arg) args + | isTypeArg arg = completeApp env (fun_ty, App fun' arg) args | otherwise = completeApp env (res_ty `bothDmdType` arg_ty, App fun' arg') args where (arg_dmd, res_ty) = splitDmdTy fun_ty From git at git.haskell.org Wed Dec 18 15:45:10 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 18 Dec 2013 15:45:10 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Add a flag -fnested-cpr-off to conveniently test the effect of nested CPR (d0fc628) Message-ID: <20131218154511.238CB2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/d0fc6283e0e1da704c2b0d6f5d4beeef85580d67/ghc >--------------------------------------------------------------- commit d0fc6283e0e1da704c2b0d6f5d4beeef85580d67 Author: Joachim Breitner Date: Wed Dec 4 09:14:26 2013 +0000 Add a flag -fnested-cpr-off to conveniently test the effect of nested CPR >--------------------------------------------------------------- d0fc6283e0e1da704c2b0d6f5d4beeef85580d67 compiler/basicTypes/Demand.lhs | 29 ++++++++++++++++++++--------- compiler/main/StaticFlags.hs | 9 +++++++-- 2 files changed, 27 insertions(+), 11 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index a09f258..c6e26f4 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -807,19 +807,29 @@ getDmdResult _ = topRes maxCPRDepth :: Int maxCPRDepth = 3 +-- This is the depth we use with -fnested-cpr-off, in order +-- to get precisely the same behaviour as before introduction of nested cpr +-- -fnested-cpr-off can eventually be removed if nested cpr is deemd to be +-- a good thing always. +flatCPRDepth :: Int +flatCPRDepth = 1 + -- With nested CPR, DmdResult can be arbitrarily deep; consider e.g. the -- DmdResult of repeat +-- -- So we need to forget information at a certain depth. We do that at all points -- where we are building RetCon constructors. -cutDmdResult :: Int -> DmdResult -> DmdResult -cutDmdResult 0 _ = topRes -cutDmdResult _ Diverges = Diverges -cutDmdResult n (Converges c) = Converges (cutCPRResult n c) -cutDmdResult n (Dunno c) = Dunno (cutCPRResult n c) - cutCPRResult :: Int -> CPRResult -> CPRResult -cutCPRResult _ NoCPR = NoCPR +cutCPRResult 0 _ = NoCPR +cutCPRResult _ NoCPR = NoCPR cutCPRResult n (RetCon tag rs) = RetCon tag (map (cutDmdResult (n-1)) rs) + where + cutDmdResult :: Int -> DmdResult -> DmdResult + cutDmdResult 0 _ = topRes + cutDmdResult _ Diverges = Diverges + cutDmdResult n (Converges c) = Converges (cutCPRResult n c) + cutDmdResult n (Dunno c) = Dunno (cutCPRResult n c) + -- Forget that something might converge for sure divergeDmdResult :: DmdResult -> DmdResult @@ -834,8 +844,9 @@ forgetCPR (Dunno _) = Dunno NoCPR cprConRes :: ConTag -> [DmdResult] -> DmdResult cprConRes tag arg_ress - | opt_CprOff = topRes - | otherwise = Converges $ cutCPRResult maxCPRDepth $ RetCon tag arg_ress + | opt_CprOff = topRes + | opt_NestedCprOff = Converges $ cutCPRResult flatCPRDepth $ RetCon tag arg_ress + | otherwise = Converges $ cutCPRResult maxCPRDepth $ RetCon tag arg_ress vanillaCprConRes :: ConTag -> Arity -> DmdResult vanillaCprConRes tag arity diff --git a/compiler/main/StaticFlags.hs b/compiler/main/StaticFlags.hs index 01dc3b7..feb7235 100644 --- a/compiler/main/StaticFlags.hs +++ b/compiler/main/StaticFlags.hs @@ -27,6 +27,7 @@ module StaticFlags ( -- optimisation opts opt_NoStateHack, opt_CprOff, + opt_NestedCprOff, opt_NoOptCoercion, -- For the parser @@ -140,7 +141,8 @@ flagsStaticNames :: [String] flagsStaticNames = [ "fno-state-hack", "fno-opt-coercion", - "fcpr-off" + "fcpr-off", + "fnested-cpr-off" ] -- We specifically need to discard static flags for clients of the @@ -195,10 +197,13 @@ opt_NoDebugOutput = lookUp (fsLit "-dno-debug-output") opt_NoStateHack :: Bool opt_NoStateHack = lookUp (fsLit "-fno-state-hack") --- Switch off CPR analysis in the new demand analyser +-- Switch off CPR analysis in the demand analyser opt_CprOff :: Bool opt_CprOff = lookUp (fsLit "-fcpr-off") +opt_NestedCprOff :: Bool +opt_NestedCprOff = lookUp (fsLit "-fnested-cpr-off") + opt_NoOptCoercion :: Bool opt_NoOptCoercion = lookUp (fsLit "-fno-opt-coercion") From git at git.haskell.org Wed Dec 18 15:45:13 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 18 Dec 2013 15:45:13 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Temporarily disable nested CPR inside sum types (f28790e) Message-ID: <20131218154513.83C342406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/f28790e43f407905dcbb17c6c7e57c02ff3059c4/ghc >--------------------------------------------------------------- commit f28790e43f407905dcbb17c6c7e57c02ff3059c4 Author: Joachim Breitner Date: Tue Dec 10 10:12:46 2013 +0000 Temporarily disable nested CPR inside sum types >--------------------------------------------------------------- f28790e43f407905dcbb17c6c7e57c02ff3059c4 compiler/basicTypes/Demand.lhs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 2532cf1..c66f2be 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -865,7 +865,7 @@ cprConRes isProd tag arg_ress | opt_NestedCprOff = Converges $ cutCPRResult flatCPRDepth $ retCon arg_ress | otherwise = Converges $ cutCPRResult maxCPRDepth $ retCon arg_ress where retCon | isProd = RetProd - | otherwise = RetSum tag + | otherwise = RetSum tag . map (const topRes) vanillaCprConRes :: Bool -> ConTag -> Arity -> DmdResult vanillaCprConRes isProd tag arity = cprConRes isProd tag (replicate arity topRes) From git at git.haskell.org Wed Dec 18 15:45:15 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 18 Dec 2013 15:45:15 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Recover [CPR for sum types] (slightly differently) (414476f) Message-ID: <20131218154516.038812406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/414476f227e1d4865e1b480eac70669e5558fc76/ghc >--------------------------------------------------------------- commit 414476f227e1d4865e1b480eac70669e5558fc76 Author: Joachim Breitner Date: Thu Nov 28 11:17:16 2013 +0000 Recover [CPR for sum types] (slightly differently) >--------------------------------------------------------------- 414476f227e1d4865e1b480eac70669e5558fc76 compiler/basicTypes/Demand.lhs | 24 ++++++++---------------- compiler/stranal/DmdAnal.lhs | 14 ++++++++------ 2 files changed, 16 insertions(+), 22 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 2309282..47cd9d3 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -30,10 +30,9 @@ module Demand ( isBotRes, isTopRes, getDmdResult, resTypeArgDmd, topRes, botRes, cprConRes, vanillaCprConRes, appIsBottom, isBottomingSig, pprIfaceStrictSig, - trimCPRInfo, returnsCPR, returnsCPR_maybe, + returnsCPR, returnsCPR_maybe, forgetCPR, StrictSig(..), mkStrictSig, mkClosedStrictSig, nopSig, botSig, cprProdSig, isNopSig, splitStrictSig, increaseStrictSigArity, - seqDemand, seqDemandList, seqDmdType, seqStrictSig, evalDmd, cleanEvalDmd, cleanEvalProdDmd, isStrictDmd, @@ -826,6 +825,13 @@ cutCPRResult :: Int -> CPRResult -> CPRResult cutCPRResult _ NoCPR = NoCPR cutCPRResult n (RetCon tag rs) = RetCon tag (map (cutDmdResult (n-1)) rs) +-- Forget the CPR information, but remember if it converges or diverges +-- Used for non-strict thunks and non-top-level things with sum type +forgetCPR :: DmdResult -> DmdResult +forgetCPR Diverges = Diverges +forgetCPR (Converges _) = Converges NoCPR +forgetCPR (Dunno _) = Dunno NoCPR + cprConRes :: ConTag -> [DmdResult] -> DmdResult cprConRes tag arg_ress | opt_CprOff = topRes @@ -844,20 +850,6 @@ isBotRes :: DmdResult -> Bool isBotRes Diverges = True isBotRes _ = False --- TODO: This currently ignores trim_sums. Evaluate if still required, and fix --- Note [CPR for sum types] -trimCPRInfo :: Bool -> Bool -> DmdResult -> DmdResult -trimCPRInfo trim_all _trim_sums res - = trimR res - where - trimR (Converges c) = Converges (trimC c) - trimR (Dunno c) = Dunno (trimC c) - trimR Diverges = Diverges - - trimC (RetCon n rs) | trim_all = NoCPR - | otherwise = RetCon n (map trimR rs) - trimC NoCPR = NoCPR - returnsCPR :: DmdResult -> Bool returnsCPR dr = isJust (returnsCPR_maybe dr) diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index 0da1085..ea1a588 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -655,9 +655,10 @@ dmdAnalRhs top_lvl rec_flag env id rhs -- See Note [NOINLINE and strictness] -- See Note [Product demands for function body] - body_dmd = case deepSplitProductType_maybe (exprType body) of - Nothing -> cleanEvalDmd - Just (dc, _, _, _) -> cleanEvalProdDmd (dataConRepArity dc) + (is_sum_type, body_dmd) + = case deepSplitProductType_maybe (exprType body) of + Nothing -> (True, cleanEvalDmd) + Just (dc, _, _, _) -> (False, cleanEvalProdDmd (dataConRepArity dc)) -- See Note [Lazy and unleashable free variables] -- See Note [Aggregated demand for cardinality] @@ -667,9 +668,10 @@ dmdAnalRhs top_lvl rec_flag env id rhs (lazy_fv, sig_fv) = splitFVs is_thunk rhs_fv1 - rhs_res' = trimCPRInfo trim_all trim_sums rhs_res - trim_all = is_thunk && not_strict - trim_sums = not (isTopLevel top_lvl) -- See Note [CPR for sum types] + -- Note [CPR for sum types] + rhs_res' | (is_sum_type && not (isTopLevel top_lvl)) || + (is_thunk && not_strict) = forgetCPR rhs_res + | otherwise = rhs_res -- See Note [CPR for thunks] is_thunk = not (exprIsHNF rhs) From git at git.haskell.org Wed Dec 18 15:45:18 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 18 Dec 2013 15:45:18 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Loop breakers are not allowed to have a Converges DmdResult (14a40f2) Message-ID: <20131218154519.F189B2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/14a40f20f867dfcac821324ec29c26646c7c79b7/ghc >--------------------------------------------------------------- commit 14a40f20f867dfcac821324ec29c26646c7c79b7 Author: Joachim Breitner Date: Tue Nov 26 10:18:35 2013 +0000 Loop breakers are not allowed to have a Converges DmdResult >--------------------------------------------------------------- 14a40f20f867dfcac821324ec29c26646c7c79b7 compiler/basicTypes/Demand.lhs | 19 +++++++++++-------- compiler/stranal/DmdAnal.lhs | 5 ++++- 2 files changed, 15 insertions(+), 9 deletions(-) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index 47cd9d3..a09f258 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -33,6 +33,7 @@ module Demand ( returnsCPR, returnsCPR_maybe, forgetCPR, StrictSig(..), mkStrictSig, mkClosedStrictSig, nopSig, botSig, cprProdSig, isNopSig, splitStrictSig, increaseStrictSigArity, + sigMayConverge, seqDemand, seqDemandList, seqDmdType, seqStrictSig, evalDmd, cleanEvalDmd, cleanEvalProdDmd, isStrictDmd, @@ -806,15 +807,10 @@ getDmdResult _ = topRes maxCPRDepth :: Int maxCPRDepth = 3 --- With nested CPR, DmdResult can be arbitrarily deep; consider --- data Rec1 = Foo Rec2 Rec2 --- data Rec2 = Bar Rec1 Rec1 --- --- x = Foo y y --- y = Bar x x --- +-- With nested CPR, DmdResult can be arbitrarily deep; consider e.g. the +-- DmdResult of repeat -- So we need to forget information at a certain depth. We do that at all points --- where we are constructing new RetCon constructors. +-- where we are building RetCon constructors. cutDmdResult :: Int -> DmdResult -> DmdResult cutDmdResult 0 _ = topRes cutDmdResult _ Diverges = Diverges @@ -825,6 +821,10 @@ cutCPRResult :: Int -> CPRResult -> CPRResult cutCPRResult _ NoCPR = NoCPR cutCPRResult n (RetCon tag rs) = RetCon tag (map (cutDmdResult (n-1)) rs) +-- Forget that something might converge for sure +divergeDmdResult :: DmdResult -> DmdResult +divergeDmdResult r = r `lubDmdResult` botRes + -- Forget the CPR information, but remember if it converges or diverges -- Used for non-strict thunks and non-top-level things with sum type forgetCPR :: DmdResult -> DmdResult @@ -1445,6 +1445,9 @@ botSig = StrictSig botDmdType cprProdSig :: Arity -> StrictSig cprProdSig arity = StrictSig (cprProdDmdType arity) +sigMayConverge :: StrictSig -> StrictSig +sigMayConverge (StrictSig (DmdType env ds res)) = (StrictSig (DmdType env ds (divergeDmdResult res))) + argsOneShots :: StrictSig -> Arity -> [[OneShotInfo]] argsOneShots (StrictSig (DmdType _ arg_ds _)) n_val_args = go arg_ds diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index ea1a588..d5bf8a0 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -1084,7 +1084,10 @@ updSigEnv env sigs = env { ae_sigs = sigs } extendAnalEnv :: TopLevelFlag -> AnalEnv -> Id -> StrictSig -> AnalEnv extendAnalEnv top_lvl env var sig - = env { ae_sigs = extendSigEnv top_lvl (ae_sigs env) var sig } + = env { ae_sigs = extendSigEnv top_lvl (ae_sigs env) var sig' } + where + sig' | isWeakLoopBreaker (idOccInfo var) = sigMayConverge sig + | otherwise = sig extendSigEnv :: TopLevelFlag -> SigEnv -> Id -> StrictSig -> SigEnv extendSigEnv top_lvl sigs var sig = extendVarEnv sigs var (sig, top_lvl) From git at git.haskell.org Wed Dec 18 15:45:20 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 18 Dec 2013 15:45:20 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Actually create a nested CPR worker-wrapper (a6f8d61) Message-ID: <20131218154520.88F8D2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/a6f8d6133e4c9b9cdaf3be6aa0500d2f5614551e/ghc >--------------------------------------------------------------- commit a6f8d6133e4c9b9cdaf3be6aa0500d2f5614551e Author: Joachim Breitner Date: Thu Dec 5 18:58:07 2013 +0000 Actually create a nested CPR worker-wrapper >--------------------------------------------------------------- a6f8d6133e4c9b9cdaf3be6aa0500d2f5614551e compiler/basicTypes/Demand.lhs | 15 +++-- compiler/stranal/WwLib.lhs | 141 +++++++++++++++++++++++++--------------- 2 files changed, 95 insertions(+), 61 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 a6f8d6133e4c9b9cdaf3be6aa0500d2f5614551e From git at git.haskell.org Wed Dec 18 15:45:22 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 18 Dec 2013 15:45:22 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Allow the CPR w/w to take unboxed tuples apart (09d44a3) Message-ID: <20131218154522.C29FC2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/09d44a3365f1238adc084adc6f1c414a2bc6769f/ghc >--------------------------------------------------------------- commit 09d44a3365f1238adc084adc6f1c414a2bc6769f Author: Joachim Breitner Date: Thu Nov 28 10:29:47 2013 +0000 Allow the CPR w/w to take unboxed tuples apart >--------------------------------------------------------------- 09d44a3365f1238adc084adc6f1c414a2bc6769f compiler/stranal/WwLib.lhs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/stranal/WwLib.lhs b/compiler/stranal/WwLib.lhs index ce4112c..5168d8f 100644 --- a/compiler/stranal/WwLib.lhs +++ b/compiler/stranal/WwLib.lhs @@ -502,7 +502,7 @@ deepSplitCprType_maybe :: ConTag -> Type -> Maybe (DataCon, [Type], [Type], Coer deepSplitCprType_maybe con_tag ty | let (co, ty1) = topNormaliseNewType_maybe ty `orElse` (mkReflCo Representational ty, ty) , Just (tc, tc_args) <- splitTyConApp_maybe ty1 - , isDataTyCon tc + , isDataTyCon tc || isUnboxedTupleTyCon tc , let cons = tyConDataCons tc con = ASSERT( cons `lengthAtLeast` con_tag ) cons !! (con_tag - fIRST_TAG) = Just (con, tc_args, dataConInstArgTys con tc_args, co) From git at git.haskell.org Wed Dec 18 15:45:25 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 18 Dec 2013 15:45:25 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: in Demand.lhs, remember what is a sum type (17a07e1) Message-ID: <20131218154525.745CC2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/17a07e167edd86815ca79fe006c2c8e80ebb1e6b/ghc >--------------------------------------------------------------- commit 17a07e167edd86815ca79fe006c2c8e80ebb1e6b Author: Joachim Breitner Date: Tue Dec 10 09:15:09 2013 +0000 in Demand.lhs, remember what is a sum type because we want to zap CPR information for sum types not only on the outermost level, but also nested. See Note [CPR for sum types] This comes up in sublist in Listplikefns in nofib?s boyer2. >--------------------------------------------------------------- 17a07e167edd86815ca79fe006c2c8e80ebb1e6b compiler/basicTypes/DataCon.lhs | 4 +++ compiler/basicTypes/Demand.lhs | 76 ++++++++++++++++++++++++--------------- compiler/basicTypes/MkId.lhs | 2 +- compiler/stranal/DmdAnal.lhs | 39 ++++++++++++-------- 4 files changed, 77 insertions(+), 44 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 17a07e167edd86815ca79fe006c2c8e80ebb1e6b From git at git.haskell.org Wed Dec 18 15:45:27 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 18 Dec 2013 15:45:27 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Check mAX_CPR_SIZE in dmdAnalVarApp (478de44) Message-ID: <20131218154527.9DFB92406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/478de441f93682cb609aede9486f0be0c4c65df6/ghc >--------------------------------------------------------------- commit 478de441f93682cb609aede9486f0be0c4c65df6 Author: Joachim Breitner Date: Thu Dec 5 18:01:34 2013 +0000 Check mAX_CPR_SIZE in dmdAnalVarApp >--------------------------------------------------------------- 478de441f93682cb609aede9486f0be0c4c65df6 compiler/stranal/DmdAnal.lhs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs index d5bf8a0..3c613b2 100644 --- a/compiler/stranal/DmdAnal.lhs +++ b/compiler/stranal/DmdAnal.lhs @@ -522,6 +522,8 @@ dmdAnalVarApp env dmd fun args | Just con <- isDataConWorkId_maybe fun -- Data constructor , isVanillaDataCon con , n_val_args == dataConRepArity con -- Saturated + , dataConRepArity con > 0 + , dataConRepArity con < 10 -- TODO: Sync with mAX_CPR_SIZE in MkId , let cpr_info = cprConRes (dataConTag con) arg_rets res_ty = foldl bothDmdType (DmdType emptyDmdEnv [] cpr_info) arg_tys = -- pprTrace "dmdAnalVarApp" (vcat [ ppr con, ppr args, ppr n_val_args, ppr cxt_ds From git at git.haskell.org Wed Dec 18 15:45:29 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 18 Dec 2013 15:45:29 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr: Add a warning to dmdTransformDataConSig (which I believe is dead code) (c679e8d) Message-ID: <20131218154532.0988E2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/nested-cpr Link : http://ghc.haskell.org/trac/ghc/changeset/c679e8d5ade72abcf7d847b2cc222775be1b5fba/ghc >--------------------------------------------------------------- commit c679e8d5ade72abcf7d847b2cc222775be1b5fba Author: Joachim Breitner Date: Tue Dec 10 13:56:08 2013 +0000 Add a warning to dmdTransformDataConSig (which I believe is dead code) >--------------------------------------------------------------- c679e8d5ade72abcf7d847b2cc222775be1b5fba compiler/basicTypes/Demand.lhs | 1 + 1 file changed, 1 insertion(+) diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs index c66f2be..b7f2476 100644 --- a/compiler/basicTypes/Demand.lhs +++ b/compiler/basicTypes/Demand.lhs @@ -1519,6 +1519,7 @@ dmdTransformDataConSig arity (StrictSig (DmdType _ _ con_res)) (CD { sd = str, ud = abs }) | Just str_dmds <- go_str arity str , Just abs_dmds <- go_abs arity abs + , WARN( True, text "dmdTransformDataConSig indeed still in use" ) True = DmdType emptyDmdEnv (mkJointDmds str_dmds abs_dmds) con_res -- Must remember whether it's a product, hence con_res, not TopRes From git at git.haskell.org Wed Dec 18 15:45:32 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 18 Dec 2013 15:45:32 +0000 (UTC) Subject: [commit: ghc] wip/nested-cpr's head updated: Add a warning to dmdTransformDataConSig (which I believe is dead code) (c679e8d) Message-ID: <20131218154532.2CBA324069@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/nested-cpr' now includes: 24eafd2 Refactor peelManyCalls 72b6224 Disentangle postProcessDmdTypeM and postProcessUnsat 0e2fd36 Make types of bothDmdType more precise d11e3d2 Add Converges to DmdResult 0d34150 In deferType, return convRes = Converges NoCPR 185c459 Initial work on Nested CPR 73c42ac Comments and small refactor 1cca81a Fix a lubDmdResult equation cf6f809 Unify RetProd and RetSum to RetCon in CPRResult 29a140a Use isTypeArg instead of isTyCoArg (forgot why) 414476f Recover [CPR for sum types] (slightly differently) 14a40f2 Loop breakers are not allowed to have a Converges DmdResult 478de44 Check mAX_CPR_SIZE in dmdAnalVarApp d0fc628 Add a flag -fnested-cpr-off to conveniently test the effect of nested CPR a6f8d61 Actually create a nested CPR worker-wrapper 17a07e1 in Demand.lhs, remember what is a sum type f28790e Temporarily disable nested CPR inside sum types 09d44a3 Allow the CPR w/w to take unboxed tuples apart c679e8d Add a warning to dmdTransformDataConSig (which I believe is dead code) From git at git.haskell.org Fri Dec 27 03:39:36 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Dec 2013 03:39:36 +0000 (UTC) Subject: [commit: ghc] master: Revert "Simplify the plumbing for checkValidTyCl" (724690f) Message-ID: <20131227033936.3CA4D2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/724690f86f9bf92e886a785141c9ef423ddae05e/ghc >--------------------------------------------------------------- commit 724690f86f9bf92e886a785141c9ef423ddae05e Author: Richard Eisenberg Date: Wed Dec 18 14:58:12 2013 -0500 Revert "Simplify the plumbing for checkValidTyCl" This reverts commit 174577912de7a21b8fe01881a28f5aafce02b92e. This is part of the fix for #8607. Only reverting RdrHsSyn.lhs. Conflicts: compiler/parser/RdrHsSyn.lhs compiler/typecheck/TcTyClsDecls.lhs >--------------------------------------------------------------- 724690f86f9bf92e886a785141c9ef423ddae05e compiler/parser/RdrHsSyn.lhs | 15 ++++----------- 1 file changed, 4 insertions(+), 11 deletions(-) diff --git a/compiler/parser/RdrHsSyn.lhs b/compiler/parser/RdrHsSyn.lhs index 79e53b2..79d2d96 100644 --- a/compiler/parser/RdrHsSyn.lhs +++ b/compiler/parser/RdrHsSyn.lhs @@ -127,7 +127,7 @@ mkClassDecl loc (L _ (mcxt, tycl_hdr)) fds where_cls ; (cls, tparams) <- checkTyClHdr tycl_hdr ; tyvars <- checkTyVars (ptext (sLit "class")) whereDots cls tparams -- Only type vars allowed - ; return (L loc (ClassDecl { tcdCtxt = cxt, tcdLName = reLocate loc cls, tcdTyVars = tyvars, + ; return (L loc (ClassDecl { tcdCtxt = cxt, tcdLName = cls, tcdTyVars = tyvars, tcdFDs = unLoc fds, tcdSigs = sigs, tcdMeths = binds, tcdATs = ats, tcdATDefs = at_defs, tcdDocs = docs, tcdFVs = placeHolderNames })) } @@ -144,7 +144,7 @@ mkTyData loc new_or_data cType (L _ (mcxt, tycl_hdr)) ksig data_cons maybe_deriv = do { (tc, tparams) <- checkTyClHdr tycl_hdr ; tyvars <- checkTyVars (ppr new_or_data) equalsDots tc tparams ; defn <- mkDataDefn new_or_data cType mcxt ksig data_cons maybe_deriv - ; return (L loc (DataDecl { tcdLName = reLocate loc tc, tcdTyVars = tyvars, + ; return (L loc (DataDecl { tcdLName = tc, tcdTyVars = tyvars, tcdDataDefn = defn, tcdFVs = placeHolderNames })) } @@ -171,7 +171,7 @@ mkTySynonym :: SrcSpan mkTySynonym loc lhs rhs = do { (tc, tparams) <- checkTyClHdr lhs ; tyvars <- checkTyVars (ptext (sLit "type")) equalsDots tc tparams - ; return (L loc (SynDecl { tcdLName = reLocate loc tc, tcdTyVars = tyvars + ; return (L loc (SynDecl { tcdLName = tc, tcdTyVars = tyvars , tcdRhs = rhs, tcdFVs = placeHolderNames })) } mkTyFamInstEqn :: LHsType RdrName @@ -213,7 +213,7 @@ mkFamDecl :: SrcSpan mkFamDecl loc info lhs ksig = do { (tc, tparams) <- checkTyClHdr lhs ; tyvars <- checkTyVars (ppr info) equals_or_where tc tparams - ; return (L loc (FamDecl (FamilyDecl { fdInfo = info, fdLName = reLocate loc tc + ; return (L loc (FamDecl (FamilyDecl { fdInfo = info, fdLName = tc , fdTyVars = tyvars, fdKindSig = ksig }))) } where equals_or_where = case info of @@ -221,13 +221,6 @@ mkFamDecl loc info lhs ksig OpenTypeFamily -> empty ClosedTypeFamily {} -> whereDots -reLocate :: SrcSpan -> Located a -> Located a --- For the main binder of a declaration, we make its SrcSpan to --- cover the whole declaration, rather than just the syntactic occurrence --- of the binder. This makes error messages refer to the declaration as --- a whole, rather than just the binding site -reLocate loc (L _ x) = L loc x - mkSpliceDecl :: LHsExpr RdrName -> HsDecl RdrName -- If the user wrote -- [pads| ... ] then return a QuasiQuoteD From git at git.haskell.org Fri Dec 27 03:39:38 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Dec 2013 03:39:38 +0000 (UTC) Subject: [commit: ghc] master: Fix #8607. (e4afeed) Message-ID: <20131227033938.B4A9C2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e4afeedc5b8ac0f48cbeac09aa702c8d10433cdb/ghc >--------------------------------------------------------------- commit e4afeedc5b8ac0f48cbeac09aa702c8d10433cdb Author: Richard Eisenberg Date: Thu Dec 26 22:34:03 2013 -0500 Fix #8607. The solution (after many false starts) is to change the behavior of hsLTyClDeclBinders. The idea is that the locations of the names that the parser generates should really be the names' locations, unlike what was done in 1745779... But, when the renamer is creating Names from the RdrNames, the locations stored in the Names should be the declarations' locations. This is now achieved in hsLTyClDeclBinders, which returns [Located name], but the location is that of the *declaration*, not the name itself. >--------------------------------------------------------------- e4afeedc5b8ac0f48cbeac09aa702c8d10433cdb compiler/hsSyn/HsUtils.lhs | 52 +++++++++++++++++++++++-------------------- compiler/rename/RnEnv.lhs | 1 - compiler/rename/RnNames.lhs | 10 ++++++--- 3 files changed, 35 insertions(+), 28 deletions(-) diff --git a/compiler/hsSyn/HsUtils.lhs b/compiler/hsSyn/HsUtils.lhs index bdbb5d4..bdc77c0 100644 --- a/compiler/hsSyn/HsUtils.lhs +++ b/compiler/hsSyn/HsUtils.lhs @@ -68,7 +68,7 @@ module HsUtils( collectLStmtsBinders, collectStmtsBinders, collectLStmtBinders, collectStmtBinders, - hsLTyClDeclBinders, hsTyClDeclBinders, hsTyClDeclsBinders, + hsLTyClDeclBinders, hsTyClDeclsBinders, hsForeignDeclsBinders, hsGroupBinders, hsDataFamInstBinders, -- Collecting implicit binders @@ -690,26 +690,25 @@ hsTyClDeclsBinders tycl_decls inst_decls ------------------- hsLTyClDeclBinders :: Eq name => Located (TyClDecl name) -> [Located name] --- ^ Returns all the /binding/ names of the decl, along with their SrcLocs. +-- ^ Returns all the /binding/ names of the decl. -- The first one is guaranteed to be the name of the decl. For record fields -- mentioned in multiple constructors, the SrcLoc will be from the first --- occurence. We use the equality to filter out duplicate field names -hsLTyClDeclBinders (L _ d) = hsTyClDeclBinders d - -------------------- -hsTyClDeclBinders :: Eq name => TyClDecl name -> [Located name] -hsTyClDeclBinders (FamDecl { tcdFam = FamilyDecl { fdLName = name} }) = [name] -hsTyClDeclBinders (ForeignType {tcdLName = name}) = [name] -hsTyClDeclBinders (SynDecl {tcdLName = name}) = [name] - -hsTyClDeclBinders (ClassDecl { tcdLName = cls_name, tcdSigs = sigs - , tcdATs = ats }) - = cls_name : - map (fdLName . unLoc) ats ++ - [n | L _ (TypeSig ns _) <- sigs, n <- ns] - -hsTyClDeclBinders (DataDecl { tcdLName = name, tcdDataDefn = defn }) - = name : hsDataDefnBinders defn +-- occurence. We use the equality to filter out duplicate field names. +-- The @SrcLoc at s are the locations of the /declaration/, not just the name. + +-- The re-mangling of the SrcLocs here are to keep good error messages while +-- avoiding #8607. +hsLTyClDeclBinders (L loc (FamDecl { tcdFam = FamilyDecl { fdLName = L _ name } })) + = [L loc name] +hsLTyClDeclBinders (L loc (ForeignType { tcdLName = L _ name })) = [L loc name] +hsLTyClDeclBinders (L loc (SynDecl { tcdLName = L _ name })) = [L loc name] +hsLTyClDeclBinders (L loc (ClassDecl { tcdLName = L _ cls_name + , tcdSigs = sigs, tcdATs = ats })) + = L loc cls_name : + [ L fam_loc fam_name | L fam_loc (FamilyDecl { fdLName = L _ fam_name }) <- ats ] ++ + [ L mem_loc mem_name | L mem_loc (TypeSig ns _) <- sigs, L _ mem_name <- ns ] +hsLTyClDeclBinders (L loc (DataDecl { tcdLName = L _ name, tcdDataDefn = defn })) + = L loc name : hsDataDefnBinders defn ------------------- hsInstDeclBinders :: Eq name => InstDecl name -> [Located name] @@ -719,32 +718,37 @@ hsInstDeclBinders (DataFamInstD { dfid_inst = fi }) = hsDataFamInstBinders fi hsInstDeclBinders (TyFamInstD {}) = [] ------------------- +-- the SrcLoc returned are for the whole declarations, not just the names hsDataFamInstBinders :: Eq name => DataFamInstDecl name -> [Located name] hsDataFamInstBinders (DataFamInstDecl { dfid_defn = defn }) = hsDataDefnBinders defn -- There can't be repeated symbols because only data instances have binders ------------------- +-- the SrcLoc returned are for the whole declarations, not just the names hsDataDefnBinders :: Eq name => HsDataDefn name -> [Located name] hsDataDefnBinders (HsDataDefn { dd_cons = cons }) = hsConDeclsBinders cons -- See Note [Binders in family instances] ------------------- hsConDeclsBinders :: (Eq name) => [LConDecl name] -> [Located name] - -- See hsTyClDeclBinders for what this does + -- See hsLTyClDeclBinders for what this does -- The function is boringly complicated because of the records -- And since we only have equality, we have to be a little careful hsConDeclsBinders cons = snd (foldl do_one ([], []) cons) where - do_one (flds_seen, acc) (L _ (ConDecl { con_name = lname, con_details = RecCon flds })) - = (map unLoc new_flds ++ flds_seen, lname : new_flds ++ acc) + do_one (flds_seen, acc) (L loc (ConDecl { con_name = L _ name + , con_details = RecCon flds })) + = (map unLoc new_flds ++ flds_seen, L loc name : new_flds ++ acc) where + -- don't re-mangle the location of field names, because we don't + -- have a record of the full location of the field declaration anyway new_flds = filterOut (\f -> unLoc f `elem` flds_seen) (map cd_fld_name flds) - do_one (flds_seen, acc) (L _ (ConDecl { con_name = lname })) - = (flds_seen, lname:acc) + do_one (flds_seen, acc) (L loc (ConDecl { con_name = L _ name })) + = (flds_seen, L loc name : acc) \end{code} Note [Binders in family instances] diff --git a/compiler/rename/RnEnv.lhs b/compiler/rename/RnEnv.lhs index f7dcdc8..c49652b 100644 --- a/compiler/rename/RnEnv.lhs +++ b/compiler/rename/RnEnv.lhs @@ -134,7 +134,6 @@ newTopSrcBinder (L loc rdr_name) -- have an arbitrary mixture of external core definitions in a single module, -- (apart from module-initialisation issues, perhaps). ; newGlobalBinder rdr_mod rdr_occ loc } - --TODO, should pass the whole span | otherwise = do { unless (not (isQual rdr_name)) diff --git a/compiler/rename/RnNames.lhs b/compiler/rename/RnNames.lhs index 93a2396..64e38f5 100644 --- a/compiler/rename/RnNames.lhs +++ b/compiler/rename/RnNames.lhs @@ -500,19 +500,23 @@ getLocalNonValBinders fixity_env ; return (envs, new_bndrs) } } where for_hs_bndrs :: [Located RdrName] - for_hs_bndrs = [nm | L _ (ForeignImport nm _ _ _) <- foreign_decls] + for_hs_bndrs = [ L decl_loc (unLoc nm) + | L decl_loc (ForeignImport nm _ _ _) <- foreign_decls] -- In a hs-boot file, the value binders come from the -- *signatures*, and there should be no foreign binders - hs_boot_sig_bndrs = [n | L _ (TypeSig ns _) <- val_sigs, n <- ns] + hs_boot_sig_bndrs = [ L decl_loc (unLoc n) + | L decl_loc (TypeSig ns _) <- val_sigs, n <- ns] ValBindsIn _ val_sigs = val_binds + -- the SrcSpan attached to the input should be the span of the + -- declaration, not just the name new_simple :: Located RdrName -> RnM AvailInfo new_simple rdr_name = do{ nm <- newTopSrcBinder rdr_name ; return (Avail nm) } new_tc tc_decl -- NOT for type/data instances - = do { let bndrs = hsTyClDeclBinders (unLoc tc_decl) + = do { let bndrs = hsLTyClDeclBinders tc_decl ; names@(main_name : _) <- mapM newTopSrcBinder bndrs ; return (AvailTC main_name names) } From git at git.haskell.org Fri Dec 27 03:39:59 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Dec 2013 03:39:59 +0000 (UTC) Subject: [commit: testsuite] master: Error wibbles while fixing #8607. (9e28639) Message-ID: <20131227033959.DD1282406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/testsuite On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9e28639756bddb797ac99ec0613aeb2a70b0e4b9/testsuite >--------------------------------------------------------------- commit 9e28639756bddb797ac99ec0613aeb2a70b0e4b9 Author: Richard Eisenberg Date: Thu Dec 26 22:32:56 2013 -0500 Error wibbles while fixing #8607. >--------------------------------------------------------------- 9e28639756bddb797ac99ec0613aeb2a70b0e4b9 tests/ghci/scripts/ghci030.stdout | 2 +- tests/module/mod145.stderr | 2 +- tests/rename/should_fail/T3265.stderr | 4 ++-- tests/rename/should_fail/rnfail042.stderr | 2 +- tests/typecheck/should_fail/tcfail156.stderr | 2 +- tests/typecheck/should_fail/tcfail173.stderr | 2 +- 6 files changed, 7 insertions(+), 7 deletions(-) diff --git a/tests/ghci/scripts/ghci030.stdout b/tests/ghci/scripts/ghci030.stdout index 3ac8cc2..9344bc3 100644 --- a/tests/ghci/scripts/ghci030.stdout +++ b/tests/ghci/scripts/ghci030.stdout @@ -3,4 +3,4 @@ data D where -- Defined at ghci030.hs:8:1 data D where C :: (Int -> a) -> Char -> D - -- Defined at ghci030.hs:8:21 + -- Defined at ghci030.hs:8:10 diff --git a/tests/module/mod145.stderr b/tests/module/mod145.stderr index 37109b3..1f94fae 100644 --- a/tests/module/mod145.stderr +++ b/tests/module/mod145.stderr @@ -3,5 +3,5 @@ mod145.hs:2:30: Conflicting exports for ?m1?: ?module Mod145_A? exports ?Mod145_A.m1? imported from ?Mod145_A? at mod145.hs:4:1-15 - (and originally defined at Mod145_A.hs:4:3-4) + (and originally defined at Mod145_A.hs:4:3-20) ?module Mod145? exports ?Mod145.m1? defined at mod145.hs:7:3 diff --git a/tests/rename/should_fail/T3265.stderr b/tests/rename/should_fail/T3265.stderr index 8022424..185861a 100644 --- a/tests/rename/should_fail/T3265.stderr +++ b/tests/rename/should_fail/T3265.stderr @@ -1,8 +1,8 @@ -T3265.hs:7:1: +T3265.hs:7:8: Illegal declaration of a type or class operator ?:+:? Use TypeOperators to declare operators in type and declarations -T3265.hs:9:1: +T3265.hs:9:9: Illegal declaration of a type or class operator ?:*:? Use TypeOperators to declare operators in type and declarations diff --git a/tests/rename/should_fail/rnfail042.stderr b/tests/rename/should_fail/rnfail042.stderr index 9e030d7..03b7c54 100644 --- a/tests/rename/should_fail/rnfail042.stderr +++ b/tests/rename/should_fail/rnfail042.stderr @@ -5,4 +5,4 @@ rnfail042.hs:6:10: Illegal binding of built-in syntax: (,,,) rnfail042.hs:7:12: Illegal binding of built-in syntax: [] -rnfail042.hs:8:17: Illegal binding of built-in syntax: : +rnfail042.hs:8:13: Illegal binding of built-in syntax: : diff --git a/tests/typecheck/should_fail/tcfail156.stderr b/tests/typecheck/should_fail/tcfail156.stderr index c7e36e6..a4d2cbe 100644 --- a/tests/typecheck/should_fail/tcfail156.stderr +++ b/tests/typecheck/should_fail/tcfail156.stderr @@ -1,5 +1,5 @@ -tcfail156.hs:7:26: +tcfail156.hs:7:15: A newtype constructor cannot have existential type variables Foo :: forall a. a -> Foo In the definition of data constructor ?Foo? diff --git a/tests/typecheck/should_fail/tcfail173.stderr b/tests/typecheck/should_fail/tcfail173.stderr index f8dfd57..2c87b91 100644 --- a/tests/typecheck/should_fail/tcfail173.stderr +++ b/tests/typecheck/should_fail/tcfail173.stderr @@ -1,4 +1,4 @@ -tcfail173.hs:5:1: +tcfail173.hs:5:12: Illegal declaration of a type or class operator ?<.>? Use TypeOperators to declare operators in type and declarations From git at git.haskell.org Fri Dec 27 12:21:31 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 27 Dec 2013 12:21:31 +0000 (UTC) Subject: [commit: ghc] master: Add hook for splicing in renamer (df2dd64) Message-ID: <20131227122132.026D82406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/df2dd64dca0796f01356f5fb2ec41edf9762c349/ghc >--------------------------------------------------------------- commit df2dd64dca0796f01356f5fb2ec41edf9762c349 Author: Edsko de Vries Date: Tue Dec 17 17:28:44 2013 +0000 Add hook for splicing in renamer With the recent modifications to the TH infrastructure, many splices are now expanded in the renamer rather than the typechecker. This means that tools which inspect the renamed tree don't get to see the original splices. Added a new hook which gets called before such a splice gets expanded, analogous to the runQuasiQuoteHook. >--------------------------------------------------------------- df2dd64dca0796f01356f5fb2ec41edf9762c349 compiler/main/Hooks.lhs | 5 ++++- compiler/rename/RnSplice.lhs | 15 +++++++++++---- 2 files changed, 15 insertions(+), 5 deletions(-) diff --git a/compiler/main/Hooks.lhs b/compiler/main/Hooks.lhs index 24bfb10..326b140 100644 --- a/compiler/main/Hooks.lhs +++ b/compiler/main/Hooks.lhs @@ -16,6 +16,7 @@ module Hooks ( Hooks , runPhaseHook , linkHook , runQuasiQuoteHook + , runRnSpliceHook , getValueSafelyHook ) where @@ -26,6 +27,7 @@ import PipelineMonad import HscTypes import HsDecls import HsBinds +import HsExpr import {-# SOURCE #-} DsMonad import OrdList import Id @@ -54,7 +56,7 @@ import Data.Maybe emptyHooks :: Hooks emptyHooks = Hooks Nothing Nothing Nothing Nothing Nothing Nothing - Nothing Nothing Nothing Nothing Nothing + Nothing Nothing Nothing Nothing Nothing Nothing data Hooks = Hooks { dsForeignsHook :: Maybe ([LForeignDecl Id] -> DsM (ForeignStubs, OrdList (Id, CoreExpr))) @@ -67,6 +69,7 @@ data Hooks = Hooks , runPhaseHook :: Maybe (PhasePlus -> FilePath -> DynFlags -> CompPipeline (PhasePlus, FilePath)) , linkHook :: Maybe (GhcLink -> DynFlags -> Bool -> HomePackageTable -> IO SuccessFlag) , runQuasiQuoteHook :: Maybe (HsQuasiQuote Name -> RnM (HsQuasiQuote Name)) + , runRnSpliceHook :: Maybe (HsSplice Name -> RnM (HsSplice Name)) , getValueSafelyHook :: Maybe (HscEnv -> Name -> Type -> IO (Maybe HValue)) } diff --git a/compiler/rename/RnSplice.lhs b/compiler/rename/RnSplice.lhs index b744313..bc47fe8 100644 --- a/compiler/rename/RnSplice.lhs +++ b/compiler/rename/RnSplice.lhs @@ -28,6 +28,7 @@ import TcEnv ( checkWellStaged, tcMetaTy ) import Outputable import BasicTypes ( TopLevelFlag, isTopLevel ) import FastString +import Hooks import {-# SOURCE #-} RnExpr ( rnLExpr ) import {-# SOURCE #-} TcExpr ( tcMonoExpr ) @@ -136,7 +137,7 @@ rnSpliceExpr is_typed splice = (PendingRnExpSplice rn_splice, HsSpliceE is_typed rn_splice) run_expr_splice :: HsSplice Name -> RnM (HsExpr Name, FreeVars) - run_expr_splice rn_splice@(HsSplice _ expr) + run_expr_splice rn_splice | is_typed -- Run it later, in the type checker = do { -- Ugh! See Note [Splices] above lcl_rdr <- getLocalRdrEnv @@ -148,7 +149,9 @@ rnSpliceExpr is_typed splice ; return (HsSpliceE is_typed rn_splice, lcl_names `plusFV` gbl_names) } | otherwise -- Run it here - = do { -- The splice must have type ExpQ + = do { HsSplice _ expr <- getHooked runRnSpliceHook return >>= ($ rn_splice) + + -- The splice must have type ExpQ ; meta_exp_ty <- tcMetaTy expQTyConName -- Typecheck the expression @@ -171,8 +174,10 @@ rnSpliceType splice k pend_type_splice rn_splice = (PendingRnTypeSplice rn_splice, HsSpliceTy rn_splice k) - run_type_splice (HsSplice _ expr) - = do { meta_exp_ty <- tcMetaTy typeQTyConName + run_type_splice rn_splice + = do { HsSplice _ expr <- getHooked runRnSpliceHook return >>= ($ rn_splice) + + ; meta_exp_ty <- tcMetaTy typeQTyConName -- Typecheck the expression ; zonked_q_expr <- tcTopSpliceExpr False $ @@ -190,6 +195,7 @@ rnSpliceType splice k ---------------------- rnSplicePat :: HsSplice RdrName -> RnM (Pat Name, FreeVars) +-- TODO: Run runHsSpliceHook (see runSpliceExpr) rnSplicePat splice = rnSpliceGen False run_pat_splice pend_pat_splice splice where @@ -226,6 +232,7 @@ rnSpliceDecl (SpliceDecl (L loc splice) flg) \begin{code} rnTopSpliceDecls :: HsSplice RdrName -> RnM ([LHsDecl RdrName], FreeVars) -- Declaration splice at the very top level of the module +-- TODO: Run runHsSpliceHook (see runSpliceExpr) rnTopSpliceDecls (HsSplice _ expr) = do { (expr', fvs) <- setStage (Splice False) $ rnLExpr expr From git at git.haskell.org Sat Dec 28 09:46:06 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 28 Dec 2013 09:46:06 +0000 (UTC) Subject: [commit: packages/template-haskell] master: Use type synonym (ec8450c) Message-ID: <20131228094606.D138F2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/template-haskell On branch : master Link : http://git.haskell.org/packages/template-haskell.git/commitdiff/ec8450c9eefe7fdf33dc62b841e5c52047b73b42 >--------------------------------------------------------------- commit ec8450c9eefe7fdf33dc62b841e5c52047b73b42 Author: Jan Stolarek Date: Sat Dec 28 09:53:17 2013 +0100 Use type synonym >--------------------------------------------------------------- ec8450c9eefe7fdf33dc62b841e5c52047b73b42 Language/Haskell/TH/Lib.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Language/Haskell/TH/Lib.hs b/Language/Haskell/TH/Lib.hs index 0ffa2c0..9b45943 100644 --- a/Language/Haskell/TH/Lib.hs +++ b/Language/Haskell/TH/Lib.hs @@ -196,7 +196,7 @@ clause ps r ds = do { ps' <- sequence ps; -- * Exp -- | Dynamically binding a variable (unhygenic) -dyn :: String -> Q Exp +dyn :: String -> ExpQ dyn s = return (VarE (mkName s)) global :: Name -> ExpQ From git at git.haskell.org Sat Dec 28 09:46:08 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 28 Dec 2013 09:46:08 +0000 (UTC) Subject: [commit: packages/template-haskell] master: Kill trailing whitespaces (409bbda) Message-ID: <20131228094608.A515C2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/template-haskell On branch : master Link : http://git.haskell.org/packages/template-haskell.git/commitdiff/409bbda4dc504b5c23dc1b00f1d4b1cab07b4c79 >--------------------------------------------------------------- commit 409bbda4dc504b5c23dc1b00f1d4b1cab07b4c79 Author: Jan Stolarek Date: Sat Dec 28 09:54:11 2013 +0100 Kill trailing whitespaces >--------------------------------------------------------------- 409bbda4dc504b5c23dc1b00f1d4b1cab07b4c79 0 files changed From git at git.haskell.org Mon Dec 30 12:11:12 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 30 Dec 2013 12:11:12 +0000 (UTC) Subject: [commit: ghc] master: Define mkTcNomReflCo = TcRefl Nominal, and use it all over (a6f6169) Message-ID: <20131230121112.A2EAE2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a6f6169a9939525c859b274955e8606d6080100f/ghc >--------------------------------------------------------------- commit a6f6169a9939525c859b274955e8606d6080100f Author: Simon Peyton Jones Date: Sat Dec 28 12:05:45 2013 +0000 Define mkTcNomReflCo = TcRefl Nominal, and use it all over This patch doesn't include the changes to TcCanonical and TcSMonad, which are a bigger follow-up patch, so it is tightly coupled to the follow-up. >--------------------------------------------------------------- a6f6169a9939525c859b274955e8606d6080100f compiler/typecheck/TcArrows.lhs | 4 ++-- compiler/typecheck/TcEvidence.lhs | 6 +++++- compiler/typecheck/TcExpr.lhs | 2 +- compiler/typecheck/TcInteract.lhs | 6 +++--- compiler/typecheck/TcMType.lhs | 2 +- compiler/typecheck/TcPat.lhs | 4 ++-- compiler/typecheck/TcUnify.lhs | 14 +++++++------- 7 files changed, 21 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 a6f6169a9939525c859b274955e8606d6080100f From git at git.haskell.org Mon Dec 30 12:11:14 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 30 Dec 2013 12:11:14 +0000 (UTC) Subject: [commit: ghc] master: Comments only (d58a8df) Message-ID: <20131230121114.F0B972406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d58a8df39eccafa2a4f3c84de7d8d5c24b44a85d/ghc >--------------------------------------------------------------- commit d58a8df39eccafa2a4f3c84de7d8d5c24b44a85d Author: Simon Peyton Jones Date: Sat Dec 28 12:29:05 2013 +0000 Comments only >--------------------------------------------------------------- d58a8df39eccafa2a4f3c84de7d8d5c24b44a85d compiler/typecheck/TcRnTypes.lhs | 2 +- compiler/typecheck/TcType.lhs | 4 ++-- 2 files changed, 3 insertions(+), 3 deletions(-) diff --git a/compiler/typecheck/TcRnTypes.lhs b/compiler/typecheck/TcRnTypes.lhs index b7c9790..af66394 100644 --- a/compiler/typecheck/TcRnTypes.lhs +++ b/compiler/typecheck/TcRnTypes.lhs @@ -987,7 +987,7 @@ We can't require *equal* kinds, because Note [Kind orientation for CFunEqCan] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -For (F xis ~ rhs) we require that kind(rhs) is a subkind of kind(lhs). +For (F xis ~ rhs) we require that kind(lhs) is a subkind of kind(rhs). This reallly only maters when rhs is an Open type variable (since only type variables have Open kinds): F ty ~ (a:Open) diff --git a/compiler/typecheck/TcType.lhs b/compiler/typecheck/TcType.lhs index a69b676..55c37b9 100644 --- a/compiler/typecheck/TcType.lhs +++ b/compiler/typecheck/TcType.lhs @@ -1050,7 +1050,7 @@ pickyEqType ty1 ty2 Note [Occurs check expansion] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ - at occurCheckExpand tv xi@ expands synonyms in xi just enough to get rid +(occurCheckExpand tv xi) expands synonyms in xi just enough to get rid of occurrences of tv outside type function arguments, if that is possible; otherwise, it returns Nothing. @@ -1070,7 +1070,7 @@ We have occurCheckExpand b (F (G b)) = F Char even though we could also expand F to get rid of b. -See also Note [Type synonyms and canonicalization] in TcCanonical +See also Note [occurCheckExpand] in TcCanonical \begin{code} data OccCheckResult a From git at git.haskell.org Mon Dec 30 12:11:17 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 30 Dec 2013 12:11:17 +0000 (UTC) Subject: [commit: ghc] master: Re-factor TcCanonical (again), fixes Trac #8603 (8721743) Message-ID: <20131230121118.4F3A12406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8721743e88f4c8c385eb0ceb0ca6804b2143a8fa/ghc >--------------------------------------------------------------- commit 8721743e88f4c8c385eb0ceb0ca6804b2143a8fa Author: Simon Peyton Jones Date: Sat Dec 28 12:28:52 2013 +0000 Re-factor TcCanonical (again), fixes Trac #8603 This is a substantial refactoring of the canonicaliser. The proximate cause was that we were sometimes failing to correctly orient a tyvar/tyvar equality (x ~ y), because the kind of x or y was not fully zonked at the moment we compared them. That in turn led me to look closely at the way that canEvNC (which decomposes equalities) worked. * The big change is that the 'reOrient' and 'classify' functions are gone, along with classify's 'TypeClassifier' return type. Instead the re-orientation is built into canEqNC. When we find a type variable we divert into canEqTyVar, and so on, very much as in TcUnify. * TcCanonical.canEqTyVar, canEqLeafFun, etc now carry a SwapFlag (to reduce duplication), just as in TcUnify; now SwapFlag itself is defined in BasicTypes * I renamed TcSMonad.rewriteCtFlavor to rewriteEvidence, * I added a new specialised version of rewriteEvidence, called TcSMonad.rewriteEqEvidence. It is easier to use, and removes the crafty but brain-mangling higher order casts that we were using before. The result is not exactly simpler, but it's pretty clear and, I think, significantly more efficient. And it fixes Trac #8603! >--------------------------------------------------------------- 8721743e88f4c8c385eb0ceb0ca6804b2143a8fa compiler/basicTypes/BasicTypes.lhs | 6 +- compiler/typecheck/TcCanonical.lhs | 665 +++++++++++++++++++----------------- compiler/typecheck/TcSMonad.lhs | 95 +++++- 3 files changed, 445 insertions(+), 321 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 8721743e88f4c8c385eb0ceb0ca6804b2143a8fa From git at git.haskell.org Mon Dec 30 12:11:19 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 30 Dec 2013 12:11:19 +0000 (UTC) Subject: [commit: ghc] master: Comments only (00a9110) Message-ID: <20131230121119.B70712406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/00a9110243ded97494535dc450838f0aebb2c3f3/ghc >--------------------------------------------------------------- commit 00a9110243ded97494535dc450838f0aebb2c3f3 Author: Simon Peyton Jones Date: Mon Dec 30 12:10:45 2013 +0000 Comments only >--------------------------------------------------------------- 00a9110243ded97494535dc450838f0aebb2c3f3 compiler/hsSyn/HsUtils.lhs | 9 ++++++--- 1 file changed, 6 insertions(+), 3 deletions(-) diff --git a/compiler/hsSyn/HsUtils.lhs b/compiler/hsSyn/HsUtils.lhs index bdc77c0..218a452 100644 --- a/compiler/hsSyn/HsUtils.lhs +++ b/compiler/hsSyn/HsUtils.lhs @@ -694,10 +694,13 @@ hsLTyClDeclBinders :: Eq name => Located (TyClDecl name) -> [Located name] -- The first one is guaranteed to be the name of the decl. For record fields -- mentioned in multiple constructors, the SrcLoc will be from the first -- occurence. We use the equality to filter out duplicate field names. --- The @SrcLoc at s are the locations of the /declaration/, not just the name. +-- +-- Each returned (Located name) is wrapped in a @SrcSpan@ of the whole +-- /declaration/, not just the name itself (which is how it appears in +-- the syntax tree). This SrcSpan (for the entire declaration) is used +-- as the SrcSpan for the Name that is finally produced, and hence for +-- error messages. (See Trac #8607.) --- The re-mangling of the SrcLocs here are to keep good error messages while --- avoiding #8607. hsLTyClDeclBinders (L loc (FamDecl { tcdFam = FamilyDecl { fdLName = L _ name } })) = [L loc name] hsLTyClDeclBinders (L loc (ForeignType { tcdLName = L _ name })) = [L loc name] From git at git.haskell.org Mon Dec 30 12:14:52 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 30 Dec 2013 12:14:52 +0000 (UTC) Subject: [commit: packages/template-haskell] master: Improve mkName, so that it correctly parses the name ^.. (21a4860) Message-ID: <20131230121452.6704D2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/template-haskell On branch : master Link : http://git.haskell.org/packages/template-haskell.git/commitdiff/21a48605d856ca334bb3a018e02255349d69a8c4 >--------------------------------------------------------------- commit 21a48605d856ca334bb3a018e02255349d69a8c4 Author: Simon Peyton Jones Date: Sat Dec 28 11:05:31 2013 +0000 Improve mkName, so that it correctly parses the name ^.. This fixes Trac #8633; thanks to aavogt for a first draft. >--------------------------------------------------------------- 21a48605d856ca334bb3a018e02255349d69a8c4 Language/Haskell/TH/Syntax.hs | 24 ++++++++++++++++++++---- 1 file changed, 20 insertions(+), 4 deletions(-) diff --git a/Language/Haskell/TH/Syntax.hs b/Language/Haskell/TH/Syntax.hs index f3868d1..3606f9d 100644 --- a/Language/Haskell/TH/Syntax.hs +++ b/Language/Haskell/TH/Syntax.hs @@ -24,7 +24,7 @@ import Data.IORef import System.IO.Unsafe ( unsafePerformIO ) import Control.Monad (liftM) import System.IO ( hPutStrLn, stderr ) -import Data.Char ( isAlpha ) +import Data.Char ( isAlpha, isAlphaNum, isUpper ) import Data.Word ( Word8 ) ----------------------------------------------------- @@ -758,17 +758,33 @@ mkName str = split [] (reverse str) where split occ [] = Name (mkOccName occ) NameS - split occ ('.':rev) | not (null occ), - not (null rev), head rev /= '.' + split occ ('.':rev) | not (null occ) + , is_rev_mod_name rev = Name (mkOccName occ) (NameQ (mkModName (reverse rev))) -- The 'not (null occ)' guard ensures that -- mkName "&." = Name "&." NameS - -- The 'rev' guards ensure that + -- The 'is_rev_mod' guards ensure that -- mkName ".&" = Name ".&" NameS + -- mkName "^.." = Name "^.." NameS -- Trac #8633 -- mkName "Data.Bits..&" = Name ".&" (NameQ "Data.Bits") -- This rather bizarre case actually happened; (.&.) is in Data.Bits split occ (c:rev) = split (c:occ) rev + -- Recognises a reversed module name xA.yB.C, + -- with at least one component, + -- and each component looks like a module name + -- (i.e. non-empty, starts with capital, all alpha) + is_rev_mod_name rev_mod_str + | (compt, rest) <- break (== '.') rev_mod_str + , not (null compt), isUpper (last compt), all is_mod_char compt + = case rest of + [] -> True + (_dot : rest') -> is_rev_mod_name rest' + | otherwise + = False + + is_mod_char c = isAlphaNum c || c == '_' || c == '\'' + -- | Only used internally mkNameU :: String -> Uniq -> Name mkNameU s (I# u) = Name (mkOccName s) (NameU u) From git at git.haskell.org Mon Dec 30 12:15:47 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 30 Dec 2013 12:15:47 +0000 (UTC) Subject: [commit: testsuite] master: Update perf numbers for 32-bit This has not been done for ages (c2e88b3) Message-ID: <20131230121547.D3F912406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/testsuite On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c2e88b34cd3cb48d4bb203b6f0e7de1980e9c570/testsuite >--------------------------------------------------------------- commit c2e88b34cd3cb48d4bb203b6f0e7de1980e9c570 Author: Simon Peyton Jones Date: Fri Nov 22 22:53:50 2013 +0000 Update perf numbers for 32-bit This has not been done for ages >--------------------------------------------------------------- c2e88b34cd3cb48d4bb203b6f0e7de1980e9c570 tests/perf/compiler/all.T | 79 ++++++++++++++++++++++++++----------------- tests/perf/haddock/all.T | 27 ++++++++++----- tests/perf/should_run/all.T | 9 +++-- 3 files changed, 72 insertions(+), 43 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 c2e88b34cd3cb48d4bb203b6f0e7de1980e9c570 From git at git.haskell.org Mon Dec 30 12:15:50 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 30 Dec 2013 12:15:50 +0000 (UTC) Subject: [commit: testsuite] master: Test Trac #8633 (3fef8e4) Message-ID: <20131230121550.0E8B52406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/testsuite On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3fef8e4094c8d0c58bad2604ecaee93d797ccbd1/testsuite >--------------------------------------------------------------- commit 3fef8e4094c8d0c58bad2604ecaee93d797ccbd1 Author: Simon Peyton Jones Date: Sat Dec 28 12:45:06 2013 +0000 Test Trac #8633 >--------------------------------------------------------------- 3fef8e4094c8d0c58bad2604ecaee93d797ccbd1 tests/th/T8633.hs | 19 +++++++++++++++++++ tests/th/all.T | 1 + 2 files changed, 20 insertions(+) diff --git a/tests/th/T8633.hs b/tests/th/T8633.hs new file mode 100644 index 0000000..79f1ec6 --- /dev/null +++ b/tests/th/T8633.hs @@ -0,0 +1,19 @@ +module Main where +import Language.Haskell.TH.Syntax + +t1 = case mkName "^.." of + Name (OccName ".") (NameQ (ModName "^")) -> error "bug0" + Name (OccName "^..") NameS -> return () + +t2 = case mkName "Control.Lens.^.." of + Name (OccName ".") (NameQ (ModName "Control.Lens.^")) -> error "bug1" + Name (OccName "^..") (NameQ (ModName "Control.Lens")) -> return () + +t3 = case mkName "Data.Bits..&." of + Name (OccName ".&.") (NameQ (ModName "Data.Bits")) -> return () + +t4 = case mkName "abcde" of + Name (OccName "abcde") NameS -> return () + +main :: IO () +main = do t1; t2; t3; t4 \ No newline at end of file diff --git a/tests/th/all.T b/tests/th/all.T index 05d5d90..b521f79 100644 --- a/tests/th/all.T +++ b/tests/th/all.T @@ -315,3 +315,4 @@ test('T8577', extra_clean(['T8577a.hi', 'T8577a.o']), multimod_compile_fail, ['T8577', '-v0 ' + config.ghc_th_way_flags]) +test('T8633', normal, compile_and_run, ['']) From git at git.haskell.org Mon Dec 30 12:15:52 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 30 Dec 2013 12:15:52 +0000 (UTC) Subject: [commit: testsuite] master: Test Trac #8603 (b34bee3) Message-ID: <20131230121552.4D1262406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/testsuite On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b34bee3a45204ff43fa31e9dee3a23a74aa252db/testsuite >--------------------------------------------------------------- commit b34bee3a45204ff43fa31e9dee3a23a74aa252db Author: Simon Peyton Jones Date: Sat Dec 28 12:45:35 2013 +0000 Test Trac #8603 >--------------------------------------------------------------- b34bee3a45204ff43fa31e9dee3a23a74aa252db tests/typecheck/should_fail/T8603.hs | 32 ++++++++++++++++++++++++++++++ tests/typecheck/should_fail/T8603.stderr | 22 ++++++++++++++++++++ tests/typecheck/should_fail/all.T | 1 + 3 files changed, 55 insertions(+) diff --git a/tests/typecheck/should_fail/T8603.hs b/tests/typecheck/should_fail/T8603.hs new file mode 100644 index 0000000..90c1db3 --- /dev/null +++ b/tests/typecheck/should_fail/T8603.hs @@ -0,0 +1,32 @@ +module T8603 where + +import Control.Monad +import Data.Functor +import Control.Monad.Trans.Class( lift ) +import Control.Monad.Trans.State( StateT ) + +newtype RV a = RV { getPDF :: [(Rational,a)] } deriving (Show, Eq) + +instance Functor RV where + fmap f = RV . map (\(x,y) -> (x, f y)) . getPDF + +instance Monad RV where + return x = RV [(1,x)] + rv >>= f = RV $ + do (p,a) <- getPDF rv + guard (p > 0) + (q,b) <- getPDF $ f a + guard (q > 0) + return (p*q, b) + +type RVState s a = StateT s RV a + +uniform :: [a] -> RV a +uniform x = RV [(1/fromIntegral (length x), y) | y <- x] + +testRVState1 :: RVState s Bool +testRVState1 + = do prize <- lift uniform [1,2,3] + return False + +-- lift :: (MonadTrans t, Monad m) => m a -> t m a \ No newline at end of file diff --git a/tests/typecheck/should_fail/T8603.stderr b/tests/typecheck/should_fail/T8603.stderr new file mode 100644 index 0000000..1777dc9 --- /dev/null +++ b/tests/typecheck/should_fail/T8603.stderr @@ -0,0 +1,22 @@ + +T8603.hs:29:17: + Couldn't match type ?(->) [a0]? with ?[t1]? + Expected type: [t1] -> StateT s RV t0 + Actual type: t2 ((->) [a0]) (StateT s RV t0) + The function ?lift? is applied to two arguments, + but its type ?([a0] -> StateT s RV t0) + -> t2 ((->) [a0]) (StateT s RV t0)? + has only one + In a stmt of a 'do' block: prize <- lift uniform [1, 2, 3] + In the expression: + do { prize <- lift uniform [1, 2, ....]; + return False } + +T8603.hs:29:22: + Couldn't match type ?StateT s RV t0? with ?RV a0? + Expected type: [a0] -> StateT s RV t0 + Actual type: [a0] -> RV a0 + Relevant bindings include + testRVState1 :: RVState s Bool (bound at T8603.hs:28:1) + In the first argument of ?lift?, namely ?uniform? + In a stmt of a 'do' block: prize <- lift uniform [1, 2, 3] diff --git a/tests/typecheck/should_fail/all.T b/tests/typecheck/should_fail/all.T index 93eb007..faef063 100644 --- a/tests/typecheck/should_fail/all.T +++ b/tests/typecheck/should_fail/all.T @@ -329,3 +329,4 @@ test('ContextStack1', normal, compile_fail, ['-fcontext-stack=10']) test('ContextStack2', normal, compile_fail, ['-ftype-function-depth=10']) test('T8570', extra_clean(['T85570a.o', 'T8570a.hi','T85570b.o', 'T8570b.hi']), multimod_compile_fail, ['T8570', '-v0']) +test('T8603', normal, compile_fail, ['']) From git at git.haskell.org Mon Dec 30 12:15:54 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 30 Dec 2013 12:15:54 +0000 (UTC) Subject: [commit: testsuite] master: Error message wibbles (653ee4b) Message-ID: <20131230121554.6806D2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/testsuite On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/653ee4b32c77945d4d4550e60e7bfc14257afc0b/testsuite >--------------------------------------------------------------- commit 653ee4b32c77945d4d4550e60e7bfc14257afc0b Author: Simon Peyton Jones Date: Sat Dec 28 12:51:19 2013 +0000 Error message wibbles >--------------------------------------------------------------- 653ee4b32c77945d4d4550e60e7bfc14257afc0b tests/indexed-types/should_compile/Simple14.stderr | 6 +++--- tests/indexed-types/should_fail/T5439.stderr | 4 ++-- tests/typecheck/should_compile/T2494.stderr | 12 ++++++------ tests/typecheck/should_fail/FrozenErrorTests.stderr | 2 +- 4 files changed, 12 insertions(+), 12 deletions(-) diff --git a/tests/indexed-types/should_compile/Simple14.stderr b/tests/indexed-types/should_compile/Simple14.stderr index 3c761c3..ed94ad5 100644 --- a/tests/indexed-types/should_compile/Simple14.stderr +++ b/tests/indexed-types/should_compile/Simple14.stderr @@ -1,14 +1,14 @@ Simple14.hs:17:19: - Couldn't match type ?z0? with ?n? + Couldn't match type ?z0? with ?m? ?z0? is untouchable inside the constraints (Maybe m ~ Maybe n) bound by a type expected by the context: Maybe m ~ Maybe n => EQ_ z0 z0 at Simple14.hs:17:12-33 - ?n? is a rigid type variable bound by + ?m? is a rigid type variable bound by the type signature for foo :: EQ_ (Maybe m) (Maybe n) - at Simple14.hs:16:17 + at Simple14.hs:16:15 Expected type: EQ_ z0 z0 Actual type: EQ_ m n Relevant bindings include diff --git a/tests/indexed-types/should_fail/T5439.stderr b/tests/indexed-types/should_fail/T5439.stderr index ea7c6c5..90f4774 100644 --- a/tests/indexed-types/should_fail/T5439.stderr +++ b/tests/indexed-types/should_fail/T5439.stderr @@ -1,7 +1,7 @@ T5439.hs:83:28: - Couldn't match type ?Attempt t0 -> Attempt (HElemOf l0)? - with ?Attempt (HElemOf rs)? + Couldn't match type ?Attempt (HNth n0 l0) -> Attempt (HElemOf l0)? + with ?Attempt (WaitOpResult (WaitOps rs))? Expected type: f (Attempt (HNth n0 l0) -> Attempt (HElemOf l0)) Actual type: f (Attempt (WaitOpResult (WaitOps rs))) Relevant bindings include diff --git a/tests/typecheck/should_compile/T2494.stderr b/tests/typecheck/should_compile/T2494.stderr index 7f1a2b0..201230b 100644 --- a/tests/typecheck/should_compile/T2494.stderr +++ b/tests/typecheck/should_compile/T2494.stderr @@ -1,10 +1,10 @@ T2494.hs:15:14: - Couldn't match type ?a? with ?b? - ?a? is a rigid type variable bound by - the RULE "foo/foo" at T2494.hs:13:16 + Couldn't match type ?b? with ?a? ?b? is a rigid type variable bound by the RULE "foo/foo" at T2494.hs:14:16 + ?a? is a rigid type variable bound by + the RULE "foo/foo" at T2494.hs:13:16 Expected type: Maybe (m a) -> Maybe (m a) Actual type: Maybe (m b) -> Maybe (m b) Relevant bindings include @@ -17,11 +17,11 @@ T2494.hs:15:14: In the second argument of ?foo?, namely ?(foo g x)? T2494.hs:15:30: - Couldn't match type ?a? with ?b? - ?a? is a rigid type variable bound by - the RULE "foo/foo" at T2494.hs:13:16 + Couldn't match type ?b? with ?a? ?b? is a rigid type variable bound by the RULE "foo/foo" at T2494.hs:14:16 + ?a? is a rigid type variable bound by + the RULE "foo/foo" at T2494.hs:13:16 Expected type: Maybe (m a) -> Maybe (m a) Actual type: Maybe (m b) -> Maybe (m b) Relevant bindings include diff --git a/tests/typecheck/should_fail/FrozenErrorTests.stderr b/tests/typecheck/should_fail/FrozenErrorTests.stderr index 9857c9c..471643b 100644 --- a/tests/typecheck/should_fail/FrozenErrorTests.stderr +++ b/tests/typecheck/should_fail/FrozenErrorTests.stderr @@ -27,7 +27,7 @@ FrozenErrorTests.hs:29:15: In an equation for ?test2?: test2 = goo2 (goo1 False undefined) FrozenErrorTests.hs:30:9: - Couldn't match type ?Int? with ?[Int]? + Couldn't match type ?[Int]? with ?Int? Expected type: [[Int]] Actual type: F [Int] Bool In the expression: goo1 False (goo2 undefined) From git at git.haskell.org Mon Dec 30 21:14:39 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 30 Dec 2013 21:14:39 +0000 (UTC) Subject: [commit: testsuite] master: Fix number literal syntax mistake (ba31360) Message-ID: <20131230211439.C9B802406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/testsuite On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ba31360e1f8a44bc8ca0ddde1cd08f341a27987b/testsuite >--------------------------------------------------------------- commit ba31360e1f8a44bc8ca0ddde1cd08f341a27987b Author: Joachim Breitner Date: Mon Dec 30 22:14:19 2013 +0100 Fix number literal syntax mistake introduced in c2e88b34cd3cb48d4bb203b6f0e7de1980e9c570. >--------------------------------------------------------------- ba31360e1f8a44bc8ca0ddde1cd08f341a27987b tests/perf/compiler/all.T | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/tests/perf/compiler/all.T b/tests/perf/compiler/all.T index c58c601..a6daa10 100644 --- a/tests/perf/compiler/all.T +++ b/tests/perf/compiler/all.T @@ -50,7 +50,7 @@ test('T1969', (wordsize(32), 6149572, 1), # 6707308 (x86/OS X) # 2009-12-31 6149572 (x86/Linux) - (wordsize(64), 11,000,000, 20)]), + (wordsize(64), 11000000, 20)]), # looks like the peak is around ~10M, but we're # unlikely to GC exactly on the peak. # varies quite a lot with CLEANUP and BINDIST, From git at git.haskell.org Tue Dec 31 15:13:04 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 31 Dec 2013 15:13:04 +0000 (UTC) Subject: [commit: ghc] master: Clean up block allocator, fixes #8609 (38d17a0) Message-ID: <20131231151304.D281B2406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/38d17a0cdfee64cc73537e7bb96eb2f25df9ec92/ghc >--------------------------------------------------------------- commit 38d17a0cdfee64cc73537e7bb96eb2f25df9ec92 Author: Edward Z. Yang Date: Wed Dec 11 16:17:39 2013 -0800 Clean up block allocator, fixes #8609 Signed-off-by: Edward Z. Yang >--------------------------------------------------------------- 38d17a0cdfee64cc73537e7bb96eb2f25df9ec92 rts/sm/BlockAlloc.c | 34 ++++++++++++++++++++++++++++++---- 1 file changed, 30 insertions(+), 4 deletions(-) diff --git a/rts/sm/BlockAlloc.c b/rts/sm/BlockAlloc.c index 18c167f..4d2685b 100644 --- a/rts/sm/BlockAlloc.c +++ b/rts/sm/BlockAlloc.c @@ -101,12 +101,28 @@ static void initMBlock(void *mblock); Free is O(1). - We cannot play this coalescing trick with mblocks, because there is + Megablocks + ~~~~~~~~~~ + + Separately from the free list of block groups, which are smaller than + an mblock, we maintain a free list of mblock groups. This is the unit + of memory the operating system gives us, and we may either split mblocks + into blocks or allocate them directly (when very large contiguous regions + of memory). mblocks have a different set of invariants than blocks: + + bd->start points to the start of the block IF the block is in the first mblock + bd->blocks and bd->link are only valid IF this block is the first block + of the first mblock + No other fields are used (in particular, free is not used, meaning that + space that is not used by the (single) object is wasted. + + This has implications for the free list as well: + We cannot play the coalescing trick with mblocks, because there is no requirement that the bdescrs in the second and subsequent mblock of an mgroup are initialised (the mgroup might be filled with a large array, overwriting the bdescrs for example). - So there is a separate free list for megablocks, sorted in *address* + The separate free list for megablocks is thus sorted in *address* order, so that we can coalesce. Allocation in this list is best-fit by traversing the whole list: we don't expect this list to be long, and allocation/freeing of large blocks is rare; avoiding @@ -170,7 +186,14 @@ initGroup(bdescr *head) bdescr *bd; W_ i, n; - n = head->blocks; + // If this block group fits in a single megablock, initialize + // all of the block descriptors. Otherwise, initialize *only* + // the first block descriptor, since for large allocations we don't + // need to give the invariant that Bdescr(p) is valid for any p in the + // block group. (This is because it is impossible to do, as the + // block descriptor table for the second mblock will get overwritten + // by contiguous user data.) + n = head->blocks > BLOCKS_PER_MBLOCK ? 1 : head->blocks; head->free = head->start; head->link = NULL; for (i=1, bd = head+1; i < n; i++, bd++) { @@ -259,6 +282,10 @@ split_free_block (bdescr *bd, W_ n, nat ln) return fg; } +/* Only initializes the start pointers on the first megablock and the + * blocks field of the first bdescr; callers are responsible for calling + * initGroup afterwards. + */ static bdescr * alloc_mega_group (StgWord mblocks) { @@ -278,7 +305,6 @@ alloc_mega_group (StgWord mblocks) } else { free_mblock_list = bd->link; } - initGroup(bd); return bd; } else if (bd->blocks > n) From git at git.haskell.org Tue Dec 31 15:14:22 2013 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 31 Dec 2013 15:14:22 +0000 (UTC) Subject: [commit: packages/base] master: s/therad/thread/ (072e299) Message-ID: <20131231151422.3D3212406B@ghc.haskell.org> Repository : ssh://git at git.haskell.org/base On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/072e299e5affd688bfbb35d120242238d259902b/base >--------------------------------------------------------------- commit 072e299e5affd688bfbb35d120242238d259902b Author: Edward Z. Yang Date: Tue Dec 31 23:13:58 2013 +0800 s/therad/thread/ Signed-off-by: Edward Z. Yang >--------------------------------------------------------------- 072e299e5affd688bfbb35d120242238d259902b Data/IORef.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Data/IORef.hs b/Data/IORef.hs index 1c1bb1b..0e5717c 100644 --- a/Data/IORef.hs +++ b/Data/IORef.hs @@ -150,7 +150,7 @@ atomicWriteIORef ref a = do operations cannot cause type-correct code to go wrong. In particular, when inspecting the value read from an 'IORef', the memory writes that created that value must have occurred from the - point of view of the current therad. + point of view of the current thread. 'atomicModifyIORef' acts as a barrier to reordering. Multiple 'atomicModifyIORef' operations occur in strict program order. An