From git at git.haskell.org Thu Nov 1 21:43:04 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 1 Nov 2018 21:43:04 +0000 (UTC) Subject: [commit: ghc] master: Actually fail in failIfEmitsConstraints (74ed9c1) Message-ID: <20181101214304.8BFBC3ABC0@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/74ed9c1c1b26971133c7166663b9c966d2eaca08/ghc >--------------------------------------------------------------- commit 74ed9c1c1b26971133c7166663b9c966d2eaca08 Author: Richard Eisenberg Date: Thu Nov 1 15:37:58 2018 -0400 Actually fail in failIfEmitsConstraints The function TcHsType.failIfEmitsConstraints says that it fails. It even does so in its name. But it didn't! It *reported* constraints but didn't fail. Now it does. This is important in tcHsClsInstType; see the comments therein. This was discovered while looking at #15797, but that ticket requires visible kind application to exhibit the bug; the test case will come with the patch for #12045. >--------------------------------------------------------------- 74ed9c1c1b26971133c7166663b9c966d2eaca08 compiler/typecheck/TcHsType.hs | 2 +- testsuite/tests/polykinds/T11520.stderr | 6 ------ testsuite/tests/rename/should_fail/T5951.stderr | 4 ---- testsuite/tests/rename/should_fail/rnfail026.stderr | 4 ---- testsuite/tests/typecheck/should_fail/T11563.stderr | 6 ------ testsuite/tests/typecheck/should_fail/T13909.stderr | 6 ------ testsuite/tests/typecheck/should_fail/T2994.stderr | 13 ------------- 7 files changed, 1 insertion(+), 40 deletions(-) diff --git a/compiler/typecheck/TcHsType.hs b/compiler/typecheck/TcHsType.hs index 3706c23..07c3a27 100644 --- a/compiler/typecheck/TcHsType.hs +++ b/compiler/typecheck/TcHsType.hs @@ -2871,7 +2871,7 @@ reportFloatingKvs tycon_name flav all_tvs bad_tvs failIfEmitsConstraints :: TcM a -> TcM a failIfEmitsConstraints thing_inside = do { (res, lie) <- captureConstraints thing_inside - ; reportAllUnsolved lie + ; checkNoErrs $ reportAllUnsolved lie ; return res } diff --git a/testsuite/tests/polykinds/T11520.stderr b/testsuite/tests/polykinds/T11520.stderr index 93078aa..11a81ba 100644 --- a/testsuite/tests/polykinds/T11520.stderr +++ b/testsuite/tests/polykinds/T11520.stderr @@ -1,10 +1,4 @@ -T11520.hs:15:57: error: - • Illegal type synonym family application ‘Any’ in instance: - Typeable (Compose f g) - Use -fprint-explicit-kinds to see the kind arguments - • In the instance declaration for ‘Typeable (Compose f g)’ - T11520.hs:15:77: error: • Expected kind ‘k20 -> k10’, but ‘g’ has kind ‘k’ • In the second argument of ‘Compose’, namely ‘g’ diff --git a/testsuite/tests/rename/should_fail/T5951.stderr b/testsuite/tests/rename/should_fail/T5951.stderr index a696997..8fda353 100644 --- a/testsuite/tests/rename/should_fail/T5951.stderr +++ b/testsuite/tests/rename/should_fail/T5951.stderr @@ -4,10 +4,6 @@ T5951.hs:8:8: error: Expected a constraint, but ‘A’ has kind ‘* -> Constraint’ • In the instance declaration for ‘B => C’ -T5951.hs:8:8: error: - • Instance head is not headed by a class: C - • In the instance declaration for ‘B => C’ - T5951.hs:9:8: error: • Expecting one more argument to ‘B’ Expected a constraint, but ‘B’ has kind ‘* -> Constraint’ diff --git a/testsuite/tests/rename/should_fail/rnfail026.stderr b/testsuite/tests/rename/should_fail/rnfail026.stderr index 79b07c4..c7ce103 100644 --- a/testsuite/tests/rename/should_fail/rnfail026.stderr +++ b/testsuite/tests/rename/should_fail/rnfail026.stderr @@ -1,8 +1,4 @@ -rnfail026.hs:16:10: error: - • Illegal polymorphic type: forall a. Eq a => Set a - • In the instance declaration for ‘Monad (forall a. Eq a => Set a)’ - rnfail026.hs:16:27: error: • Expected kind ‘* -> *’, but ‘Set a’ has kind ‘*’ • In the first argument of ‘Monad’, namely diff --git a/testsuite/tests/typecheck/should_fail/T11563.stderr b/testsuite/tests/typecheck/should_fail/T11563.stderr index 1283c33..27eca84 100644 --- a/testsuite/tests/typecheck/should_fail/T11563.stderr +++ b/testsuite/tests/typecheck/should_fail/T11563.stderr @@ -1,10 +1,4 @@ -T11563.hs:5:10: error: - • Variable ‘s’ occurs more often - in the constraint ‘C s’ than in the instance head ‘C T’ - (Use UndecidableInstances to permit this) - • In the instance declaration for ‘C T’ - T11563.hs:5:19: error: • Expecting one more argument to ‘T’ Expected a type, but ‘T’ has kind ‘* -> *’ diff --git a/testsuite/tests/typecheck/should_fail/T13909.stderr b/testsuite/tests/typecheck/should_fail/T13909.stderr index d70221c..599be5a 100644 --- a/testsuite/tests/typecheck/should_fail/T13909.stderr +++ b/testsuite/tests/typecheck/should_fail/T13909.stderr @@ -1,10 +1,4 @@ -T13909.hs:11:10: error: - • Illegal type synonym family application ‘GHC.Types.Any’ in instance: - HasName Hm - Use -fprint-explicit-kinds to see the kind arguments - • In the instance declaration for ‘HasName Hm’ - T13909.hs:11:18: error: • Expected kind ‘k0’, but ‘Hm’ has kind ‘forall k -> k -> *’ • In the first argument of ‘HasName’, namely ‘Hm’ diff --git a/testsuite/tests/typecheck/should_fail/T2994.stderr b/testsuite/tests/typecheck/should_fail/T2994.stderr index 09b3616..7f20acf 100644 --- a/testsuite/tests/typecheck/should_fail/T2994.stderr +++ b/testsuite/tests/typecheck/should_fail/T2994.stderr @@ -5,20 +5,12 @@ T2994.hs:11:10: error: but ‘MonadReader Int’ has kind ‘* -> Constraint’ • In the instance declaration for ‘MonadReader Int’ -T2994.hs:11:10: error: - • Instance head is not headed by a class: MonadReader Int - • In the instance declaration for ‘MonadReader Int’ - T2994.hs:13:10: error: • Expecting one more argument to ‘MonadReader (Reader' r)’ Expected a constraint, but ‘MonadReader (Reader' r)’ has kind ‘* -> Constraint’ • In the instance declaration for ‘MonadReader (Reader' r)’ -T2994.hs:13:10: error: - • Instance head is not headed by a class: MonadReader (Reader' r) - • In the instance declaration for ‘MonadReader (Reader' r)’ - T2994.hs:13:23: error: • Expecting one more argument to ‘Reader' r’ Expected a type, but ‘Reader' r’ has kind ‘* -> *’ @@ -29,8 +21,3 @@ T2994.hs:15:10: error: • Expected kind ‘(* -> *) -> Constraint’, but ‘MonadReader r r’ has kind ‘Constraint’ • In the instance declaration for ‘MonadReader r r (Reader' r)’ - -T2994.hs:15:10: error: - • Instance head is not headed by a class: - MonadReader r r (Reader' r) - • In the instance declaration for ‘MonadReader r r (Reader' r)’ From git at git.haskell.org Thu Nov 1 21:43:07 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 1 Nov 2018 21:43:07 +0000 (UTC) Subject: [commit: ghc] master: Fix embarrassing, egregious bug in roles of (->) (255d2e3) Message-ID: <20181101214307.95C4C3ABC0@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/255d2e323a8879a7296a5ab94e6cc49023e2c86e/ghc >--------------------------------------------------------------- commit 255d2e323a8879a7296a5ab94e6cc49023e2c86e Author: Richard Eisenberg Date: Thu Nov 1 15:07:36 2018 -0400 Fix embarrassing, egregious bug in roles of (->) Previously, I had inexplicably decided that (->)'s roles were all Representational. But, of course, its first two parameters are *dependent* RuntimeReps. All dependent parameters have a Nominal role, because all roles in kinds are Nominal. Fix is easy, but I have no idea how the world hasn't come crashing down before now. This was found while investigating #15801, which requires visible type application in types to observe. Hence, the test case will come with the main patch for #12045. >--------------------------------------------------------------- 255d2e323a8879a7296a5ab94e6cc49023e2c86e compiler/iface/IfaceSyn.hs | 2 +- compiler/types/TyCon.hs | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/iface/IfaceSyn.hs b/compiler/iface/IfaceSyn.hs index 3266c5a..7d1e697 100644 --- a/compiler/iface/IfaceSyn.hs +++ b/compiler/iface/IfaceSyn.hs @@ -903,7 +903,7 @@ pprRoles :: (Role -> Bool) -> SDoc -> [IfaceTyConBinder] pprRoles suppress_if tyCon bndrs roles = sdocWithDynFlags $ \dflags -> let froles = suppressIfaceInvisibles dflags bndrs roles - in ppUnless (all suppress_if roles || null froles) $ + in ppUnless (all suppress_if froles || null froles) $ text "type role" <+> tyCon <+> hsep (map ppr froles) pprInfixIfDeclBndr :: ShowHowMuch -> OccName -> SDoc diff --git a/compiler/types/TyCon.hs b/compiler/types/TyCon.hs index c96cb6b..eeebf8b 100644 --- a/compiler/types/TyCon.hs +++ b/compiler/types/TyCon.hs @@ -2259,7 +2259,7 @@ tyConRoles :: TyCon -> [Role] -- See also Note [TyCon Role signatures] tyConRoles tc = case tc of - { FunTyCon {} -> const_role Representational + { FunTyCon {} -> [Nominal, Nominal, Representational, Representational] ; AlgTyCon { tcRoles = roles } -> roles ; SynonymTyCon { tcRoles = roles } -> roles ; FamilyTyCon {} -> const_role Nominal From git at git.haskell.org Thu Nov 1 22:11:13 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 1 Nov 2018 22:11:13 +0000 (UTC) Subject: [commit: ghc] master: Don't lint erroneous programs. (1f72a1c) Message-ID: <20181101221113.827293ABC0@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1f72a1c81368e34387aac38c0b1c59521cec58ec/ghc >--------------------------------------------------------------- commit 1f72a1c81368e34387aac38c0b1c59521cec58ec Author: Richard Eisenberg Date: Thu Nov 1 18:03:21 2018 -0400 Don't lint erroneous programs. newFamInst lints its types. This is good. But it's not so good when there have been errors and thus recovery tycons are about. So we now don't. Fixes #15796. Test case: typecheck/should_fail/T15796 >--------------------------------------------------------------- 1f72a1c81368e34387aac38c0b1c59521cec58ec compiler/typecheck/FamInst.hs | 7 +++++-- testsuite/tests/typecheck/should_fail/T15796.hs | 8 ++++++++ testsuite/tests/typecheck/should_fail/T15796.stderr | 6 ++++++ testsuite/tests/typecheck/should_fail/all.T | 1 + 4 files changed, 20 insertions(+), 2 deletions(-) diff --git a/compiler/typecheck/FamInst.hs b/compiler/typecheck/FamInst.hs index 5825232..4944598 100644 --- a/compiler/typecheck/FamInst.hs +++ b/compiler/typecheck/FamInst.hs @@ -150,7 +150,7 @@ See #9562. -- It is defined here to avoid a dependency from FamInstEnv on the monad -- code. -newFamInst :: FamFlavor -> CoAxiom Unbranched -> TcRnIf gbl lcl FamInst +newFamInst :: FamFlavor -> CoAxiom Unbranched -> TcM FamInst -- Freshen the type variables of the FamInst branches newFamInst flavor axiom@(CoAxiom { co_ax_tc = fam_tc }) = ASSERT2( tyCoVarsOfTypes lhs `subVarSet` tcv_set, text "lhs" <+> pp_ax ) @@ -162,7 +162,10 @@ newFamInst flavor axiom@(CoAxiom { co_ax_tc = fam_tc }) ; let lhs' = substTys subst lhs rhs' = substTy subst rhs tcvs' = tvs' ++ cvs' - ; when (gopt Opt_DoCoreLinting dflags) $ + ; ifErrsM (return ()) $ -- Don't lint when there are errors, because + -- errors might mean TcTyCons. + -- See Note [Recover from validity error] in TcTyClsDecls + when (gopt Opt_DoCoreLinting dflags) $ -- Check that the types involved in this instance are well formed. -- Do /not/ expand type synonyms, for the reasons discussed in -- Note [Linting type synonym applications]. diff --git a/testsuite/tests/typecheck/should_fail/T15796.hs b/testsuite/tests/typecheck/should_fail/T15796.hs new file mode 100644 index 0000000..450064d --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T15796.hs @@ -0,0 +1,8 @@ +{-# LANGUAGE GADTs #-} +{-# LANGUAGE TypeFamilies #-} +module Bug where + +newtype N a where + MkN :: Show a => a -> N a +type family T a +type instance T (N a) = N a diff --git a/testsuite/tests/typecheck/should_fail/T15796.stderr b/testsuite/tests/typecheck/should_fail/T15796.stderr new file mode 100644 index 0000000..3aa7ae8 --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T15796.stderr @@ -0,0 +1,6 @@ + +T15796.hs:6:3: error: + • A newtype constructor cannot have a context in its type + MkN :: forall a. Show a => a -> N a + • In the definition of data constructor ‘MkN’ + In the newtype declaration for ‘N’ diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T index f80f5cd..c3a9f51 100644 --- a/testsuite/tests/typecheck/should_fail/all.T +++ b/testsuite/tests/typecheck/should_fail/all.T @@ -486,3 +486,4 @@ test('T15552a', normal, compile_fail, ['']) test('T15629', normal, compile_fail, ['']) test('T15767', normal, compile_fail, ['']) test('T15648', [extra_files(['T15648a.hs'])], multimod_compile_fail, ['T15648', '-v0 -fprint-equality-relations']) +test('T15796', normal, compile_fail, ['']) From git at git.haskell.org Fri Nov 2 00:34:23 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 2 Nov 2018 00:34:23 +0000 (UTC) Subject: [commit: ghc] master: hadrian: build ghc-iserv-prof in addition to ghc-iserv (695f1f2) Message-ID: <20181102003423.0A0AF3AC01@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/695f1f2fe03d71bad47d52f003881b34eb5083b4/ghc >--------------------------------------------------------------- commit 695f1f2fe03d71bad47d52f003881b34eb5083b4 Author: Alp Mestanogullari Date: Thu Nov 1 18:31:46 2018 -0400 hadrian: build ghc-iserv-prof in addition to ghc-iserv As it is required for 10+ tests. Hadrian didn't give us a chance to build a given executable in vanilla and profiling, simultaneously, under two different names. This patch implements support for this in general and applies it to ghc-iserv[-prof]. Test Plan: scc001 fails without this patch, passes with it. Reviewers: snowleopard, bgamari Reviewed By: bgamari Subscribers: simonpj, ndmitchell, simonmar, rwbarton, carter Differential Revision: https://phabricator.haskell.org/D5255 >--------------------------------------------------------------- 695f1f2fe03d71bad47d52f003881b34eb5083b4 hadrian/src/Packages.hs | 16 ++++++++++++---- hadrian/src/Rules/Program.hs | 21 +++++++++++++++------ hadrian/src/Rules/Test.hs | 11 ++++++----- 3 files changed, 33 insertions(+), 15 deletions(-) diff --git a/hadrian/src/Packages.hs b/hadrian/src/Packages.hs index 8a9a48f..4ce1a2c 100644 --- a/hadrian/src/Packages.hs +++ b/hadrian/src/Packages.hs @@ -132,10 +132,17 @@ programName Context {..} = do targetPlatform <- setting TargetPlatformFull let prefix = if cross then targetPlatform ++ "-" else "" -- TODO: Can we extract this information from Cabal files? + -- Alp: We could, but then the iserv package would have to + -- use Cabal conditionals + a 'profiling' flag + -- to declare the executable name, and I'm not sure + -- this is allowed (or desired for that matter). return $ prefix ++ case package of p | p == ghc -> "ghc" | p == hpcBin -> "hpc" - | p == iserv -> "ghc-iserv" + | p == iserv -> + if Profiling `wayUnit` way + then "ghc-iserv-prof" + else "ghc-iserv" _ -> pkgName package -- | The 'FilePath' to a program executable in a given 'Context'. @@ -144,10 +151,11 @@ programPath context at Context {..} = do -- TODO: The @touchy@ utility lives in the @lib/bin@ directory instead of -- @bin@, which is likely just a historical accident that should be fixed. -- See: https://github.com/snowleopard/hadrian/issues/570 - -- Likewise for 'unlit'. + -- Likewise for @iserv@ and @unlit at . name <- programName context - path <- if package `elem` [touchy, unlit] then stageLibPath stage <&> (-/- "bin") - else stageBinPath stage + path <- if package `elem` [iserv, touchy, unlit] + then stageLibPath stage <&> (-/- "bin") + else stageBinPath stage return $ path -/- name <.> exe -- TODO: Move @timeout@ to the @util@ directory and build in a more standard diff --git a/hadrian/src/Rules/Program.hs b/hadrian/src/Rules/Program.hs index f5be21a..7128a75 100644 --- a/hadrian/src/Rules/Program.hs +++ b/hadrian/src/Rules/Program.hs @@ -28,14 +28,23 @@ buildProgram rs = do -- TODO: Shall we use Stage2 for testsuite packages instead? let allPackages = sPackages ++ if stage == Stage1 then tPackages else [] - nameToCtxList <- forM allPackages $ \pkg -> do - let ctx = vanillaContext stage pkg - name <- programName ctx - return (name <.> exe, ctx) + nameToCtxList <- fmap concat . forM allPackages $ \pkg -> do + -- the iserv pkg results in two different programs at + -- the moment, ghc-iserv (built the vanilla way) + -- and ghc-iserv-prof (built the profiling way), and + -- the testsuite requires both to be present, so we + -- make sure that we cover these + -- "prof-build-under-other-name" cases. + -- iserv gets its two names from Packages.hs:programName + let ctxV = vanillaContext stage pkg + ctxProf = Context stage pkg profiling + nameV <- programName ctxV + nameProf <- programName ctxProf + return [ (nameV <.> exe, ctxV), (nameProf <.> exe, ctxProf) ] case lookup (takeFileName bin) nameToCtxList of Nothing -> error $ "Unknown program " ++ show bin - Just (Context {..}) -> do + Just ctx@(Context {..}) -> do -- Custom dependencies: this should be modeled better in the -- Cabal file somehow. -- TODO: Is this still needed? See 'runtimeDependencies'. @@ -58,7 +67,7 @@ buildProgram rs = do (False, s) | s > Stage0 && (package `elem` [touchy, unlit]) -> do srcDir <- stageLibPath Stage0 <&> (-/- "bin") copyFile (srcDir -/- takeFileName bin) bin - _ -> buildBinary rs bin =<< programContext stage package + _ -> buildBinary rs bin ctx buildBinary :: [(Resource, Int)] -> FilePath -> Context -> Action () buildBinary rs bin context at Context {..} = do diff --git a/hadrian/src/Rules/Test.hs b/hadrian/src/Rules/Test.hs index f5d6990..6a02ce6 100644 --- a/hadrian/src/Rules/Test.hs +++ b/hadrian/src/Rules/Test.hs @@ -81,12 +81,8 @@ testRules = do needTestsuitePackages :: Action () needTestsuitePackages = do targets <- mapM (needFile Stage1) =<< testsuitePackages - libPath <- stageLibPath Stage1 - iservPath <- needFile Stage1 iserv + needIservBins need targets - -- | We need to copy iserv bin to lib/bin as this is where testsuite looks - -- | for iserv. - copyFile iservPath $ libPath -/- "bin/ghc-iserv" -- | Build the timeout program. -- See: https://github.com/ghc/ghc/blob/master/testsuite/timeout/Makefile#L23 @@ -107,6 +103,11 @@ timeoutProgBuilder = do writeFile' (root -/- timeoutPath) script makeExecutable (root -/- timeoutPath) +needIservBins :: Action () +needIservBins = + need =<< traverse programPath + [ Context Stage1 iserv w | w <- [vanilla, profiling] ] + needTestBuilders :: Action () needTestBuilders = do needBuilder $ Ghc CompileHs Stage2 From git at git.haskell.org Fri Nov 2 00:34:26 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 2 Nov 2018 00:34:26 +0000 (UTC) Subject: [commit: ghc] master: Add built-in syntax suggestions, and refactor to allow library use (1c92f19) Message-ID: <20181102003426.112063AC01@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1c92f193ee406545daedd06e0b9d5d7354d9af64/ghc >--------------------------------------------------------------- commit 1c92f193ee406545daedd06e0b9d5d7354d9af64 Author: Matthías Páll Gissurarson Date: Thu Nov 1 18:32:32 2018 -0400 Add built-in syntax suggestions, and refactor to allow library use Summary: This change to the valid hole fits adds built-in syntax candidates (like (:) and []), so that they are checked in addition to what is in scope. The rest is merely a refactor and export of the functions used to find the valid hole fits, since there was interest at ICFP to use the valid hole fit machinery for additional uses. By exporting the `tcFilterHoleFits` function, this can now be done without having to rely on parsing the actual error message. Test Plan: Test for built-in syntax included Reviewers: bgamari Reviewed By: bgamari Subscribers: RyanGlScott, rwbarton, carter Differential Revision: https://phabricator.haskell.org/D5227 >--------------------------------------------------------------- 1c92f193ee406545daedd06e0b9d5d7354d9af64 compiler/typecheck/TcHoleErrors.hs | 434 ++++++++++++--------- .../tests/typecheck/should_compile/T14273.stderr | 5 +- .../abstract_refinement_hole_fits.stderr | 36 +- .../should_compile/constraint_hole_fits.stderr | 2 +- .../should_compile/hole_constraints.stderr | 2 + .../tests/typecheck/should_compile/holes.stderr | 14 +- .../tests/typecheck/should_compile/holes2.stderr | 3 +- .../tests/typecheck/should_compile/holes3.stderr | 14 +- .../should_compile/refinement_hole_fits.stderr | 4 +- .../should_compile/type_in_type_hole_fits.stderr | 30 +- .../typecheck/should_compile/valid_hole_fits.hs | 4 + .../should_compile/valid_hole_fits.stderr | 37 +- 12 files changed, 341 insertions(+), 244 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 1c92f193ee406545daedd06e0b9d5d7354d9af64 From git at git.haskell.org Fri Nov 2 00:34:29 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 2 Nov 2018 00:34:29 +0000 (UTC) Subject: [commit: ghc] master: Data.Maybe: add callstack for fromJust (Trac #15559) (614028e) Message-ID: <20181102003429.BA0923AC01@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/614028e3b02a5b71a9fbf9c7028f270760ccdab2/ghc >--------------------------------------------------------------- commit 614028e3b02a5b71a9fbf9c7028f270760ccdab2 Author: Fangyi Zhou Date: Thu Nov 1 18:21:23 2018 -0400 Data.Maybe: add callstack for fromJust (Trac #15559) Per feature request, add `HasCallStack` to `fromJust` in `Data.Maybe` and use `error` instead of `errorWithoutStackTrace`. This allows `fromJust` to print call stacks when throwing the error. Also add a new test case for the behaviour, modify existing test cases for new signature Test Plan: New test cases Reviewers: hvr, bgamari Reviewed By: bgamari Subscribers: ulysses4ever, rwbarton, carter GHC Trac Issues: #15559 Differential Revision: https://phabricator.haskell.org/D5256 >--------------------------------------------------------------- 614028e3b02a5b71a9fbf9c7028f270760ccdab2 libraries/base/Data/Maybe.hs | 5 +++-- libraries/base/tests/fromJust.hs | 10 ++++++++++ libraries/base/tests/fromJust.stderr | 4 ++++ testsuite/tests/ghci/scripts/ghci023.stdout | 2 +- testsuite/tests/ghci/scripts/ghci025.stdout | 2 +- testsuite/tests/ghci/scripts/ghci026.stdout | 2 +- 6 files changed, 20 insertions(+), 5 deletions(-) diff --git a/libraries/base/Data/Maybe.hs b/libraries/base/Data/Maybe.hs index d41ae92..2a3e0ef 100644 --- a/libraries/base/Data/Maybe.hs +++ b/libraries/base/Data/Maybe.hs @@ -32,6 +32,7 @@ module Data.Maybe ) where import GHC.Base +import GHC.Stack.Types ( HasCallStack ) -- $setup -- Allow the use of some Prelude functions in doctests. @@ -143,8 +144,8 @@ isNothing _ = False -- >>> 2 * (fromJust Nothing) -- *** Exception: Maybe.fromJust: Nothing -- -fromJust :: Maybe a -> a -fromJust Nothing = errorWithoutStackTrace "Maybe.fromJust: Nothing" -- yuck +fromJust :: HasCallStack => Maybe a -> a +fromJust Nothing = error "Maybe.fromJust: Nothing" -- yuck fromJust (Just x) = x -- | The 'fromMaybe' function takes a default value and and 'Maybe' diff --git a/libraries/base/tests/fromJust.hs b/libraries/base/tests/fromJust.hs new file mode 100644 index 0000000..2da524f --- /dev/null +++ b/libraries/base/tests/fromJust.hs @@ -0,0 +1,10 @@ +module Main where + +-- Trac #15559: Add HasCallStack to fromJust + +import Data.Maybe ( fromJust ) + +main :: IO () +main = do + _ <- fromJust Nothing `seq` return () + putStrLn "Should see a stacktrace instead of this" diff --git a/libraries/base/tests/fromJust.stderr b/libraries/base/tests/fromJust.stderr new file mode 100644 index 0000000..9b3a638 --- /dev/null +++ b/libraries/base/tests/fromJust.stderr @@ -0,0 +1,4 @@ +fromJust.hs: Maybe.fromJust: Nothing +CallStack (from HasCallStack): + error, called at libraries/base/Data/Maybe.hs:148:21 in base:Data.Maybe + fromJust, called at fromJust.hs:9:8 in main:Main diff --git a/testsuite/tests/ghci/scripts/ghci023.stdout b/testsuite/tests/ghci/scripts/ghci023.stdout index 334b67d..9403102 100644 --- a/testsuite/tests/ghci/scripts/ghci023.stdout +++ b/testsuite/tests/ghci/scripts/ghci023.stdout @@ -4,7 +4,7 @@ -- layout rule instead of explicit braces and semicolons works too (1,2,3) Data.Maybe.catMaybes :: [Maybe a] -> [a] -Data.Maybe.fromJust :: Maybe a -> a +Data.Maybe.fromJust :: GHC.Stack.Types.HasCallStack => Maybe a -> a Data.Maybe.fromMaybe :: a -> Maybe a -> a Data.Maybe.isJust :: Maybe a -> Bool Data.Maybe.isNothing :: Maybe a -> Bool diff --git a/testsuite/tests/ghci/scripts/ghci025.stdout b/testsuite/tests/ghci/scripts/ghci025.stdout index e5638b0..75933a9 100644 --- a/testsuite/tests/ghci/scripts/ghci025.stdout +++ b/testsuite/tests/ghci/scripts/ghci025.stdout @@ -25,7 +25,7 @@ class GHC.Base.Applicative m => Monad (m :: * -> *) ... -- imported via Data.Maybe catMaybes :: [Maybe a] -> [a] -fromJust :: Maybe a -> a +fromJust :: GHC.Stack.Types.HasCallStack => Maybe a -> a fromMaybe :: a -> Maybe a -> a isJust :: Maybe a -> GHC.Types.Bool isNothing :: Maybe a -> GHC.Types.Bool diff --git a/testsuite/tests/ghci/scripts/ghci026.stdout b/testsuite/tests/ghci/scripts/ghci026.stdout index 9fb2790..24049ee 100644 --- a/testsuite/tests/ghci/scripts/ghci026.stdout +++ b/testsuite/tests/ghci/scripts/ghci026.stdout @@ -1,5 +1,5 @@ catMaybes :: [Maybe a] -> [a] -fromJust :: Maybe a -> a +fromJust :: GHC.Stack.Types.HasCallStack => Maybe a -> a fromMaybe :: a -> Maybe a -> a isJust :: Maybe a -> Bool isNothing :: Maybe a -> Bool From git at git.haskell.org Fri Nov 2 00:34:32 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 2 Nov 2018 00:34:32 +0000 (UTC) Subject: [commit: ghc] master: users-guide: Fix formatting of eventlog format documentation (fcd919f) Message-ID: <20181102003432.B87C03AC01@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/fcd919f991452cc0d42805fca6e549c2efeb0dde/ghc >--------------------------------------------------------------- commit fcd919f991452cc0d42805fca6e549c2efeb0dde Author: Ben Gamari Date: Thu Nov 1 18:31:33 2018 -0400 users-guide: Fix formatting of eventlog format documentation Test Plan: Read it Reviewers: mpickering Reviewed By: mpickering Subscribers: rwbarton, carter Differential Revision: https://phabricator.haskell.org/D5264 >--------------------------------------------------------------- fcd919f991452cc0d42805fca6e549c2efeb0dde docs/users_guide/eventlog-formats.rst | 7 +++++++ 1 file changed, 7 insertions(+) diff --git a/docs/users_guide/eventlog-formats.rst b/docs/users_guide/eventlog-formats.rst index 9910d4d..6fd7d89 100644 --- a/docs/users_guide/eventlog-formats.rst +++ b/docs/users_guide/eventlog-formats.rst @@ -29,6 +29,7 @@ Beginning of sample stream A single fixed-width event emitted during program start-up describing the samples that follow. * ``EVENT_HEAP_PROF_BEGIN`` + * ``Word8``: Profile ID * ``Word64``: Sampling period in nanoseconds * ``Word32``: Sample break-down type. One of, @@ -55,6 +56,7 @@ Cost centre definitions A variable-length packet produced once for each cost centre, * ``EVENT_HEAP_PROF_COST_CENTRE`` + * ``Word32``: cost centre number * ``String``: label * ``String``: module @@ -74,6 +76,7 @@ We mark the beginning of a new sample with an ``EVENT_HEAP_PROF_SAMPLE_BEGIN`` event, * ``EVENT_HEAP_PROF_SAMPLE_BEGIN`` + * ``Word64``: sample number A heap residency census will follow. Since events may only be up to 2^16^ bytes @@ -88,7 +91,9 @@ Cost-centre break-down A variable-length packet encoding a heap profile sample broken down by, * cost-centre (``-hc``) + * ``EVENT_HEAP_PROF_SAMPLE_COST_CENTRE`` + * ``Word8``: Profile ID * ``Word64``: heap residency in bytes * ``Word8``: stack depth @@ -99,11 +104,13 @@ String break-down ^^^^^^^^^^^^^^^^^ A variable-length event encoding a heap sample broken down by, + * type description (``-hy``) * closure description (``-hd``) * module (``-hm``) * ``EVENT_HEAP_PROF_SAMPLE_STRING`` + * ``Word8``: Profile ID * ``Word64``: heap residency in bytes * ``String``: type or closure description, or module name From git at git.haskell.org Fri Nov 2 00:34:37 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 2 Nov 2018 00:34:37 +0000 (UTC) Subject: [commit: ghc] master: Lower precedence for {-# UNPACK #-} (a78e23b) Message-ID: <20181102003437.293503AC01@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a78e23b8bb614ded2ff842e3a5c2dc51db1fa790/ghc >--------------------------------------------------------------- commit a78e23b8bb614ded2ff842e3a5c2dc51db1fa790 Author: Vladislav Zavialov Date: Thu Nov 1 18:20:57 2018 -0400 Lower precedence for {-# UNPACK #-} Test Plan: Validate Reviewers: goldfire, bgamari Subscribers: osa1, mpickering, rwbarton, carter Differential Revision: https://phabricator.haskell.org/D5221 >--------------------------------------------------------------- a78e23b8bb614ded2ff842e3a5c2dc51db1fa790 compiler/parser/RdrHsSyn.hs | 120 +++++++++++++++------ docs/users_guide/8.8.1-notes.rst | 9 ++ testsuite/tests/parser/should_fail/all.T | 3 + .../parser/should_fail/strictnessDataCon_A.hs | 2 +- .../parser/should_fail/strictnessDataCon_A.stderr | 2 +- .../parser/should_fail/strictnessDataCon_B.hs | 2 +- .../parser/should_fail/strictnessDataCon_B.stderr | 4 +- .../tests/parser/should_fail/unpack_before_opr.hs | 6 ++ .../parser/should_fail/unpack_before_opr.stderr | 3 + .../tests/parser/should_fail/unpack_empty_type.hs | 3 + .../parser/should_fail/unpack_empty_type.stderr | 3 + .../tests/parser/should_fail/unpack_inside_type.hs | 3 + .../parser/should_fail/unpack_inside_type.stderr | 3 + .../tests/typecheck/should_compile/T14761c.hs | 21 ++++ testsuite/tests/typecheck/should_compile/all.T | 1 + testsuite/tests/typecheck/should_fail/T14761a.hs | 19 +++- .../tests/typecheck/should_fail/T14761a.stderr | 18 +++- 17 files changed, 177 insertions(+), 45 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 a78e23b8bb614ded2ff842e3a5c2dc51db1fa790 From git at git.haskell.org Fri Nov 2 00:34:40 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 2 Nov 2018 00:34:40 +0000 (UTC) Subject: [commit: ghc] master: Move eta-reduced coaxiom compatibility handling quirks into FamInstEnv. (f877d9c) Message-ID: <20181102003440.BF1393AC01@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f877d9cc99dd1ba0c038e70527031e9ba0934cd3/ghc >--------------------------------------------------------------- commit f877d9cc99dd1ba0c038e70527031e9ba0934cd3 Author: mniip Date: Thu Nov 1 18:33:10 2018 -0400 Move eta-reduced coaxiom compatibility handling quirks into FamInstEnv. The quirk caused an issue where GHC concluded that 'D' is possibly unifiable with 'D a' (the two types could have the same kind if D is a data family). Test Plan: Ensure T9371 stays fixed. Introduce T15704 Reviewers: goldfire, bgamari Reviewed By: goldfire Subscribers: RyanGlScott, rwbarton, carter GHC Trac Issues: #15704 Differential Revision: https://phabricator.haskell.org/D5206 >--------------------------------------------------------------- f877d9cc99dd1ba0c038e70527031e9ba0934cd3 compiler/types/FamInstEnv.hs | 31 +++++++++++++++++++++- compiler/types/Unify.hs | 23 ++-------------- compiler/utils/Util.hs | 11 +++++++- .../tests/indexed-types/should_compile/T15704.hs | 12 +++++++++ testsuite/tests/indexed-types/should_compile/all.T | 1 + 5 files changed, 55 insertions(+), 23 deletions(-) diff --git a/compiler/types/FamInstEnv.hs b/compiler/types/FamInstEnv.hs index a5cfba1..d149dbf 100644 --- a/compiler/types/FamInstEnv.hs +++ b/compiler/types/FamInstEnv.hs @@ -551,13 +551,42 @@ find a branch that matches the target, but then we make sure that the target is apart from every previous *incompatible* branch. We don't check the branches that are compatible with the matching branch, because they are either irrelevant (clause 1 of compatible) or benign (clause 2 of compatible). + +Note [Compatibility of eta-reduced axioms] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +In newtype instances of data families we eta-reduce the axioms, +See Note [Eta reduction for data family axioms] in TcInstDcls. This means that +we sometimes need to test compatibility of two axioms that were eta-reduced to +different degrees, e.g.: + + +data family D a b c +newtype instance D a Int c = DInt (Maybe a) + -- D a Int ~ Maybe + -- lhs = [a, Int] +newtype instance D Bool Int Char = DIntChar Float + -- D Bool Int Char ~ Float + -- lhs = [Bool, Int, Char] + +These are obviously incompatible. We could detect this by saturating +(eta-expanding) the shorter LHS with fresh tyvars until the lists are of +equal length, but instead we can just remove the tail of the longer list, as +those types will simply unify with the freshly introduced tyvars. + +By doing this, in case the LHS are unifiable, the yielded substitution won't +mention the tyvars that appear in the tail we dropped off, and we might try +to test equality RHSes of different kinds, but that's fine since this case +occurs only for data families, where the RHS is a unique tycon and the equality +fails anyway. -} -- See Note [Compatibility] compatibleBranches :: CoAxBranch -> CoAxBranch -> Bool compatibleBranches (CoAxBranch { cab_lhs = lhs1, cab_rhs = rhs1 }) (CoAxBranch { cab_lhs = lhs2, cab_rhs = rhs2 }) - = case tcUnifyTysFG (const BindMe) lhs1 lhs2 of + = let (commonlhs1, commonlhs2) = zipAndUnzip lhs1 lhs2 + -- See Note [Compatibility of eta-reduced axioms] + in case tcUnifyTysFG (const BindMe) commonlhs1 commonlhs2 of SurelyApart -> True Unifiable subst | Type.substTyAddInScope subst rhs1 `eqType` diff --git a/compiler/types/Unify.hs b/compiler/types/Unify.hs index 60bba12..951a3f9 100644 --- a/compiler/types/Unify.hs +++ b/compiler/types/Unify.hs @@ -344,26 +344,6 @@ If we discover that two types unify if and only if a skolem variable is substituted, we can't properly unify the types. But, that skolem variable may later be instantiated with a unifyable type. So, we return maybeApart in these cases. - -Note [Lists of different lengths are MaybeApart] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -It is unusual to call tcUnifyTys or tcUnifyTysFG with lists of different -lengths. The place where we know this can happen is from compatibleBranches in -FamInstEnv, when checking data family instances. Data family instances may be -eta-reduced; see Note [Eta reduction for data family axioms] in TcInstDcls. - -We wish to say that - - D :: * -> * -> * - axDF1 :: D Int ~ DFInst1 - axDF2 :: D Int Bool ~ DFInst2 - -overlap. If we conclude that lists of different lengths are SurelyApart, then -it will look like these do *not* overlap, causing disaster. See Trac #9371. - -In usages of tcUnifyTys outside of family instances, we always use tcUnifyTys, -which can't tell the difference between MaybeApart and SurelyApart, so those -usages won't notice this design choice. -} -- | Simple unification of two types; all type variables are bindable @@ -1044,7 +1024,8 @@ unify_tys env orig_xs orig_ys -- See Note [Kind coercions in Unify] = do { unify_ty env x y (mkNomReflCo $ typeKind x) ; go xs ys } - go _ _ = maybeApart -- See Note [Lists of different lengths are MaybeApart] + go _ _ = surelyApart + -- Possibly different saturations of a polykinded tycon (See Trac #15704) --------------------------------- uVar :: UMEnv diff --git a/compiler/utils/Util.hs b/compiler/utils/Util.hs index c348f79..c6c5362 100644 --- a/compiler/utils/Util.hs +++ b/compiler/utils/Util.hs @@ -16,7 +16,7 @@ module Util ( -- * General list processing zipEqual, zipWithEqual, zipWith3Equal, zipWith4Equal, - zipLazy, stretchZipWith, zipWithAndUnzip, + zipLazy, stretchZipWith, zipWithAndUnzip, zipAndUnzip, zipWithLazy, zipWith3Lazy, @@ -441,6 +441,15 @@ zipWithAndUnzip f (a:as) (b:bs) (r1:rs1, r2:rs2) zipWithAndUnzip _ _ _ = ([],[]) +-- | This has the effect of making the two lists have equal length by dropping +-- the tail of the longer one. +zipAndUnzip :: [a] -> [b] -> ([a],[b]) +zipAndUnzip (a:as) (b:bs) + = let (rs1, rs2) = zipAndUnzip as bs + in + (a:rs1, b:rs2) +zipAndUnzip _ _ = ([],[]) + mapAccumL2 :: (s1 -> s2 -> a -> (s1, s2, b)) -> s1 -> s2 -> [a] -> (s1, s2, [b]) mapAccumL2 f s1 s2 xs = (s1', s2', ys) where ((s1', s2'), ys) = mapAccumL (\(s1, s2) x -> case f s1 s2 x of diff --git a/testsuite/tests/indexed-types/should_compile/T15704.hs b/testsuite/tests/indexed-types/should_compile/T15704.hs new file mode 100644 index 0000000..fbd317f --- /dev/null +++ b/testsuite/tests/indexed-types/should_compile/T15704.hs @@ -0,0 +1,12 @@ +{-# LANGUAGE TypeFamilies, PolyKinds #-} + +module T15704 where + +import Data.Kind + +data family D :: k + +type family F (a :: k) :: Type + +type instance F D = Int +type instance F (D a) = Char diff --git a/testsuite/tests/indexed-types/should_compile/all.T b/testsuite/tests/indexed-types/should_compile/all.T index 687e71d..5725c96 100644 --- a/testsuite/tests/indexed-types/should_compile/all.T +++ b/testsuite/tests/indexed-types/should_compile/all.T @@ -294,4 +294,5 @@ test('T15322a', normal, compile_fail, ['']) test('T15142', normal, compile, ['']) test('T15352', normal, compile, ['']) test('T15664', normal, compile, ['']) +test('T15704', normal, compile, ['']) test('T15711', normal, compile, ['-ddump-types']) From git at git.haskell.org Fri Nov 2 15:36:56 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 2 Nov 2018 15:36:56 +0000 (UTC) Subject: [commit: ghc] ghc-8.6: users-guide: Fix version number (cfc3ad1) Message-ID: <20181102153656.89A313AC01@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.6 Link : http://ghc.haskell.org/trac/ghc/changeset/cfc3ad1fabe6a01da0571caf457811a30d1779c2/ghc >--------------------------------------------------------------- commit cfc3ad1fabe6a01da0571caf457811a30d1779c2 Author: Ben Gamari Date: Wed Oct 31 12:23:39 2018 -0400 users-guide: Fix version number >--------------------------------------------------------------- cfc3ad1fabe6a01da0571caf457811a30d1779c2 docs/users_guide/8.6.2-notes.rst | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/docs/users_guide/8.6.2-notes.rst b/docs/users_guide/8.6.2-notes.rst index 2dd2508..5fc6d8f 100644 --- a/docs/users_guide/8.6.2-notes.rst +++ b/docs/users_guide/8.6.2-notes.rst @@ -35,7 +35,7 @@ The highlights, since the 8.6.1 release, are: Known issues ------------ -Note that the LLVM code generator (:ghc-flag:`-fllvm`) in GHC 8.8, as well as +Note that the LLVM code generator (:ghc-flag:`-fllvm`) in GHC 8.6, as well as all earlier releases, are affected by :ghc-ticket:`14251`, which can result in miscompilation of some programs calling functions with unboxed floating-point arguments. While originally scheduled to be fixed for this release, the fix From git at git.haskell.org Fri Nov 2 15:37:11 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 2 Nov 2018 15:37:11 +0000 (UTC) Subject: [commit: ghc] ghc-8.6: Fix #15787 by squashing a coercion hole. (7a439e7) Message-ID: <20181102153711.BB6AE3AC01@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.6 Link : http://ghc.haskell.org/trac/ghc/changeset/7a439e7b13f350e1ac6163f1bfa60e30924dbeea/ghc >--------------------------------------------------------------- commit 7a439e7b13f350e1ac6163f1bfa60e30924dbeea Author: Richard Eisenberg Date: Sun Oct 28 16:06:17 2018 -0400 Fix #15787 by squashing a coercion hole. In type-incorrect code, we can sometimes let a coercion hole make it through the zonker. If this coercion hole then ends up in the environment (e.g., in the type of a data constructor), then it causes trouble later. This patch avoids trouble by substituting the coercion hole for its representative CoVar. Really, any coercion would do, but the CoVar was very handy. test case: polykinds/T15787 (cherry picked from commit 4427315a65b25db22e1754d41b43dd4b782b022f) >--------------------------------------------------------------- 7a439e7b13f350e1ac6163f1bfa60e30924dbeea compiler/typecheck/TcHsSyn.hs | 4 +++- testsuite/tests/polykinds/T15787.hs | 19 +++++++++++++++++++ testsuite/tests/polykinds/T15787.stderr | 6 ++++++ testsuite/tests/polykinds/all.T | 1 + 4 files changed, 29 insertions(+), 1 deletion(-) diff --git a/compiler/typecheck/TcHsSyn.hs b/compiler/typecheck/TcHsSyn.hs index b3f9a691..986047b 100644 --- a/compiler/typecheck/TcHsSyn.hs +++ b/compiler/typecheck/TcHsSyn.hs @@ -1673,7 +1673,9 @@ zonkCoHole env hole@(CoercionHole { ch_ref = ref, ch_co_var = cv }) , text "Type-correct unfilled coercion hole" <+> ppr hole ) ; cv' <- zonkCoVar cv - ; return $ mkHoleCo (hole { ch_co_var = cv' }) } } + ; return $ mkCoVarCo cv' } } + -- This will be an out-of-scope variable, but keeping + -- this as a coercion hole led to #15787 zonk_tycomapper :: TyCoMapper ZonkEnv TcM zonk_tycomapper = TyCoMapper diff --git a/testsuite/tests/polykinds/T15787.hs b/testsuite/tests/polykinds/T15787.hs new file mode 100644 index 0000000..85e737a --- /dev/null +++ b/testsuite/tests/polykinds/T15787.hs @@ -0,0 +1,19 @@ +{-# Language RankNTypes #-} +{-# Language TypeApplications #-} +{-# Language DataKinds #-} +{-# Language PolyKinds #-} +{-# Language GADTs #-} +{-# Language TypeFamilies #-} + +import Data.Kind + +class Ríki (ob :: Type) where + type Hom :: ob -> ob -> Type + +data + Kl_kind :: forall ob . (ob -> ob) -> ob -> Type where + Kl :: k -> Kl_kind (m :: ob -> ob) k + +type family + UnKl (kl :: Kl_kind m k) = (res :: k) where + UnKl (Kl a) = a diff --git a/testsuite/tests/polykinds/T15787.stderr b/testsuite/tests/polykinds/T15787.stderr new file mode 100644 index 0000000..6d368d5 --- /dev/null +++ b/testsuite/tests/polykinds/T15787.stderr @@ -0,0 +1,6 @@ + +T15787.hs:15:43: error: + • Expected kind ‘ob’, but ‘k’ has kind ‘*’ + • In the second argument of ‘Kl_kind’, namely ‘k’ + In the type ‘Kl_kind (m :: ob -> ob) k’ + In the definition of data constructor ‘Kl’ diff --git a/testsuite/tests/polykinds/all.T b/testsuite/tests/polykinds/all.T index 2d0f993..53a33e3 100644 --- a/testsuite/tests/polykinds/all.T +++ b/testsuite/tests/polykinds/all.T @@ -193,3 +193,4 @@ test('T15116a', normal, compile_fail, ['']) test('T15170', normal, compile, ['']) test('T14939', normal, compile, ['-O']) test('T15577', normal, compile_fail, ['-O']) +test('T15787', normal, compile_fail, ['']) From git at git.haskell.org Fri Nov 2 15:37:23 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 2 Nov 2018 15:37:23 +0000 (UTC) Subject: [commit: ghc] ghc-8.6: Don't lint erroneous programs. (41f0f6c) Message-ID: <20181102153723.493513AC01@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.6 Link : http://ghc.haskell.org/trac/ghc/changeset/41f0f6c2f571ea05c49f9f6ed64beebdc5a9f9fc/ghc >--------------------------------------------------------------- commit 41f0f6c2f571ea05c49f9f6ed64beebdc5a9f9fc Author: Richard Eisenberg Date: Thu Nov 1 18:03:21 2018 -0400 Don't lint erroneous programs. newFamInst lints its types. This is good. But it's not so good when there have been errors and thus recovery tycons are about. So we now don't. Fixes #15796. Test case: typecheck/should_fail/T15796 (cherry picked from commit 1f72a1c81368e34387aac38c0b1c59521cec58ec) >--------------------------------------------------------------- 41f0f6c2f571ea05c49f9f6ed64beebdc5a9f9fc compiler/typecheck/FamInst.hs | 7 +++++-- testsuite/tests/typecheck/should_fail/T15796.hs | 8 ++++++++ testsuite/tests/typecheck/should_fail/T15796.stderr | 6 ++++++ testsuite/tests/typecheck/should_fail/all.T | 1 + 4 files changed, 20 insertions(+), 2 deletions(-) diff --git a/compiler/typecheck/FamInst.hs b/compiler/typecheck/FamInst.hs index 00602ec..eff33e3 100644 --- a/compiler/typecheck/FamInst.hs +++ b/compiler/typecheck/FamInst.hs @@ -150,7 +150,7 @@ See #9562. -- It is defined here to avoid a dependency from FamInstEnv on the monad -- code. -newFamInst :: FamFlavor -> CoAxiom Unbranched -> TcRnIf gbl lcl FamInst +newFamInst :: FamFlavor -> CoAxiom Unbranched -> TcM FamInst -- Freshen the type variables of the FamInst branches newFamInst flavor axiom@(CoAxiom { co_ax_tc = fam_tc }) = ASSERT2( tyCoVarsOfTypes lhs `subVarSet` tcv_set, text "lhs" <+> pp_ax ) @@ -162,7 +162,10 @@ newFamInst flavor axiom@(CoAxiom { co_ax_tc = fam_tc }) ; let lhs' = substTys subst lhs rhs' = substTy subst rhs tcvs' = tvs' ++ cvs' - ; when (gopt Opt_DoCoreLinting dflags) $ + ; ifErrsM (return ()) $ -- Don't lint when there are errors, because + -- errors might mean TcTyCons. + -- See Note [Recover from validity error] in TcTyClsDecls + when (gopt Opt_DoCoreLinting dflags) $ -- Check that the types involved in this instance are well formed. -- Do /not/ expand type synonyms, for the reasons discussed in -- Note [Linting type synonym applications]. diff --git a/testsuite/tests/typecheck/should_fail/T15796.hs b/testsuite/tests/typecheck/should_fail/T15796.hs new file mode 100644 index 0000000..450064d --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T15796.hs @@ -0,0 +1,8 @@ +{-# LANGUAGE GADTs #-} +{-# LANGUAGE TypeFamilies #-} +module Bug where + +newtype N a where + MkN :: Show a => a -> N a +type family T a +type instance T (N a) = N a diff --git a/testsuite/tests/typecheck/should_fail/T15796.stderr b/testsuite/tests/typecheck/should_fail/T15796.stderr new file mode 100644 index 0000000..3aa7ae8 --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T15796.stderr @@ -0,0 +1,6 @@ + +T15796.hs:6:3: error: + • A newtype constructor cannot have a context in its type + MkN :: forall a. Show a => a -> N a + • In the definition of data constructor ‘MkN’ + In the newtype declaration for ‘N’ diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T index e12aba6..1b635cf 100644 --- a/testsuite/tests/typecheck/should_fail/all.T +++ b/testsuite/tests/typecheck/should_fail/all.T @@ -477,3 +477,4 @@ test('T15067', normal, compile_fail, ['']) test('T15361', normal, compile_fail, ['']) test('T15527', normal, compile_fail, ['']) test('T15767', normal, compile_fail, ['']) +test('T15796', normal, compile_fail, ['']) From git at git.haskell.org Fri Nov 2 15:40:27 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 2 Nov 2018 15:40:27 +0000 (UTC) Subject: [commit: ghc] tag 'ghc-8.6.2-release' created Message-ID: <20181102154027.9C83B3AC01@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New tag : ghc-8.6.2-release Referencing: bd9fd4938864bf0bc6cd14ff36c7f3150dd03969 From git at git.haskell.org Fri Nov 2 16:48:46 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 2 Nov 2018 16:48:46 +0000 (UTC) Subject: [commit: ghc] master: users-guide: Update link to Safe Coercions paper (efb3145) Message-ID: <20181102164846.C3C263AC01@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/efb314582f1a1974d68505bbf9312f130416ef65/ghc >--------------------------------------------------------------- commit efb314582f1a1974d68505bbf9312f130416ef65 Author: Ben Gamari Date: Fri Nov 2 12:43:25 2018 -0400 users-guide: Update link to Safe Coercions paper Fixes #15841. >--------------------------------------------------------------- efb314582f1a1974d68505bbf9312f130416ef65 docs/users_guide/glasgow_exts.rst | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst index 723f1a3..5cf50b7 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -9725,7 +9725,7 @@ denotes representational equality between ``t1`` and ``t2`` in the sense of Roles (:ref:`roles`). It is exported by :base-ref:`Data.Coerce.`, which also contains the documentation. More details and discussion can be found in the paper -`"Safe Coercions" `__. +`"Safe Coercions" `__. .. _constraint-kind: From git at git.haskell.org Fri Nov 2 18:11:02 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 2 Nov 2018 18:11:02 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Tc-tracing, and order of arguments only (0901381) Message-ID: <20181102181102.5DC893AC01@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/090138153e963805da071be6cf7e05c32ce598c3/ghc >--------------------------------------------------------------- commit 090138153e963805da071be6cf7e05c32ce598c3 Author: Simon Peyton Jones Date: Wed Oct 31 08:31:38 2018 +0000 Tc-tracing, and order of arguments only I changed the order of arguments to reportAllUnsolved, and the tc-tracing that surrounds it. No change in behaviour >--------------------------------------------------------------- 090138153e963805da071be6cf7e05c32ce598c3 compiler/typecheck/TcErrors.hs | 29 ++++++++++++++++------------- compiler/typecheck/TcRnMonad.hs | 2 ++ compiler/typecheck/TcSimplify.hs | 4 ---- 3 files changed, 18 insertions(+), 17 deletions(-) diff --git a/compiler/typecheck/TcErrors.hs b/compiler/typecheck/TcErrors.hs index 1fd98f1..ee80ded 100644 --- a/compiler/typecheck/TcErrors.hs +++ b/compiler/typecheck/TcErrors.hs @@ -146,8 +146,9 @@ reportUnsolved wanted | warn_out_of_scope = HoleWarn | otherwise = HoleDefer - ; report_unsolved binds_var type_errors expr_holes - type_holes out_of_scope_holes wanted + ; report_unsolved type_errors expr_holes + type_holes out_of_scope_holes + binds_var wanted ; ev_binds <- getTcEvBindsMap binds_var ; return (evBindMapBinds ev_binds)} @@ -162,8 +163,8 @@ reportUnsolved wanted reportAllUnsolved :: WantedConstraints -> TcM () reportAllUnsolved wanted = do { ev_binds <- newNoTcEvBinds - ; report_unsolved ev_binds TypeError - HoleError HoleError HoleError wanted } + ; report_unsolved TypeError HoleError HoleError HoleError + ev_binds wanted } -- | Report all unsolved goals as warnings (but without deferring any errors to -- run-time). See Note [Safe Haskell Overlapping Instances Implementation] in @@ -171,22 +172,23 @@ reportAllUnsolved wanted warnAllUnsolved :: WantedConstraints -> TcM () warnAllUnsolved wanted = do { ev_binds <- newTcEvBinds - ; report_unsolved ev_binds (TypeWarn NoReason) - HoleWarn HoleWarn HoleWarn wanted } + ; report_unsolved (TypeWarn NoReason) HoleWarn HoleWarn HoleWarn + ev_binds wanted } -- | Report unsolved goals as errors or warnings. -report_unsolved :: EvBindsVar -- cec_binds - -> TypeErrorChoice -- Deferred type errors +report_unsolved :: TypeErrorChoice -- Deferred type errors -> HoleChoice -- Expression holes -> HoleChoice -- Type holes -> HoleChoice -- Out of scope holes + -> EvBindsVar -- cec_binds -> WantedConstraints -> TcM () -report_unsolved mb_binds_var type_errors expr_holes - type_holes out_of_scope_holes wanted +report_unsolved type_errors expr_holes + type_holes out_of_scope_holes binds_var wanted | isEmptyWC wanted = return () | otherwise - = do { traceTc "reportUnsolved warning/error settings:" $ + = do { traceTc "reportUnsolved {" empty + ; traceTc "reportUnsolved warning/error settings:" $ vcat [ text "type errors:" <+> ppr type_errors , text "expr holes:" <+> ppr expr_holes , text "type holes:" <+> ppr type_holes @@ -219,10 +221,11 @@ report_unsolved mb_binds_var type_errors expr_holes -- See Trac #15539 and c.f. setting ic_status -- in TcSimplify.setImplicationStatus , cec_warn_redundant = warn_redundant - , cec_binds = mb_binds_var } + , cec_binds = binds_var } ; tc_lvl <- getTcLevel - ; reportWanteds err_ctxt tc_lvl wanted } + ; reportWanteds err_ctxt tc_lvl wanted + ; traceTc "reportUnsolved }" empty } -------------------------------------------- -- Internal functions diff --git a/compiler/typecheck/TcRnMonad.hs b/compiler/typecheck/TcRnMonad.hs index bef1044..5e6cb8f 100644 --- a/compiler/typecheck/TcRnMonad.hs +++ b/compiler/typecheck/TcRnMonad.hs @@ -1532,8 +1532,10 @@ pushLevelAndCaptureConstraints :: TcM a -> TcM (TcLevel, WantedConstraints, a) pushLevelAndCaptureConstraints thing_inside = do { env <- getLclEnv ; let tclvl' = pushTcLevel (tcl_tclvl env) + ; traceTc "pushLevelAndCaptureConstraints {" (ppr tclvl') ; (res, lie) <- setLclEnv (env { tcl_tclvl = tclvl' }) $ captureConstraints thing_inside + ; traceTc "pushLevelAndCaptureConstraints }" (ppr tclvl') ; return (tclvl', lie, res) } pushTcLevelM_ :: TcM a -> TcM a diff --git a/compiler/typecheck/TcSimplify.hs b/compiler/typecheck/TcSimplify.hs index 6ef62c8..c424a02 100644 --- a/compiler/typecheck/TcSimplify.hs +++ b/compiler/typecheck/TcSimplify.hs @@ -178,9 +178,7 @@ solveEqualities thing_inside -- vars to LiftedRep. This is needed to avoid #14991. ; traceTc "End solveEqualities }" empty - ; traceTc "reportAllUnsolved {" empty ; reportAllUnsolved final_wc - ; traceTc "reportAllUnsolved }" empty ; return result } -- | Simplify top-level constraints, but without reporting any unsolved @@ -514,9 +512,7 @@ simplifyDefault theta = do { traceTc "simplifyDefault" empty ; wanteds <- newWanteds DefaultOrigin theta ; unsolved <- runTcSDeriveds (solveWantedsAndDrop (mkSimpleWC wanteds)) - ; traceTc "reportUnsolved {" empty ; reportAllUnsolved unsolved - ; traceTc "reportUnsolved }" empty ; return () } ------------------ From git at git.haskell.org Fri Nov 2 18:11:05 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 2 Nov 2018 18:11:05 +0000 (UTC) Subject: [commit: ghc] wip/T15809: WIP on using level numbers for generalisation (9d70d5a) Message-ID: <20181102181105.6320A3AC01@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/9d70d5a8d1a189456537213b47b7a1c873308ec7/ghc >--------------------------------------------------------------- commit 9d70d5a8d1a189456537213b47b7a1c873308ec7 Author: Simon Peyton Jones Date: Wed Oct 31 08:40:40 2018 +0000 WIP on using level numbers for generalisation This mostly works. So far I simply have a WARNING in quantifyTyVars which fires if the two methods (old "global-tyvars" and new "level-numbers") give different answers. Some modest but important refactoring along the way. Main thing that is still wrong: in instance declarations we are not skoelmising. Here's a partial patch to TcInstDcls, that /doesn't/ yet work -- Next, process any associated types. ; traceTc "tcLocalInstDecl" (ppr poly_ty) - ; tyfam_insts0 <- scopeTyVars InstSkol tyvars $ - mapAndRecoverM (tcTyFamInstDecl mb_info) ats - ; datafam_stuff <- scopeTyVars InstSkol tyvars $ - mapAndRecoverM (tcDataFamInstDecl mb_info) adts + ; (_subst, skol_tvs) <- tcInstSkolTyVars tyvars + ; (tyfam_insts0, datafam_stuff) + <- tcExtendNameTyVarEnv (map tyVarName tyvars `zip` skol_tvs) $ + do { tfs <- mapAndRecoverM (tcTyFamInstDecl mb_info) ats + ; dfs <- mapAndRecoverM (tcDataFamInstDecl mb_info) adts + ; return (tfs, dfs) } ; let (datafam_insts, m_deriv_infos) = unzip datafam_stuff >--------------------------------------------------------------- 9d70d5a8d1a189456537213b47b7a1c873308ec7 compiler/typecheck/TcHsType.hs | 93 +++++++++++++++++++++++------------ compiler/typecheck/TcMType.hs | 99 ++++++++++++++++++++++++++------------ compiler/typecheck/TcSimplify.hs | 19 +++++--- compiler/typecheck/TcTyClsDecls.hs | 86 ++++++++++++++++----------------- compiler/typecheck/TcValidity.hs | 12 ++--- 5 files changed, 191 insertions(+), 118 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 9d70d5a8d1a189456537213b47b7a1c873308ec7 From git at git.haskell.org Fri Nov 2 18:11:08 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 2 Nov 2018 18:11:08 +0000 (UTC) Subject: [commit: ghc] wip/T15809: More progress on using level numbers for gen (3055b0a) Message-ID: <20181102181108.743633AC01@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/3055b0a19c951cb6198950a31c6ca2ee4c50a59a/ghc >--------------------------------------------------------------- commit 3055b0a19c951cb6198950a31c6ca2ee4c50a59a Author: Simon Peyton Jones Date: Wed Oct 31 15:00:16 2018 +0000 More progress on using level numbers for gen >--------------------------------------------------------------- 3055b0a19c951cb6198950a31c6ca2ee4c50a59a compiler/typecheck/TcHsType.hs | 196 ++++++++++++++++++------------------- compiler/typecheck/TcInstDcls.hs | 11 +-- compiler/typecheck/TcMType.hs | 5 +- compiler/typecheck/TcSimplify.hs | 11 ++- compiler/typecheck/TcTyClsDecls.hs | 8 +- 5 files changed, 112 insertions(+), 119 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 3055b0a19c951cb6198950a31c6ca2ee4c50a59a From git at git.haskell.org Fri Nov 2 18:11:11 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 2 Nov 2018 18:11:11 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Further work on TyCon generalisation (b152e99) Message-ID: <20181102181111.7EAFC3AC01@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/b152e99478ed641629a2229a2eb0c800277b2a03/ghc >--------------------------------------------------------------- commit b152e99478ed641629a2229a2eb0c800277b2a03 Author: Simon Peyton Jones Date: Fri Nov 2 18:06:16 2018 +0000 Further work on TyCon generalisation >--------------------------------------------------------------- b152e99478ed641629a2229a2eb0c800277b2a03 compiler/typecheck/TcHsType.hs | 109 +++++++++++---------- compiler/typecheck/TcMType.hs | 54 +++++++--- compiler/typecheck/TcRnTypes.hs | 8 +- compiler/typecheck/TcTyClsDecls.hs | 93 +++++------------- compiler/types/TyCoRep.hs | 16 ++- compiler/types/Type.hs | 2 +- testsuite/tests/dependent/should_compile/T14880.hs | 1 + .../tests/dependent/should_compile/T15743e.stderr | 6 +- .../tests/indexed-types/should_fail/T13972.stderr | 2 +- testsuite/tests/polykinds/T11520.stderr | 6 -- testsuite/tests/polykinds/T12593.stderr | 8 +- testsuite/tests/rename/should_fail/T5951.stderr | 4 - .../tests/rename/should_fail/rnfail026.stderr | 4 - .../tests/typecheck/should_fail/T11563.stderr | 6 -- .../tests/typecheck/should_fail/T13909.stderr | 6 -- testsuite/tests/typecheck/should_fail/T2994.stderr | 13 --- 16 files changed, 147 insertions(+), 191 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 b152e99478ed641629a2229a2eb0c800277b2a03 From git at git.haskell.org Fri Nov 2 18:11:13 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 2 Nov 2018 18:11:13 +0000 (UTC) Subject: [commit: ghc] wip/T15809's head updated: Further work on TyCon generalisation (b152e99) Message-ID: <20181102181113.EEE333AC01@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/T15809' now includes: 23956b2 Remove redundant SOURCE import 512eeb9 More explicit foralls (GHC Proposal 0007) d849554 Fix for T14251 on ARM 3c452d0 Fix rare undefined asm temp end label error in x86 134de45 includes: Allow headers to be built with C++11 compilers c4a876d Fix `:k` command: add validity checking 8e1a559 Fix integer overflow when encoding doubles (Trac #15271) 2f2308e Comment out CONSTANT_FOLDED in GHC.Natural a7f64c6 Fix TcType.anyRewritableTyVar be88c81 plugins: search for .a files if necessary e69590f testsuite: EtaExpandLevPoly now passes in profiled ways 49f5c6c Plugins: Add documentation and missing exports e400b9b Fix ghc-pkg when only prof way is enabled 4257570 Improve diagnostic when using `make fast` in top directory 5126764 Rewrite FastString table in concurrent hashtable e8a652f Bump template-haskell version to 2.15.0.0 5e45ad1 Finish fix for #14880. 4427315 Fix #15787 by squashing a coercion hole. 3a51abd Remove kind generalisation from tcRnType c1db1eb Test T15711 in indexed-types/should_compile/T15711 731c95f Test #15825 in dependent/should_fail/T15825 2adffd8 Test #15076 in dependent/should_compile/T15076* 09740d5 Revert "Remove kind generalisation from tcRnType" 331081b Add a test case for #15829 b8a797e Fix #15815 by parenthesizing the arguments to infix ~ b2db706 users guide: Mention :since: in editing-guide e35ed9d users guide: Introduce :pragma: directive 44a1d1f Fix sample code of -fprint-explicit-kinds, plus sample when disabling PolyKinds 503ddd6 Docs: clarify the interaction between throwSTM and catchSTM. b8e30e4 Improve documentation for warning options 78fb310 circleci: Build with in-tree GMP on Darwin 66cb344 Correctly detect GIT in a subtree 0bdbbd4 Bump time submodule 849d384 Revert "Bump time submodule" 42faeb3 Add second test case for #15592 21d169b circleci: Store test results of slow validation builds 7e1690d Fix docs typo in Bitraversable composition law 9cbf6f2 Revert "Allocate bss section within proper range of other sections" 82a7164 Revert "Add a RTS option -xp to load PIC object anywhere in address space" 0901381 Tc-tracing, and order of arguments only 9d70d5a WIP on using level numbers for generalisation 3055b0a More progress on using level numbers for gen b152e99 Further work on TyCon generalisation From git at git.haskell.org Fri Nov 2 21:10:28 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 2 Nov 2018 21:10:28 +0000 (UTC) Subject: [commit: ghc] master: Bump time submodule (c3c552d) Message-ID: <20181102211028.94B5F3AC01@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c3c552d6ef4bdbbd7e2928dac864ff6009b36311/ghc >--------------------------------------------------------------- commit c3c552d6ef4bdbbd7e2928dac864ff6009b36311 Author: Ben Gamari Date: Mon Oct 29 17:15:40 2018 -0400 Bump time submodule >--------------------------------------------------------------- c3c552d6ef4bdbbd7e2928dac864ff6009b36311 compiler/ghc.cabal.in | 2 +- ghc/ghc-bin.cabal.in | 2 +- libraries/Cabal | 2 +- libraries/hpc | 2 +- libraries/time | 2 +- libraries/unix | 2 +- 6 files changed, 6 insertions(+), 6 deletions(-) diff --git a/compiler/ghc.cabal.in b/compiler/ghc.cabal.in index f952b88..a9a8da5 100644 --- a/compiler/ghc.cabal.in +++ b/compiler/ghc.cabal.in @@ -60,7 +60,7 @@ Library process >= 1 && < 1.7, bytestring >= 0.9 && < 0.11, binary == 0.8.*, - time >= 1.4 && < 1.9, + time >= 1.4 && < 1.10, containers >= 0.5 && < 0.7, array >= 0.1 && < 0.6, filepath >= 1 && < 1.5, diff --git a/ghc/ghc-bin.cabal.in b/ghc/ghc-bin.cabal.in index 1f15c34..7819330 100644 --- a/ghc/ghc-bin.cabal.in +++ b/ghc/ghc-bin.cabal.in @@ -62,7 +62,7 @@ Executable ghc ghc-prim == 0.5.*, ghci == @ProjectVersionMunged@, haskeline == 0.7.*, - time == 1.8.*, + time >= 1.8 && < 1.10, transformers == 0.5.* CPP-Options: -DGHCI GHC-Options: -fno-warn-name-shadowing diff --git a/libraries/Cabal b/libraries/Cabal index 5a42391..836ba04 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit 5a42391b88aca4467e45c23aff3d74720c353667 +Subproject commit 836ba04516516ec3740a9a584e514e0fed1d50d9 diff --git a/libraries/hpc b/libraries/hpc index 85e04ed..2678098 160000 --- a/libraries/hpc +++ b/libraries/hpc @@ -1 +1 @@ -Subproject commit 85e04edd6e29de549301cf10d2c725cbf29b2098 +Subproject commit 26780988735bdb8fdbeffb59c4a8d585b9e46c3e diff --git a/libraries/time b/libraries/time index 1fcaa07..9e96c26 160000 --- a/libraries/time +++ b/libraries/time @@ -1 +1 @@ -Subproject commit 1fcaa07e10d7966356373ed0e946eb078fcdd6e6 +Subproject commit 9e96c26132fef01a3113c8b152b1be96c0eccd86 diff --git a/libraries/unix b/libraries/unix index f4f500d..dbada98 160000 --- a/libraries/unix +++ b/libraries/unix @@ -1 +1 @@ -Subproject commit f4f500d53b4c73e542a377a5c675309dbbe5774d +Subproject commit dbada9890c1d58111af7d4ebb2a67d38a3a6a872 From git at git.haskell.org Fri Nov 2 21:10:43 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 2 Nov 2018 21:10:43 +0000 (UTC) Subject: [commit: ghc] master: base: Misc haddock fixes (c088137) Message-ID: <20181102211043.C2D5F3AC01@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c088137949bd69ee463c08a0d221517bc5108945/ghc >--------------------------------------------------------------- commit c088137949bd69ee463c08a0d221517bc5108945 Author: Simon Jakobi Date: Tue Oct 23 16:29:13 2018 +0200 base: Misc haddock fixes (cherry picked from commit ee545ff44e0ba9a165de40807548c75bf181dda3) >--------------------------------------------------------------- c088137949bd69ee463c08a0d221517bc5108945 libraries/base/GHC/Float.hs | 4 ++-- libraries/base/GHC/Num.hs | 14 +++++++------- libraries/base/GHC/Real.hs | 10 +++++----- 3 files changed, 14 insertions(+), 14 deletions(-) diff --git a/libraries/base/GHC/Float.hs b/libraries/base/GHC/Float.hs index 9296978..3ac9408 100644 --- a/libraries/base/GHC/Float.hs +++ b/libraries/base/GHC/Float.hs @@ -65,11 +65,11 @@ infixr 8 ** -- | Trigonometric and hyperbolic functions and related functions. -- --- The Haskell Report defines no laws for 'Floating'. However, '(+)', '(*)' +-- The Haskell Report defines no laws for 'Floating'. However, @('+')@, @('*')@ -- and 'exp' are customarily expected to define an exponential field and have -- the following properties: -- --- * @exp (a + b)@ = @exp a * exp b +-- * @exp (a + b)@ = @exp a * exp b@ -- * @exp (fromInteger 0)@ = @fromInteger 1@ class (Fractional a) => Floating a where pi :: a diff --git a/libraries/base/GHC/Num.hs b/libraries/base/GHC/Num.hs index 1fa63fb..aed11a3 100644 --- a/libraries/base/GHC/Num.hs +++ b/libraries/base/GHC/Num.hs @@ -36,17 +36,17 @@ default () -- Double isn't available yet, -- | Basic numeric class. -- --- The Haskell Report defines no laws for 'Num'. However, '(+)' and '(*)' are +-- The Haskell Report defines no laws for 'Num'. However, @('+')@ and @('*')@ are -- customarily expected to define a ring and have the following properties: -- --- [__Associativity of (+)__]: @(x + y) + z@ = @x + (y + z)@ --- [__Commutativity of (+)__]: @x + y@ = @y + x@ --- [__ at fromInteger 0@ is the additive identity__]: @x + fromInteger 0@ = @x@ +-- [__Associativity of @('+')@__]: @(x + y) + z@ = @x + (y + z)@ +-- [__Commutativity of @('+')@__]: @x + y@ = @y + x@ +-- [__@'fromInteger' 0@ is the additive identity__]: @x + fromInteger 0@ = @x@ -- [__'negate' gives the additive inverse__]: @x + negate x@ = @fromInteger 0@ --- [__Associativity of (*)__]: @(x * y) * z@ = @x * (y * z)@ --- [__ at fromInteger 1@ is the multiplicative identity__]: +-- [__Associativity of @('*')@__]: @(x * y) * z@ = @x * (y * z)@ +-- [__@'fromInteger' 1@ is the multiplicative identity__]: -- @x * fromInteger 1@ = @x@ and @fromInteger 1 * x@ = @x@ --- [__Distributivity of (*) with respect to (+)__]: +-- [__Distributivity of @('*')@ with respect to @('+')@__]: -- @a * (b + c)@ = @(a * b) + (a * c)@ and @(b + c) * a@ = @(b * a) + (c * a)@ -- -- Note that it /isn't/ customarily expected that a type instance of both 'Num' diff --git a/libraries/base/GHC/Real.hs b/libraries/base/GHC/Real.hs index c96959f..da64c8b 100644 --- a/libraries/base/GHC/Real.hs +++ b/libraries/base/GHC/Real.hs @@ -138,7 +138,7 @@ class (Num a, Ord a) => Real a where -- -- The Haskell Report defines no laws for 'Integral'. However, 'Integral' -- instances are customarily expected to define a Euclidean domain and have the --- following properties for the 'div'/'mod' and 'quot'/'rem' pairs, given +-- following properties for the `div`\/`mod` and `quot`\/`rem` pairs, given -- suitable Euclidean functions @f@ and @g@: -- -- * @x@ = @y * quot x y + rem x y@ with @rem x y@ = @fromInteger 0@ or @@ -182,8 +182,8 @@ class (Real a, Enum a) => Integral a where -- | Fractional numbers, supporting real division. -- --- The Haskell Report defines no laws for 'Fractional'. However, '(+)' and --- '(*)' are customarily expected to define a division ring and have the +-- The Haskell Report defines no laws for 'Fractional'. However, @('+')@ and +-- @('*')@ are customarily expected to define a division ring and have the -- following properties: -- -- [__'recip' gives the multiplicative inverse__]: @@ -194,9 +194,9 @@ class (Real a, Enum a) => Integral a where class (Num a) => Fractional a where {-# MINIMAL fromRational, (recip | (/)) #-} - -- | fractional division + -- | Fractional division. (/) :: a -> a -> a - -- | reciprocal fraction + -- | Reciprocal fraction. recip :: a -> a -- | Conversion from a 'Rational' (that is @'Ratio' 'Integer'@). -- A floating literal stands for an application of 'fromRational' From git at git.haskell.org Fri Nov 2 21:13:26 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 2 Nov 2018 21:13:26 +0000 (UTC) Subject: [commit: ghc] master: base: Improve haddocks for Functor (118fca7) Message-ID: <20181102211326.F3A0D3AC01@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/118fca7fe413c3cf986cd07b8694917fde190a3b/ghc >--------------------------------------------------------------- commit 118fca7fe413c3cf986cd07b8694917fde190a3b Author: Simon Jakobi Date: Wed Oct 24 12:40:36 2018 +0200 base: Improve haddocks for Functor >--------------------------------------------------------------- 118fca7fe413c3cf986cd07b8694917fde190a3b libraries/base/GHC/Base.hs | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/libraries/base/GHC/Base.hs b/libraries/base/GHC/Base.hs index d1f87e1..92c8a28 100644 --- a/libraries/base/GHC/Base.hs +++ b/libraries/base/GHC/Base.hs @@ -448,8 +448,11 @@ instance Monoid a => Monoid (IO a) where lets you apply any function from @(a -> b)@ to turn an @f a@ into an @f b@, preserving the structure of @f at . Furthermore @f@ needs to adhere to the following laws: -> fmap id == id -> fmap (f . g) == fmap f . fmap g +[/identity/] + @'fmap' 'id' = 'id'@ + +[/composition/] + @'fmap' (f . g) = 'fmap' f . 'fmap' g@ -} class Functor f where From git at git.haskell.org Fri Nov 2 21:13:43 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 2 Nov 2018 21:13:43 +0000 (UTC) Subject: [commit: ghc] master: rts: Allow output filename of eventlog to be given by command-line (5f81952) Message-ID: <20181102211343.14B3D3AC01@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5f81952e230fef1f65ae473e09d44101c489c483/ghc >--------------------------------------------------------------- commit 5f81952e230fef1f65ae473e09d44101c489c483 Author: Ben Gamari Date: Fri Nov 2 14:24:12 2018 -0400 rts: Allow output filename of eventlog to be given by command-line This introduces the `+RTS -ol` flag, which allows user to specify the destination file for eventlog output. Test Plan: Validate with included test Reviewers: simonmar, erikd Reviewed By: simonmar Subscribers: rwbarton, carter Differential Revision: https://phabricator.haskell.org/D5293 >--------------------------------------------------------------- 5f81952e230fef1f65ae473e09d44101c489c483 docs/users_guide/8.8.1-notes.rst | 2 + docs/users_guide/runtime_control.rst | 7 +++ includes/rts/Flags.h | 1 + rts/RtsFlags.c | 29 +++++++++- rts/eventlog/EventLogWriter.c | 64 +++++++++++++--------- .../{driver/T10219.hspp => rts/EventlogOutput.hs} | 0 testsuite/tests/rts/Makefile | 12 ++++ testsuite/tests/rts/all.T | 12 ++++ 8 files changed, 98 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 5f81952e230fef1f65ae473e09d44101c489c483 From git at git.haskell.org Fri Nov 2 21:13:58 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 2 Nov 2018 21:13:58 +0000 (UTC) Subject: [commit: ghc] master: rts: Add FALLTHROUGH macro (6bb8aaa) Message-ID: <20181102211358.C6D2D3AC02@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6bb8aaa3b4fcebf8f0de2f81f00dcc20b857c4f5/ghc >--------------------------------------------------------------- commit 6bb8aaa3b4fcebf8f0de2f81f00dcc20b857c4f5 Author: Ben Gamari Date: Fri Nov 2 14:25:27 2018 -0400 rts: Add FALLTHROUGH macro Instead of using the GCC `/* fallthrough */` syntax we now use the `__attribute__((fallthrough))`, which Phyx says should be more portable than the former. Also adds a missing fallthrough annotation in the MachO linker, fixing #14613. Reviewers: erikd, simonmar Reviewed By: simonmar Subscribers: rwbarton, carter GHC Trac Issues: #14613 Differential Revision: https://phabricator.haskell.org/D5292 >--------------------------------------------------------------- 6bb8aaa3b4fcebf8f0de2f81f00dcc20b857c4f5 includes/Stg.h | 7 +++++++ rts/RaiseAsync.c | 2 +- rts/linker/Elf.c | 2 +- rts/linker/MachO.c | 1 + rts/sm/CNF.c | 16 ++++++++-------- rts/sm/MarkWeak.c | 2 +- rts/sm/Sanity.c | 2 +- rts/sm/Scav.c | 10 +++++----- 8 files changed, 25 insertions(+), 17 deletions(-) diff --git a/includes/Stg.h b/includes/Stg.h index 3a11af1..9b54526 100644 --- a/includes/Stg.h +++ b/includes/Stg.h @@ -196,6 +196,13 @@ #define GNUC3_ATTRIBUTE(at) #endif +/* Used to mark a switch case that falls-through */ +#if (defined(__GNUC__) && __GNUC__ >= 7) || defined(__clang__) +#define FALLTHROUGH GNU_ATTRIBUTE(fallthrough) +#else +#define FALLTHROUGH ((void)0) +#endif /* __GNUC__ >= 7 */ + #if !defined(DEBUG) && (__GNUC__ > 4 || (__GNUC__ == 4 && __GNUC_MINOR__ >= 3)) #define GNUC_ATTR_HOT __attribute__((hot)) #else diff --git a/rts/RaiseAsync.c b/rts/RaiseAsync.c index b08acc4..72f5dff 100644 --- a/rts/RaiseAsync.c +++ b/rts/RaiseAsync.c @@ -449,8 +449,8 @@ check_target: } // fall to next } + FALLTHROUGH; #endif - /* fallthrough */ case BlockedOnCCall: blockedThrowTo(cap,target,msg); return THROWTO_BLOCKED; diff --git a/rts/linker/Elf.c b/rts/linker/Elf.c index fd24a92..8df7e54 100644 --- a/rts/linker/Elf.c +++ b/rts/linker/Elf.c @@ -1536,7 +1536,7 @@ do_Elf_Rela_relocations ( ObjectCode* oc, char* ehdrC, case R_PPC_PLTREL24: value -= 0x8000; /* See Note [.LCTOC1 in PPC PIC code] */ - /* fallthrough */ + FALLTHROUGH; case R_PPC_REL24: delta = value - P; diff --git a/rts/linker/MachO.c b/rts/linker/MachO.c index 5812e89..e28d173 100644 --- a/rts/linker/MachO.c +++ b/rts/linker/MachO.c @@ -1530,6 +1530,7 @@ ocGetNames_MachO(ObjectCode* oc) secArray[i].info->macho_section = section; secArray[i].info->relocation_info = (MachORelocationInfo*)(oc->image + section->reloff); + FALLTHROUGH; } default: { // just set the pointer to the loaded image. diff --git a/rts/sm/CNF.c b/rts/sm/CNF.c index 6bc58cd..8d0ebcc 100644 --- a/rts/sm/CNF.c +++ b/rts/sm/CNF.c @@ -212,7 +212,7 @@ compactAllocateBlockInternal(Capability *cap, case ALLOCATE_IMPORT_NEW: dbl_link_onto(block, &g0->compact_blocks_in_import); - /* fallthrough */ + FALLTHROUGH; case ALLOCATE_IMPORT_APPEND: ASSERT(first == NULL); ASSERT(g == g0); @@ -689,17 +689,17 @@ verify_consistency_block (StgCompactNFData *str, StgCompactNFDataBlock *block) switch (info->type) { case CONSTR_1_0: check_object_in_compact(str, UNTAG_CLOSURE(q->payload[0])); - /* fallthrough */ + FALLTHROUGH; case CONSTR_0_1: p += sizeofW(StgClosure) + 1; break; case CONSTR_2_0: check_object_in_compact(str, UNTAG_CLOSURE(q->payload[1])); - /* fallthrough */ + FALLTHROUGH; case CONSTR_1_1: check_object_in_compact(str, UNTAG_CLOSURE(q->payload[0])); - /* fallthrough */ + FALLTHROUGH; case CONSTR_0_2: p += sizeofW(StgClosure) + 2; break; @@ -931,7 +931,7 @@ fixup_block(StgCompactNFDataBlock *block, StgWord *fixup_table, uint32_t count) if (!fixup_one_pointer(fixup_table, count, &((StgClosure*)p)->payload[0])) return false; - /* fallthrough */ + FALLTHROUGH; case CONSTR_0_1: p += sizeofW(StgClosure) + 1; break; @@ -940,12 +940,12 @@ fixup_block(StgCompactNFDataBlock *block, StgWord *fixup_table, uint32_t count) if (!fixup_one_pointer(fixup_table, count, &((StgClosure*)p)->payload[1])) return false; - /* fallthrough */ + FALLTHROUGH; case CONSTR_1_1: if (!fixup_one_pointer(fixup_table, count, &((StgClosure*)p)->payload[0])) return false; - /* fallthrough */ + FALLTHROUGH; case CONSTR_0_2: p += sizeofW(StgClosure) + 2; break; @@ -999,7 +999,7 @@ fixup_block(StgCompactNFDataBlock *block, StgWord *fixup_table, uint32_t count) break; } - // fall through + FALLTHROUGH; default: debugBelch("Invalid non-NFData closure (type %d) in Compact\n", diff --git a/rts/sm/MarkWeak.c b/rts/sm/MarkWeak.c index 88037f6..d7b8fe6 100644 --- a/rts/sm/MarkWeak.c +++ b/rts/sm/MarkWeak.c @@ -155,7 +155,7 @@ traverseWeakPtrList(void) // otherwise, fall through... } - /* fallthrough */ + FALLTHROUGH; case WeakPtrs: { diff --git a/rts/sm/Sanity.c b/rts/sm/Sanity.c index c6861f4..1da3e44 100644 --- a/rts/sm/Sanity.c +++ b/rts/sm/Sanity.c @@ -102,7 +102,7 @@ checkStackFrame( StgPtr c ) case UPDATE_FRAME: ASSERT(LOOKS_LIKE_CLOSURE_PTR(((StgUpdateFrame*)c)->updatee)); - /* fallthrough */ + FALLTHROUGH; case ATOMICALLY_FRAME: case CATCH_RETRY_FRAME: case CATCH_STM_FRAME: diff --git a/rts/sm/Scav.c b/rts/sm/Scav.c index 2f61914..8bc7029 100644 --- a/rts/sm/Scav.c +++ b/rts/sm/Scav.c @@ -498,7 +498,7 @@ scavenge_block (bdescr *bd) case FUN_1_0: scavenge_fun_srt(info); - /* fallthrough */ + FALLTHROUGH; case CONSTR_1_0: evacuate(&((StgClosure *)p)->payload[0]); p += sizeofW(StgHeader) + 1; @@ -511,7 +511,7 @@ scavenge_block (bdescr *bd) case FUN_0_1: scavenge_fun_srt(info); - /* fallthrough */ + FALLTHROUGH; case CONSTR_0_1: p += sizeofW(StgHeader) + 1; break; @@ -523,7 +523,7 @@ scavenge_block (bdescr *bd) case FUN_0_2: scavenge_fun_srt(info); - /* fallthrough */ + FALLTHROUGH; case CONSTR_0_2: p += sizeofW(StgHeader) + 2; break; @@ -536,7 +536,7 @@ scavenge_block (bdescr *bd) case FUN_1_1: scavenge_fun_srt(info); - /* fallthrough */ + FALLTHROUGH; case CONSTR_1_1: evacuate(&((StgClosure *)p)->payload[0]); p += sizeofW(StgHeader) + 2; @@ -1738,7 +1738,7 @@ scavenge_static(void) case FUN_STATIC: scavenge_fun_srt(info); - /* fallthrough */ + FALLTHROUGH; // a FUN_STATIC can also be an SRT, so it may have pointer // fields. See Note [SRTs] in CmmBuildInfoTables, specifically From git at git.haskell.org Fri Nov 2 21:15:23 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 2 Nov 2018 21:15:23 +0000 (UTC) Subject: [commit: ghc] master: Add Int8# and Word8# (2c959a1) Message-ID: <20181102211523.69B603AC02@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2c959a1894311e59cd2fd469c1967491c1e488f3/ghc >--------------------------------------------------------------- commit 2c959a1894311e59cd2fd469c1967491c1e488f3 Author: Michal Terepeta Date: Fri Nov 2 14:27:03 2018 -0400 Add Int8# and Word8# This is the first step of implementing: https://github.com/ghc-proposals/ghc-proposals/pull/74 The main highlights/changes: primops.txt.pp gets two new sections for two new primitive types for signed and unsigned 8-bit integers (Int8# and Word8 respectively) along with basic arithmetic and comparison operations. PrimRep/RuntimeRep get two new constructors for them. All of the primops translate into the existing MachOPs. For CmmCalls the codegen will now zero-extend the values at call site (so that they can be moved to the right register) and then truncate them back their original width. x86 native codegen needed some updates, since it wasn't able to deal with the new widths, but all the changes are quite localized. LLVM backend seems to just work. This is the second attempt at merging this, after the first attempt in D4475 had to be backed out due to regressions on i386. Bumps binary submodule. Signed-off-by: Michal Terepeta Test Plan: ./validate (on both x86-{32,64}) Reviewers: bgamari, hvr, goldfire, simonmar Subscribers: rwbarton, carter Differential Revision: https://phabricator.haskell.org/D5258 >--------------------------------------------------------------- 2c959a1894311e59cd2fd469c1967491c1e488f3 compiler/cmm/CmmExpr.hs | 5 +- compiler/cmm/CmmMachOp.hs | 10 + compiler/cmm/CmmUtils.hs | 6 +- compiler/cmm/MkGraph.hs | 73 ++++++-- compiler/cmm/PprC.hs | 3 + compiler/codeGen/StgCmmArgRep.hs | 2 + compiler/codeGen/StgCmmPrim.hs | 74 ++++++-- compiler/ghci/ByteCodeGen.hs | 17 +- compiler/llvmGen/LlvmCodeGen/CodeGen.hs | 4 + compiler/nativeGen/X86/CodeGen.hs | 105 ++++++++++- compiler/nativeGen/X86/Instr.hs | 8 +- compiler/nativeGen/X86/Ppr.hs | 10 +- compiler/prelude/PrelNames.hs | 121 +++++++------ compiler/prelude/TysPrim.hs | 26 ++- compiler/prelude/TysWiredIn.hs | 33 ++-- compiler/prelude/TysWiredIn.hs-boot | 6 +- compiler/prelude/primops.txt.pp | 82 +++++++++ compiler/simplStg/RepType.hs | 7 +- compiler/typecheck/TcGenDeriv.hs | 156 ++++++++++------ compiler/types/TyCon.hs | 4 + compiler/utils/Binary.hs | 8 + includes/CodeGen.Platform.hs | 7 +- libraries/base/Data/Typeable/Internal.hs | 4 +- libraries/binary | 2 +- libraries/ghc-prim/GHC/Types.hs | 4 +- testsuite/tests/ffi/should_run/PrimFFIInt8.hs | 28 +++ testsuite/tests/ffi/should_run/PrimFFIInt8.stdout | 1 + testsuite/tests/ffi/should_run/PrimFFIInt8_c.c | 7 + testsuite/tests/ffi/should_run/PrimFFIWord8.hs | 28 +++ testsuite/tests/ffi/should_run/PrimFFIWord8.stdout | 1 + testsuite/tests/ffi/should_run/PrimFFIWord8_c.c | 7 + testsuite/tests/ffi/should_run/all.T | 4 + testsuite/tests/primops/should_run/ArithInt8.hs | 201 +++++++++++++++++++++ .../tests/primops/should_run/ArithInt8.stdout | 8 + testsuite/tests/primops/should_run/ArithWord8.hs | 198 ++++++++++++++++++++ .../tests/primops/should_run/ArithWord8.stdout | 8 + testsuite/tests/primops/should_run/CmpInt8.hs | 84 +++++++++ testsuite/tests/primops/should_run/CmpInt8.stdout | 6 + testsuite/tests/primops/should_run/CmpWord8.hs | 84 +++++++++ testsuite/tests/primops/should_run/CmpWord8.stdout | 6 + testsuite/tests/primops/should_run/ShowPrim.hs | 14 ++ testsuite/tests/primops/should_run/ShowPrim.stdout | 1 + testsuite/tests/primops/should_run/all.T | 5 + utils/genprimopcode/Main.hs | 2 + 44 files changed, 1283 insertions(+), 187 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 2c959a1894311e59cd2fd469c1967491c1e488f3 From git at git.haskell.org Sun Nov 4 16:56:14 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 4 Nov 2018 16:56:14 +0000 (UTC) Subject: [commit: ghc] master: Fix for Trac #15611: Scope errors lie about what modules are imported. (1a3b9bd) Message-ID: <20181104165614.228423AC02@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1a3b9bd0b674ad16a41b942c738b8f34564bcd8d/ghc >--------------------------------------------------------------- commit 1a3b9bd0b674ad16a41b942c738b8f34564bcd8d Author: roland Date: Sun Nov 4 16:45:29 2018 +0100 Fix for Trac #15611: Scope errors lie about what modules are imported. Summary: For the error message: Not in scope X.Y Module X does not export Y No module named ‘X’ is imported: there are 2 cases, where we don't show the last "no module named is imported" line: 1. If the module X has been imported. 2. If the module X is the current module. There are 2 subcases: 2.1 If the unknown module name is in a input source file, then we can use the getModule function to get the current module name. 2.2 If the unknown module name has been entered by the user in GHCi, then the getModule function returns something like "interactive:Ghci1", and we have to check the current module in the last added entry of the HomePackageTable. Test Plan: make test TESTS="T15611a T15611b" Reviewers: monoidal, hvr, thomie, dfeuer, bgamari, DavidEichmann Reviewed By: monoidal, DavidEichmann Subscribers: rwbarton, carter GHC Trac Issues: #15611 Differential Revision: https://phabricator.haskell.org/D5284 >--------------------------------------------------------------- 1a3b9bd0b674ad16a41b942c738b8f34564bcd8d compiler/rename/RnUnbound.hs | 53 +++++++++++++++++++--- compiler/typecheck/TcErrors.hs | 4 +- testsuite/tests/module/mod62.stderr | 1 - testsuite/tests/rename/should_fail/T15611a.hs | 2 + testsuite/tests/rename/should_fail/T15611a.stderr | 1 + testsuite/tests/rename/should_fail/T15611b.hs | 1 + testsuite/tests/rename/should_fail/T15611b.script | 2 + testsuite/tests/rename/should_fail/T15611b.stderr | 1 + testsuite/tests/rename/should_fail/T5892b.stderr | 4 +- testsuite/tests/rename/should_fail/all.T | 2 + .../tests/rename/should_fail/rnfail034.stderr | 1 - 11 files changed, 60 insertions(+), 12 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 1a3b9bd0b674ad16a41b942c738b8f34564bcd8d From git at git.haskell.org Mon Nov 5 16:47:41 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 5 Nov 2018 16:47:41 +0000 (UTC) Subject: [commit: ghc] ghc-8.6: integer-gmp: Fix TBA in changelog (9448fdc) Message-ID: <20181105164741.1DD163AC02@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.6 Link : http://ghc.haskell.org/trac/ghc/changeset/9448fdce111137bf96e4313b6e23fa45264c0443/ghc >--------------------------------------------------------------- commit 9448fdce111137bf96e4313b6e23fa45264c0443 Author: Ben Gamari Date: Fri Nov 2 11:48:05 2018 -0400 integer-gmp: Fix TBA in changelog >--------------------------------------------------------------- 9448fdce111137bf96e4313b6e23fa45264c0443 libraries/integer-gmp/changelog.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/integer-gmp/changelog.md b/libraries/integer-gmp/changelog.md index 51c84bc..a70f214 100644 --- a/libraries/integer-gmp/changelog.md +++ b/libraries/integer-gmp/changelog.md @@ -1,6 +1,6 @@ # Changelog for [`integer-gmp` package](http://hackage.haskell.org/package/integer-gmp) -## 1.0.2.0 *TBA* +## 1.0.2.0 *April 2018* * Bundled with GHC 8.4.2 From git at git.haskell.org Mon Nov 5 16:47:43 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 5 Nov 2018 16:47:43 +0000 (UTC) Subject: [commit: ghc] ghc-8.6: Set RELEASE=NO (701c872) Message-ID: <20181105164743.E44713AC02@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.6 Link : http://ghc.haskell.org/trac/ghc/changeset/701c872fb733e200daa3aa4957202872dbb81f71/ghc >--------------------------------------------------------------- commit 701c872fb733e200daa3aa4957202872dbb81f71 Author: Ben Gamari Date: Mon Nov 5 11:47:11 2018 -0500 Set RELEASE=NO >--------------------------------------------------------------- 701c872fb733e200daa3aa4957202872dbb81f71 configure.ac | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/configure.ac b/configure.ac index 257c4e5..2556561 100644 --- a/configure.ac +++ b/configure.ac @@ -16,7 +16,7 @@ dnl AC_INIT([The Glorious Glasgow Haskell Compilation System], [8.6.2], [glasgow-haskell-bugs at haskell.org], [ghc-AC_PACKAGE_VERSION]) # Set this to YES for a released version, otherwise NO -: ${RELEASE=YES} +: ${RELEASE=NO} # The primary version (e.g. 7.5, 7.4.1) is set in the AC_INIT line # above. If this is not a released version, then we will append the From git at git.haskell.org Mon Nov 5 17:43:36 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 5 Nov 2018 17:43:36 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Further progress (f52b59a) Message-ID: <20181105174336.637333AC02@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/f52b59a5f9767664c9ad702c97443cae70329f95/ghc >--------------------------------------------------------------- commit f52b59a5f9767664c9ad702c97443cae70329f95 Author: Simon Peyton Jones Date: Mon Nov 5 17:43:08 2018 +0000 Further progress >--------------------------------------------------------------- f52b59a5f9767664c9ad702c97443cae70329f95 compiler/typecheck/TcHsSyn.hs | 28 ++++++----- compiler/typecheck/TcHsType.hs | 7 ++- compiler/typecheck/TcMType.hs | 95 ++++++++++++++++++++++++-------------- compiler/typecheck/TcRules.hs | 2 +- compiler/typecheck/TcSimplify.hs | 6 +-- compiler/typecheck/TcTyClsDecls.hs | 43 +++++++++-------- 6 files changed, 111 insertions(+), 70 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 f52b59a5f9767664c9ad702c97443cae70329f95 From git at git.haskell.org Mon Nov 5 18:52:51 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 5 Nov 2018 18:52:51 +0000 (UTC) Subject: [commit: ghc] master: Fix #15859 by checking, not assuming, an ArgFlag (72b8234) Message-ID: <20181105185251.548CF3AC02@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/72b82343b79365dc74ffafb345dd33499a7fd394/ghc >--------------------------------------------------------------- commit 72b82343b79365dc74ffafb345dd33499a7fd394 Author: Richard Eisenberg Date: Mon Nov 5 11:01:47 2018 -0500 Fix #15859 by checking, not assuming, an ArgFlag We thought that visible dependent quantification was impossible in terms, but Iceland Jack discovered otherwise in #15859. This fixes an ASSERT failure that arose. test case: dependent/should_fail/T15859 >--------------------------------------------------------------- 72b82343b79365dc74ffafb345dd33499a7fd394 compiler/typecheck/TcExpr.hs | 10 ++++------ testsuite/tests/dependent/should_fail/T15859.stderr | 6 ++++++ testsuite/tests/dependent/should_fail/all.T | 1 + 3 files changed, 11 insertions(+), 6 deletions(-) diff --git a/compiler/typecheck/TcExpr.hs b/compiler/typecheck/TcExpr.hs index f27922f..a087917 100644 --- a/compiler/typecheck/TcExpr.hs +++ b/compiler/typecheck/TcExpr.hs @@ -1329,14 +1329,12 @@ tcArgs fun orig_fun_ty fun_orig orig_args herald = do { (wrap1, upsilon_ty) <- topInstantiateInferred fun_orig fun_ty -- wrap1 :: fun_ty "->" upsilon_ty ; case tcSplitForAllTy_maybe upsilon_ty of - Just (tvb, inner_ty) -> + Just (tvb, inner_ty) + | binderArgFlag tvb == Specified -> + -- It really can't be Inferred, because we've just instantiated those + -- But, oddly, it might just be Required. See #15859. do { let tv = binderVar tvb - vis = binderArgFlag tvb kind = tyVarKind tv - ; MASSERT2( vis == Specified - , (vcat [ ppr fun_ty, ppr upsilon_ty, ppr tvb - , ppr inner_ty, pprTyVar tv - , ppr vis ]) ) ; ty_arg <- tcHsTypeApp hs_ty_arg kind ; inner_ty <- zonkTcType inner_ty diff --git a/testsuite/tests/dependent/should_fail/T15859.stderr b/testsuite/tests/dependent/should_fail/T15859.stderr new file mode 100644 index 0000000..e479404 --- /dev/null +++ b/testsuite/tests/dependent/should_fail/T15859.stderr @@ -0,0 +1,6 @@ + +T15859.hs:13:5: error: + • Cannot apply expression of type ‘forall k -> k -> *’ + to a visible type argument ‘Int’ + • In the expression: (undefined :: KindOf A) @Int + In an equation for ‘a’: a = (undefined :: KindOf A) @Int diff --git a/testsuite/tests/dependent/should_fail/all.T b/testsuite/tests/dependent/should_fail/all.T index d76fc35..f127220 100644 --- a/testsuite/tests/dependent/should_fail/all.T +++ b/testsuite/tests/dependent/should_fail/all.T @@ -38,3 +38,4 @@ test('T15591c', normal, compile_fail, ['']) test('T15743c', normal, compile_fail, ['']) test('T15743d', normal, compile_fail, ['']) test('T15825', normal, compile_fail, ['']) +test('T15859', normal, compile_fail, ['']) From git at git.haskell.org Tue Nov 6 03:53:01 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 6 Nov 2018 03:53:01 +0000 (UTC) Subject: [commit: ghc] master: Actually add test for #15859. (5693ddd) Message-ID: <20181106035301.044CA3AC02@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5693ddd071033516a1804420a903cb7e3677682b/ghc >--------------------------------------------------------------- commit 5693ddd071033516a1804420a903cb7e3677682b Author: Richard Eisenberg Date: Mon Nov 5 22:51:58 2018 -0500 Actually add test for #15859. Oops. Forgot to `git add`. >--------------------------------------------------------------- 5693ddd071033516a1804420a903cb7e3677682b testsuite/tests/dependent/should_fail/T15859.hs | 13 +++++++++++++ 1 file changed, 13 insertions(+) diff --git a/testsuite/tests/dependent/should_fail/T15859.hs b/testsuite/tests/dependent/should_fail/T15859.hs new file mode 100644 index 0000000..e8ffdf4 --- /dev/null +++ b/testsuite/tests/dependent/should_fail/T15859.hs @@ -0,0 +1,13 @@ +{-# Language PolyKinds #-} +{-# Language TypeApplications #-} +{-# Language ImpredicativeTypes #-} + +module T15859 where + +import Data.Kind + +data A k :: k -> Type + +type KindOf (a :: k) = k + +a = (undefined :: KindOf A) @Int From git at git.haskell.org Tue Nov 6 09:11:40 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 6 Nov 2018 09:11:40 +0000 (UTC) Subject: [commit: ghc] wip/T15809: More progress (6c41f1f) Message-ID: <20181106091140.BA3733AC02@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/6c41f1fa4b5ae77b5fc1aa4137536bd1cc1c0b94/ghc >--------------------------------------------------------------- commit 6c41f1fa4b5ae77b5fc1aa4137536bd1cc1c0b94 Author: Simon Peyton Jones Date: Tue Nov 6 08:55:37 2018 +0000 More progress >--------------------------------------------------------------- 6c41f1fa4b5ae77b5fc1aa4137536bd1cc1c0b94 compiler/typecheck/TcEnv.hs | 2 +- compiler/typecheck/TcHsSyn.hs | 7 ++++- compiler/typecheck/TcHsType.hs | 4 --- compiler/typecheck/TcMType.hs | 14 ++++----- compiler/typecheck/TcRnDriver.hs | 2 +- compiler/typecheck/TcSimplify.hs | 2 +- compiler/typecheck/TcTyClsDecls.hs | 61 +++++++++++++++++++++++++------------- 7 files changed, 57 insertions(+), 35 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 6c41f1fa4b5ae77b5fc1aa4137536bd1cc1c0b94 From git at git.haskell.org Tue Nov 6 17:45:07 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 6 Nov 2018 17:45:07 +0000 (UTC) Subject: [commit: ghc] wip/T15809: More progress (9a32110) Message-ID: <20181106174507.262A73AC02@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/9a32110f2fd1a33b5de209f47772424ffdbe4782/ghc >--------------------------------------------------------------- commit 9a32110f2fd1a33b5de209f47772424ffdbe4782 Author: Simon Peyton Jones Date: Tue Nov 6 17:44:25 2018 +0000 More progress >--------------------------------------------------------------- 9a32110f2fd1a33b5de209f47772424ffdbe4782 compiler/typecheck/TcHsType.hs | 290 +++++++++------------ compiler/typecheck/TcMType.hs | 122 ++++----- compiler/typecheck/TcTyClsDecls.hs | 229 ++++++++-------- compiler/typecheck/TcValidity.hs | 19 +- testsuite/tests/dependent/should_compile/T14880.hs | 1 - .../tests/dependent/should_compile/T15743e.stderr | 2 +- testsuite/tests/ghci/scripts/T15591.hs | 5 + testsuite/tests/ghci/scripts/T15743b.stdout | 2 +- testsuite/tests/ghci/scripts/T7873.stderr | 2 +- .../tests/indexed-types/should_fail/T13972.stderr | 2 +- testsuite/tests/polykinds/T11203.stderr | 2 +- testsuite/tests/polykinds/T11821a.stderr | 2 +- testsuite/tests/polykinds/T15592b.stderr | 2 +- .../tests/typecheck/should_fail/T13983.stderr | 2 +- testsuite/tests/typecheck/should_fail/T2688.stderr | 6 +- 15 files changed, 318 insertions(+), 370 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 9a32110f2fd1a33b5de209f47772424ffdbe4782 From git at git.haskell.org Wed Nov 7 07:54:10 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 7 Nov 2018 07:54:10 +0000 (UTC) Subject: [commit: ghc] wip/T15809: More progress (a45352b) Message-ID: <20181107075410.D8D983AC02@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/a45352bf57f5cb91b62c037a8e61ffa55d8773a7/ghc >--------------------------------------------------------------- commit a45352bf57f5cb91b62c037a8e61ffa55d8773a7 Author: Simon Peyton Jones Date: Wed Nov 7 07:52:16 2018 +0000 More progress A fixup in TcPatSyn >--------------------------------------------------------------- a45352bf57f5cb91b62c037a8e61ffa55d8773a7 compiler/typecheck/TcMType.hs | 48 ++++++++++++++++---------------- compiler/typecheck/TcPatSyn.hs | 56 +++++++++++++++++++++++++++++++------- compiler/typecheck/TcSimplify.hs | 7 +++-- compiler/typecheck/TcTyClsDecls.hs | 1 + 4 files changed, 75 insertions(+), 37 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc a45352bf57f5cb91b62c037a8e61ffa55d8773a7 From git at git.haskell.org Wed Nov 7 11:41:34 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 7 Nov 2018 11:41:34 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Comemnts only (c70945e) Message-ID: <20181107114134.469B63AC02@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/c70945e117738f6d24fb9587b69f5a4ddd3141a3/ghc >--------------------------------------------------------------- commit c70945e117738f6d24fb9587b69f5a4ddd3141a3 Author: Simon Peyton Jones Date: Wed Nov 7 11:40:50 2018 +0000 Comemnts only >--------------------------------------------------------------- c70945e117738f6d24fb9587b69f5a4ddd3141a3 compiler/typecheck/TcTyClsDecls.hs | 74 +++++++++++++++++++++++--------------- 1 file changed, 46 insertions(+), 28 deletions(-) diff --git a/compiler/typecheck/TcTyClsDecls.hs b/compiler/typecheck/TcTyClsDecls.hs index 3f90c42..cefc9ca 100644 --- a/compiler/typecheck/TcTyClsDecls.hs +++ b/compiler/typecheck/TcTyClsDecls.hs @@ -637,37 +637,55 @@ generaliseTcTyCon tc {- Note [Required, Specified, and Inferred for types] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -We have some design choices in how we classify the tyvars bound -in a type declaration. (Here, I use "type" to refer to any TyClDecl.) -Much of the debate is memorialized in #15743. This Note documents -the final conclusion. - -First, a reminder: - * a Required argument is one that must be provided at every call site - * a Specified argument is one that can be inferred at call sites, but - may be instantiated with visible type application - * an Inferred argument is one that must be inferred at call sites; it - is unavailable for use with visible type application. - -Why have Inferred at all? Because we just can't make user-facing promises -about the ordering of some variables. These might swizzle around even between -minor released. By forbidding visible type application, we ensure users -aren't caught unawares. See also -Note [VarBndrs, TyCoVarBinders, TyConBinders, and visibility] in TyCoRep. - -When inferring the ordering of variables (that is, for those -variables that he user has not specified the order with an explicit `forall`) -we use the following order: - - 1. Inferred variables from an enclosing class (associated types only) - 2. Specified variables from an enclosing class (associated types only) - 3. Inferred variables not from an enclosing class - 4. Specified variables not from an enclosing class - 5. Required variables before a top-level :: - 6. All variables after a top-level :: +Each forall'd type variable in a type or kind is one of + + * Required: an argument must be provided at every call site + + * Specified: the argument can be inferred at call sites, but + may be instantiated with visible type/kind application + + * Inferred: the must be inferred at call sites; it + is unavailable for use with visible type/kind application. + +Why have Inferred at all? Because we just can't make user-facing +promises about the ordering of some variables. These might swizzle +around even between minor released. By forbidding visible type +application, we ensure users aren't caught unawares. + +Go read Note [VarBndrs, TyCoVarBinders, TyConBinders, and visibility] in TyCoRep. + +The question for this Note is this: + given a TyClDecl, how are its quantified type variables classified? +Much of the debate is memorialized in #15743. + +Here is our design choice. When inferring the ordering of variables +for a TyCl declaration (that is, for those variables that he user +has not specified the order with an explicit `forall`), we use the +following order: + + 1. Inferred variables + 2. Specified variables; in the left-to-right order in which + the user wrote them, modified by scopedSort (see below) + to put them in depdendency order. + 3. Required variables before a top-level :: + 4. All variables after a top-level :: If this ordering does not make a valid telescope, we reject the definition. +Example: + data SameKind :: k -> k -> * + data X a (b :: SameKind a b) (c :: k) d + +For X: + - a, b, c, d are Required; they are explicitly listed by the user + as the positional arguments of X + - k is Specified; it appears explicitly in a kind signature + - k2, the kind of d, is Inferred; it is not mentioned explicitly at all + +Putting variables in the order Inferred, Specified, Required gives us + Inferred: k2 + Specified: k (a ::kb + This idea is implemented in the generalise function within kcTyClGroup (for declarations without CUSKs), and in kcLHsQTyVars (for declarations with CUSKs). Note that neither definition worries about point (6) above, as this From git at git.haskell.org Wed Nov 7 13:10:12 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 7 Nov 2018 13:10:12 +0000 (UTC) Subject: [commit: ghc] master: integer-gmp: Fix TBA in changelog (7189469) Message-ID: <20181107131012.573B43AC02@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7189469ad46022bb9a16ac32fcf64e6c5f932b2a/ghc >--------------------------------------------------------------- commit 7189469ad46022bb9a16ac32fcf64e6c5f932b2a Author: Ben Gamari Date: Fri Nov 2 11:48:05 2018 -0400 integer-gmp: Fix TBA in changelog >--------------------------------------------------------------- 7189469ad46022bb9a16ac32fcf64e6c5f932b2a libraries/integer-gmp/changelog.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/integer-gmp/changelog.md b/libraries/integer-gmp/changelog.md index 51c84bc..a70f214 100644 --- a/libraries/integer-gmp/changelog.md +++ b/libraries/integer-gmp/changelog.md @@ -1,6 +1,6 @@ # Changelog for [`integer-gmp` package](http://hackage.haskell.org/package/integer-gmp) -## 1.0.2.0 *TBA* +## 1.0.2.0 *April 2018* * Bundled with GHC 8.4.2 From git at git.haskell.org Wed Nov 7 13:10:15 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 7 Nov 2018 13:10:15 +0000 (UTC) Subject: [commit: ghc] master: Bump directory submodule to 1.3.3.1 (648b0c2) Message-ID: <20181107131015.613813AC02@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/648b0c2dc8ef8c6ce2325389b84d629f7bdf6ff0/ghc >--------------------------------------------------------------- commit 648b0c2dc8ef8c6ce2325389b84d629f7bdf6ff0 Author: Ben Gamari Date: Mon Nov 5 12:06:58 2018 -0500 Bump directory submodule to 1.3.3.1 >--------------------------------------------------------------- 648b0c2dc8ef8c6ce2325389b84d629f7bdf6ff0 libraries/directory | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/directory b/libraries/directory index e9debc1..19d6dc0 160000 --- a/libraries/directory +++ b/libraries/directory @@ -1 +1 @@ -Subproject commit e9debc1d4a9c4b608a32f60bae173ed10f89fdce +Subproject commit 19d6dc0d33366a8920bf8acc7a0fd3ef533d39c3 From git at git.haskell.org Wed Nov 7 13:10:18 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 7 Nov 2018 13:10:18 +0000 (UTC) Subject: [commit: ghc] master: CircleCI: Build DWARF-enabled Linux bindists (406978c) Message-ID: <20181107131018.5A1E33AC02@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/406978c478e4b14e677f396499420d7b8e5d21fd/ghc >--------------------------------------------------------------- commit 406978c478e4b14e677f396499420d7b8e5d21fd Author: Ben Gamari Date: Mon Nov 5 13:45:59 2018 -0500 CircleCI: Build DWARF-enabled Linux bindists >--------------------------------------------------------------- 406978c478e4b14e677f396499420d7b8e5d21fd .circleci/config.yml | 23 +++++++++++++++++++++++ .circleci/prepare-system.sh | 7 +++++++ 2 files changed, 30 insertions(+) diff --git a/.circleci/config.yml b/.circleci/config.yml index f356901..6fd9b84 100644 --- a/.circleci/config.yml +++ b/.circleci/config.yml @@ -114,6 +114,27 @@ jobs: - *test - *store_test_results + "validate-x86_64-linux-dwarf": + resource_class: xlarge + docker: + - image: ghcci/x86_64-linux:0.0.4 + environment: + <<: *buildenv + GHC_COLLECTOR_FLAVOR: x86_64-linux-dwarf + ENABLE_DWARF: 1 + CONFIGURE_OPTS: --enable-dwarf-unwind + steps: + - checkout + - *prepare + - *submodules + - *boot + - *configure_unix + - *make + - *bindist + - *storeartifacts + - *test + - *store_test_results + "validate-x86_64-freebsd": resource_class: xlarge docker: @@ -292,6 +313,8 @@ workflows: jobs: - validate-x86_64-linux: *trigger_on_tags + - validate-x86_64-linux-dwarf: + *trigger_on_tags # FreeBSD disabled: https://github.com/haskell/unix/issues/102 # - validate-x86_64-freebsd - validate-x86_64-darwin: diff --git a/.circleci/prepare-system.sh b/.circleci/prepare-system.sh index dbb1011..39d32f1 100755 --- a/.circleci/prepare-system.sh +++ b/.circleci/prepare-system.sh @@ -22,6 +22,10 @@ BUILD_SPHINX_PDF=$BUILD_SPHINX_PDF BeConservative=YES EOF +if [[ -z ${ENABLE_DWARF:-} ]]; then + echo "GhcLibHcOpts=-g3" >> mk/build.mk +fi + case "$(uname)" in Linux) if [[ -n ${TARGET:-} ]]; then @@ -47,6 +51,9 @@ case "$(uname)" in cabal update cabal install --reinstall hscolour sudo ln -s /home/ghc/.cabal/bin/HsColour /usr/local/bin/HsColour || true + if [[ -z ${ENABLE_DWARF:-} ]]; then + apt-get install -qy libdw1-dev + fi fi ;; From git at git.haskell.org Wed Nov 7 13:10:21 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 7 Nov 2018 13:10:21 +0000 (UTC) Subject: [commit: ghc] master: [LlvmCodeGen] Fixes for Int8#/Word8# (f424515) Message-ID: <20181107131021.5E39B3AC02@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f424515fd8cbc2b7380cdf8427f972d062940bd5/ghc >--------------------------------------------------------------- commit f424515fd8cbc2b7380cdf8427f972d062940bd5 Author: Michal Terepeta Date: Wed Nov 7 08:03:16 2018 -0500 [LlvmCodeGen] Fixes for Int8#/Word8# This fixes two isssues: - Using bitcast for MO_XX_Conv Arguments to a bitcast must be of the same size. We should be using `trunc` and `zext` instead. - Using unsupported MO_*_QuotRem for LLVM The two primops `MO_*_QuotRem` are not supported by the LLVM backend, so we shouldn't use them for `Int8#`/`Word8#` (just as we do not use them for `Int#`/`Word#`). Signed-off-by: Michal Terepeta Test Plan: manually run tests with WAY=llvm Reviewers: bgamari, simonmar Reviewed By: bgamari Subscribers: rwbarton, carter GHC Trac Issues: #15864 Differential Revision: https://phabricator.haskell.org/D5304 >--------------------------------------------------------------- f424515fd8cbc2b7380cdf8427f972d062940bd5 compiler/codeGen/StgCmmPrim.hs | 6 +++--- compiler/llvmGen/LlvmCodeGen/CodeGen.hs | 2 +- 2 files changed, 4 insertions(+), 4 deletions(-) diff --git a/compiler/codeGen/StgCmmPrim.hs b/compiler/codeGen/StgCmmPrim.hs index 9da472e..75d46b5 100644 --- a/compiler/codeGen/StgCmmPrim.hs +++ b/compiler/codeGen/StgCmmPrim.hs @@ -881,7 +881,7 @@ callishPrimOpSupported dflags op Right (genericIntQuotRemOp (wordWidth dflags)) Int8QuotRemOp | (ncg && x86ish) - || llvm -> Left (MO_S_QuotRem W8) + -> Left (MO_S_QuotRem W8) | otherwise -> Right (genericIntQuotRemOp W8) WordQuotRemOp | ncg && (x86ish || ppc) -> @@ -895,8 +895,8 @@ callishPrimOpSupported dflags op | otherwise -> Right (genericWordQuotRem2Op dflags) Word8QuotRemOp | (ncg && x86ish) - || llvm -> Left (MO_U_QuotRem W8) - | otherwise -> Right (genericWordQuotRemOp W8) + -> Left (MO_U_QuotRem W8) + | otherwise -> Right (genericWordQuotRemOp W8) WordAdd2Op | (ncg && (x86ish || ppc)) diff --git a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs index efc8709..d24075e 100644 --- a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs +++ b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs @@ -1194,7 +1194,7 @@ genMachOp _ op [x] = case op of -> sameConv from (widthToLlvmInt to) LM_Trunc LM_Zext MO_XX_Conv from to - -> sameConv from (widthToLlvmInt to) LM_Bitcast LM_Bitcast + -> sameConv from (widthToLlvmInt to) LM_Trunc LM_Zext MO_FF_Conv from to -> sameConv from (widthToLlvmFloat to) LM_Fptrunc LM_Fpext From git at git.haskell.org Wed Nov 7 13:10:24 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 7 Nov 2018 13:10:24 +0000 (UTC) Subject: [commit: ghc] master: Revert "Fix for T14251 on ARM" (802ce6e) Message-ID: <20181107131024.5D97F3AC02@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/802ce6eb090838d4e7573d96cf056afd2d898b78/ghc >--------------------------------------------------------------- commit 802ce6eb090838d4e7573d96cf056afd2d898b78 Author: Ben Gamari Date: Wed Nov 7 08:05:34 2018 -0500 Revert "Fix for T14251 on ARM" This reverts commit d8495549ba9d194815c2d0eaee6797fc7c00756a. >--------------------------------------------------------------- 802ce6eb090838d4e7573d96cf056afd2d898b78 compiler/llvmGen/LlvmCodeGen/Base.hs | 123 ++++++++++---------------------- compiler/llvmGen/LlvmCodeGen/CodeGen.hs | 6 +- 2 files changed, 39 insertions(+), 90 deletions(-) diff --git a/compiler/llvmGen/LlvmCodeGen/Base.hs b/compiler/llvmGen/LlvmCodeGen/Base.hs index 0a40b73..ec91bac 100644 --- a/compiler/llvmGen/LlvmCodeGen/Base.hs +++ b/compiler/llvmGen/LlvmCodeGen/Base.hs @@ -26,7 +26,7 @@ module LlvmCodeGen.Base ( cmmToLlvmType, widthToLlvmFloat, widthToLlvmInt, llvmFunTy, llvmFunSig, llvmFunArgs, llvmStdFunAttrs, llvmFunAlign, llvmInfAlign, - llvmPtrBits, tysToParams, llvmFunSection, padLiveArgs, isFPR, + llvmPtrBits, tysToParams, llvmFunSection, padLiveArgs, isSSE, strCLabel_llvm, strDisplayName_llvm, strProcedureName_llvm, getGlobalPtr, generateExternDecls, @@ -47,7 +47,6 @@ import CodeGen.Platform ( activeStgRegs ) import DynFlags import FastString import Cmm hiding ( succ ) -import CmmUtils ( regsOverlap ) import Outputable as Outp import Platform import UniqFM @@ -59,7 +58,8 @@ import ErrUtils import qualified Stream import Control.Monad (ap) -import Data.List (sort, groupBy, head) +import Data.List (sort) +import Data.Maybe (mapMaybe) -- ---------------------------------------------------------------------------- -- * Some Data Types @@ -152,91 +152,36 @@ llvmFunArgs dflags live = map (lmGlobalRegArg dflags) (filter isPassed allRegs) where platform = targetPlatform dflags allRegs = activeStgRegs platform - paddedLive = map (\(_,r) -> r) $ padLiveArgs dflags live + paddedLive = map (\(_,r) -> r) $ padLiveArgs live isLive r = r `elem` alwaysLive || r `elem` paddedLive - isPassed r = not (isFPR r) || isLive r - - -isFPR :: GlobalReg -> Bool -isFPR (FloatReg _) = True -isFPR (DoubleReg _) = True -isFPR (XmmReg _) = True -isFPR (YmmReg _) = True -isFPR (ZmmReg _) = True -isFPR _ = False - -sameFPRClass :: GlobalReg -> GlobalReg -> Bool -sameFPRClass (FloatReg _) (FloatReg _) = True -sameFPRClass (DoubleReg _) (DoubleReg _) = True -sameFPRClass (XmmReg _) (XmmReg _) = True -sameFPRClass (YmmReg _) (YmmReg _) = True -sameFPRClass (ZmmReg _) (ZmmReg _) = True -sameFPRClass _ _ = False - -normalizeFPRNum :: GlobalReg -> GlobalReg -normalizeFPRNum (FloatReg _) = FloatReg 1 -normalizeFPRNum (DoubleReg _) = DoubleReg 1 -normalizeFPRNum (XmmReg _) = XmmReg 1 -normalizeFPRNum (YmmReg _) = YmmReg 1 -normalizeFPRNum (ZmmReg _) = ZmmReg 1 -normalizeFPRNum _ = error "normalizeFPRNum expected only FPR regs" - -getFPRCtor :: GlobalReg -> Int -> GlobalReg -getFPRCtor (FloatReg _) = FloatReg -getFPRCtor (DoubleReg _) = DoubleReg -getFPRCtor (XmmReg _) = XmmReg -getFPRCtor (YmmReg _) = YmmReg -getFPRCtor (ZmmReg _) = ZmmReg -getFPRCtor _ = error "getFPRCtor expected only FPR regs" - -fprRegNum :: GlobalReg -> Int -fprRegNum (FloatReg i) = i -fprRegNum (DoubleReg i) = i -fprRegNum (XmmReg i) = i -fprRegNum (YmmReg i) = i -fprRegNum (ZmmReg i) = i -fprRegNum _ = error "fprRegNum expected only FPR regs" - --- | Input: dynflags, and the list of live registers --- --- Output: An augmented list of live registers, where padding was --- added to the list of registers to ensure the calling convention is --- correctly used by LLVM. --- --- Each global reg in the returned list is tagged with a bool, which --- indicates whether the global reg was added as padding, or was an original --- live register. --- --- That is, True => padding, False => a real, live global register. --- --- Also, the returned list is not sorted in any particular order. --- -padLiveArgs :: DynFlags -> LiveGlobalRegs -> [(Bool, GlobalReg)] -padLiveArgs dflags live = - if platformUnregisterised plat - then taggedLive -- not using GHC's register convention for platform. - else padding ++ taggedLive - where - taggedLive = map (\x -> (False, x)) live - plat = targetPlatform dflags - - fprLive = filter isFPR live - padding = concatMap calcPad $ groupBy sharesClass fprLive - - sharesClass :: GlobalReg -> GlobalReg -> Bool - sharesClass a b = sameFPRClass a b || overlappingClass - where - overlappingClass = regsOverlap dflags (norm a) (norm b) - norm = CmmGlobal . normalizeFPRNum - - calcPad :: [GlobalReg] -> [(Bool, GlobalReg)] - calcPad rs = getFPRPadding (getFPRCtor $ head rs) rs - -getFPRPadding :: (Int -> GlobalReg) -> LiveGlobalRegs -> [(Bool, GlobalReg)] -getFPRPadding paddingCtor live = padding + isPassed r = not (isSSE r) || isLive r + + +isSSE :: GlobalReg -> Bool +isSSE (FloatReg _) = True +isSSE (DoubleReg _) = True +isSSE (XmmReg _) = True +isSSE (YmmReg _) = True +isSSE (ZmmReg _) = True +isSSE _ = False + +sseRegNum :: GlobalReg -> Maybe Int +sseRegNum (FloatReg i) = Just i +sseRegNum (DoubleReg i) = Just i +sseRegNum (XmmReg i) = Just i +sseRegNum (YmmReg i) = Just i +sseRegNum (ZmmReg i) = Just i +sseRegNum _ = Nothing + +-- the bool indicates whether the global reg was added as padding. +-- the returned list is not sorted in any particular order, +-- but does indicate the set of live registers needed, with SSE padding. +padLiveArgs :: LiveGlobalRegs -> [(Bool, GlobalReg)] +padLiveArgs live = allRegs where - fprRegNums = sort $ map fprRegNum live - (_, padding) = foldl assignSlots (1, []) $ fprRegNums + sseRegNums = sort $ mapMaybe sseRegNum live + (_, padding) = foldl assignSlots (1, []) $ sseRegNums + allRegs = padding ++ map (\r -> (False, r)) live assignSlots (i, acc) regNum | i == regNum = -- don't need padding here @@ -250,7 +195,11 @@ getFPRPadding paddingCtor live = padding genPad start n = take n $ flip map (iterate (+1) start) (\i -> - (True, paddingCtor i)) + (True, FloatReg i)) + -- NOTE: Picking float should be fine for the following reasons: + -- (1) Float aliases with all the other SSE register types on + -- the given platform. + -- (2) The argument is not live anyways. -- | Llvm standard fun attributes diff --git a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs index d24075e..de839fb 100644 --- a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs +++ b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs @@ -1818,14 +1818,14 @@ funPrologue live cmmBlocks = do -- STG Liveness optimisation done here. funEpilogue :: LiveGlobalRegs -> LlvmM ([LlvmVar], LlvmStatements) funEpilogue live = do - dflags <- getDynFlags -- the bool indicates whether the register is padding. let alwaysNeeded = map (\r -> (False, r)) alwaysLive - livePadded = alwaysNeeded ++ padLiveArgs dflags live + livePadded = alwaysNeeded ++ padLiveArgs live -- Set to value or "undef" depending on whether the register is -- actually live + dflags <- getDynFlags let loadExpr r = do (v, _, s) <- getCmmRegVal (CmmGlobal r) return (Just $ v, s) @@ -1837,7 +1837,7 @@ funEpilogue live = do loads <- flip mapM allRegs $ \r -> case () of _ | (False, r) `elem` livePadded -> loadExpr r -- if r is not padding, load it - | not (isFPR r) || (True, r) `elem` livePadded + | not (isSSE r) || (True, r) `elem` livePadded -> loadUndef r | otherwise -> return (Nothing, nilOL) From git at git.haskell.org Wed Nov 7 13:10:27 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 7 Nov 2018 13:10:27 +0000 (UTC) Subject: [commit: ghc] master: Revert "Multiple fixes / improvements for LLVM backend" (39cd12b) Message-ID: <20181107131027.6896A3AC02@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/39cd12b8d73b9d931ce1acaa7d9e74271c51086f/ghc >--------------------------------------------------------------- commit 39cd12b8d73b9d931ce1acaa7d9e74271c51086f Author: Ben Gamari Date: Wed Nov 7 08:06:18 2018 -0500 Revert "Multiple fixes / improvements for LLVM backend" This reverts commit adcb5fb47c0942671d409b940d8884daa9359ca4. >--------------------------------------------------------------- 39cd12b8d73b9d931ce1acaa7d9e74271c51086f compiler/llvmGen/Llvm/Types.hs | 2 +- compiler/llvmGen/LlvmCodeGen/Base.hs | 62 +++++--------------------------- compiler/llvmGen/LlvmCodeGen/CodeGen.hs | 60 +++++++++++++++++++++++++------ llvm-passes | 2 +- testsuite/tests/codeGen/should_run/all.T | 3 +- 5 files changed, 62 insertions(+), 67 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 39cd12b8d73b9d931ce1acaa7d9e74271c51086f From git at git.haskell.org Wed Nov 7 14:09:29 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 7 Nov 2018 14:09:29 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Finally done (c704d00) Message-ID: <20181107140929.7441C3AC02@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/c704d00b7067f0f9c8798a1136b3b1ff132ae441/ghc >--------------------------------------------------------------- commit c704d00b7067f0f9c8798a1136b3b1ff132ae441 Author: Simon Peyton Jones Date: Wed Nov 7 12:51:32 2018 +0000 Finally done >--------------------------------------------------------------- c704d00b7067f0f9c8798a1136b3b1ff132ae441 compiler/typecheck/TcHsType.hs | 128 +++----------- compiler/typecheck/TcMType.hs | 63 +++---- compiler/typecheck/TcTyClsDecls.hs | 188 ++++++++++++++++----- compiler/typecheck/TcValidity.hs | 77 ++++++--- .../dependent/should_fail/BadTelescope.stderr | 7 +- .../dependent/should_fail/BadTelescope3.stderr | 6 +- .../dependent/should_fail/BadTelescope4.stderr | 13 +- .../tests/dependent/should_fail/T13895.stderr | 37 +--- .../tests/dependent/should_fail/T14066f.stderr | 6 +- .../tests/dependent/should_fail/T14066g.stderr | 8 +- .../tests/dependent/should_fail/T15591b.stderr | 9 +- .../tests/dependent/should_fail/T15591c.stderr | 9 +- .../tests/dependent/should_fail/T15743c.stderr | 13 +- .../tests/dependent/should_fail/T15743d.stderr | 13 +- testsuite/tests/ghci/scripts/T15591.hs | 9 +- testsuite/tests/ghci/scripts/T15591.stdout | 6 +- 16 files changed, 312 insertions(+), 280 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 c704d00b7067f0f9c8798a1136b3b1ff132ae441 From git at git.haskell.org Wed Nov 7 14:18:25 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 7 Nov 2018 14:18:25 +0000 (UTC) Subject: [commit: ghc] master: Revert "CircleCI: Build DWARF-enabled Linux bindists" (82a5c24) Message-ID: <20181107141825.9FA403AC02@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/82a5c2410a47b16df09039b9786c2c0e34ba130e/ghc >--------------------------------------------------------------- commit 82a5c2410a47b16df09039b9786c2c0e34ba130e Author: Ben Gamari Date: Wed Nov 7 09:17:59 2018 -0500 Revert "CircleCI: Build DWARF-enabled Linux bindists" This reverts commit 406978c478e4b14e677f396499420d7b8e5d21fd. >--------------------------------------------------------------- 82a5c2410a47b16df09039b9786c2c0e34ba130e .circleci/config.yml | 23 ----------------------- .circleci/prepare-system.sh | 7 ------- 2 files changed, 30 deletions(-) diff --git a/.circleci/config.yml b/.circleci/config.yml index 6fd9b84..f356901 100644 --- a/.circleci/config.yml +++ b/.circleci/config.yml @@ -114,27 +114,6 @@ jobs: - *test - *store_test_results - "validate-x86_64-linux-dwarf": - resource_class: xlarge - docker: - - image: ghcci/x86_64-linux:0.0.4 - environment: - <<: *buildenv - GHC_COLLECTOR_FLAVOR: x86_64-linux-dwarf - ENABLE_DWARF: 1 - CONFIGURE_OPTS: --enable-dwarf-unwind - steps: - - checkout - - *prepare - - *submodules - - *boot - - *configure_unix - - *make - - *bindist - - *storeartifacts - - *test - - *store_test_results - "validate-x86_64-freebsd": resource_class: xlarge docker: @@ -313,8 +292,6 @@ workflows: jobs: - validate-x86_64-linux: *trigger_on_tags - - validate-x86_64-linux-dwarf: - *trigger_on_tags # FreeBSD disabled: https://github.com/haskell/unix/issues/102 # - validate-x86_64-freebsd - validate-x86_64-darwin: diff --git a/.circleci/prepare-system.sh b/.circleci/prepare-system.sh index 39d32f1..dbb1011 100755 --- a/.circleci/prepare-system.sh +++ b/.circleci/prepare-system.sh @@ -22,10 +22,6 @@ BUILD_SPHINX_PDF=$BUILD_SPHINX_PDF BeConservative=YES EOF -if [[ -z ${ENABLE_DWARF:-} ]]; then - echo "GhcLibHcOpts=-g3" >> mk/build.mk -fi - case "$(uname)" in Linux) if [[ -n ${TARGET:-} ]]; then @@ -51,9 +47,6 @@ case "$(uname)" in cabal update cabal install --reinstall hscolour sudo ln -s /home/ghc/.cabal/bin/HsColour /usr/local/bin/HsColour || true - if [[ -z ${ENABLE_DWARF:-} ]]; then - apt-get install -qy libdw1-dev - fi fi ;; From git at git.haskell.org Wed Nov 7 17:08:06 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 7 Nov 2018 17:08:06 +0000 (UTC) Subject: [commit: ghc] master: testsuite: Save performance metrics in git notes. (932cd41) Message-ID: <20181107170806.9AFA93AC02@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/932cd41d8c7984c767c1b3b58e05146f69cc5c15/ghc >--------------------------------------------------------------- commit 932cd41d8c7984c767c1b3b58e05146f69cc5c15 Author: David Eichmann Date: Wed Nov 7 12:02:47 2018 -0500 testsuite: Save performance metrics in git notes. This patch makes the following improvement: - Automatically records test metrics (per test environment) so that the programmer need not supply nor update expected values in *.T files. - On expected metric changes, the programmer need only indicate the direction of change in the git commit message. - Provides a simple python tool "perf_notes.py" to compare metrics over time. Issues: - Using just the previous commit allows performance to drift with each commit. - Currently we allow drift as we have a preference for minimizing false positives. - Some possible alternatives include: - Use metrics from a fixed commit per test: the last commit that allowed a change in performance (else the oldest metric) - Or use some sort of aggregate since the last commit that allowed a change in performance (else all available metrics) - These alternatives may result in a performance issue (with the test driver) having to heavily search git commits/notes. - Run locally, performance tests will trivially pass unless the tests were run locally on the previous commit. This is often not the case e.g. after pulling recent changes. Previously, *.T files contain statements such as: ``` stats_num_field('peak_megabytes_allocated', (2, 1)) compiler_stats_num_field('bytes allocated', [(wordsize(64), 165890392, 10)]) ``` This required the programmer to give the expected values and a tolerance deviation (percentage). With this patch, the above statements are replaced with: ``` collect_stats('peak_megabytes_allocated', 5) collect_compiler_stats('bytes allocated', 10) ``` So that programmer must only enter which metrics to test and a tolerance deviation. No expected value is required. CircleCI will then run the tests per test environment and record the metrics to a git note for that commit and push them to the git.haskell.org ghc repo. Metrics will be compared to the previous commit. If they are different by the tolerance deviation from the *.T file, then the corresponding test will fail. By adding to the git commit message e.g. ``` # Metric (In|De)crease : Metric Increase ['bytes allocated', 'peak_megabytes_allocated'] \ (test_env='linux_x86', way='default'): Test012, Test345 Metric Decrease 'bytes allocated': Test678 Metric Increase: Test711 ``` This will allow the noted changes (letting the test pass). Note that by omitting metrics or options, the change will apply to all possible metrics/options (i.e. in the above, an increase for all metrics in all test environments is allowed for Test711) phabricator will use the message in the description Reviewers: bgamari, hvr Reviewed By: bgamari Subscribers: rwbarton, carter GHC Trac Issues: #12758 Differential Revision: https://phabricator.haskell.org/D5059 >--------------------------------------------------------------- 932cd41d8c7984c767c1b3b58e05146f69cc5c15 .circleci/config.yml | 43 +- .circleci/push-test-metrics.sh | 46 ++ libraries/base/tests/all.T | 18 +- testsuite/driver/README.md | 133 +++ testsuite/driver/perf_notes.py | 382 +++++++++ testsuite/driver/runtests.py | 71 +- testsuite/driver/testglobals.py | 33 +- testsuite/driver/testlib.py | 228 +++-- testsuite/driver/testutil.py | 18 + testsuite/mk/test.mk | 12 + testsuite/tests/callarity/perf/all.T | 12 +- testsuite/tests/deriving/perf/all.T | 11 +- testsuite/tests/perf/compiler/all.T | 1056 ++---------------------- testsuite/tests/perf/haddock/all.T | 184 +---- testsuite/tests/perf/join_points/all.T | 16 +- testsuite/tests/perf/should_run/all.T | 374 ++------- testsuite/tests/perf/space_leaks/all.T | 75 +- testsuite/tests/pmcheck/should_compile/all.T | 27 +- testsuite/tests/primops/should_run/all.T | 6 +- testsuite/tests/simplCore/should_compile/all.T | 3 +- testsuite/tests/simplStg/should_run/all.T | 5 +- 21 files changed, 1018 insertions(+), 1735 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 932cd41d8c7984c767c1b3b58e05146f69cc5c15 From git at git.haskell.org Wed Nov 7 23:31:10 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 7 Nov 2018 23:31:10 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Comments and alpha-renaming (c588c3e) Message-ID: <20181107233110.4B93B3AC02@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/c588c3eb2a457fa03fa52f67f63f12239a31aa78/ghc >--------------------------------------------------------------- commit c588c3eb2a457fa03fa52f67f63f12239a31aa78 Author: Simon Peyton Jones Date: Wed Nov 7 23:26:05 2018 +0000 Comments and alpha-renaming >--------------------------------------------------------------- c588c3eb2a457fa03fa52f67f63f12239a31aa78 compiler/typecheck/TcHsType.hs | 2 -- compiler/typecheck/TcInstDcls.hs | 10 +++++----- compiler/typecheck/TcMType.hs | 2 +- compiler/typecheck/TcSimplify.hs | 7 ++++--- 4 files changed, 10 insertions(+), 11 deletions(-) diff --git a/compiler/typecheck/TcHsType.hs b/compiler/typecheck/TcHsType.hs index 2ce23e7..dd2995e 100644 --- a/compiler/typecheck/TcHsType.hs +++ b/compiler/typecheck/TcHsType.hs @@ -1744,7 +1744,6 @@ kcImplicitTKBndrs = kcImplicitTKBndrsX newFlexiKindedTyVarTyVar -- | Bring implicitly quantified type/kind variables into scope during -- kind checking. The returned TcTyVars are in 1-1 correspondence --- with the names passed in. --- Note [Use TyVarTvs in kind-checking pass] in TcTyClsDecls. kcImplicitTKBndrsX :: (Name -> TcM TcTyVar) -- new_tv function -> [Name] -- of the vars -> TcM a @@ -2065,7 +2064,6 @@ kcLookupTcTyCon nm -- Never emits constraints, though the thing_inside might. kcTyClTyVars :: Name -> TcM a -> TcM a kcTyClTyVars tycon_name thing_inside - -- See Note [Use TyVarTvs in kind-checking pass] in TcTyClsDecls = do { tycon <- kcLookupTcTyCon tycon_name ; tcExtendNameTyVarEnv (tcTyConScopedTyVars tycon) $ thing_inside } diff --git a/compiler/typecheck/TcInstDcls.hs b/compiler/typecheck/TcInstDcls.hs index 84f43e9..63c565d 100644 --- a/compiler/typecheck/TcInstDcls.hs +++ b/compiler/typecheck/TcInstDcls.hs @@ -465,14 +465,14 @@ tcLocalInstDecl (L _ (XInstDecl _)) = panic "tcLocalInstDecl" tcClsInstDecl :: LClsInstDecl GhcRn -> TcM ([InstInfo GhcRn], [FamInst], [DerivInfo]) -- The returned DerivInfos are for any associated data families -tcClsInstDecl (L loc (ClsInstDecl { cid_poly_ty = poly_ty, cid_binds = binds +tcClsInstDecl (L loc (ClsInstDecl { cid_poly_ty = hs_ty, cid_binds = binds , cid_sigs = uprags, cid_tyfam_insts = ats , cid_overlap_mode = overlap_mode , cid_datafam_insts = adts })) = setSrcSpan loc $ - addErrCtxt (instDeclCtxt1 poly_ty) $ + addErrCtxt (instDeclCtxt1 hs_ty) $ do { (tyvars, theta, clas, inst_tys) - <- tcHsClsInstType (InstDeclCtxt False) poly_ty + <- tcHsClsInstType (InstDeclCtxt False) hs_ty -- NB: tcHsClsInstType does checkValidInstance ; tcExtendTyVarEnv tyvars $ @@ -481,7 +481,7 @@ tcClsInstDecl (L loc (ClsInstDecl { cid_poly_ty = poly_ty, cid_binds = binds mb_info = Just (clas, tyvars, mini_env) -- Next, process any associated types. - ; traceTc "tcLocalInstDecl" (ppr poly_ty) + ; traceTc "tcLocalInstDecl" (ppr hs_ty) ; tyfam_insts0 <- mapAndRecoverM (tcTyFamInstDecl mb_info) ats ; datafam_stuff <- mapAndRecoverM (tcDataFamInstDecl mb_info) adts ; let (datafam_insts, m_deriv_infos) = unzip datafam_stuff @@ -500,7 +500,7 @@ tcClsInstDecl (L loc (ClsInstDecl { cid_poly_ty = poly_ty, cid_binds = binds -- Finally, construct the Core representation of the instance. -- (This no longer includes the associated types.) - ; dfun_name <- newDFunName clas inst_tys (getLoc (hsSigType poly_ty)) + ; dfun_name <- newDFunName clas inst_tys (getLoc (hsSigType hs_ty)) -- Dfun location is that of instance *header* ; ispec <- newClsInst (fmap unLoc overlap_mode) dfun_name tyvars theta diff --git a/compiler/typecheck/TcMType.hs b/compiler/typecheck/TcMType.hs index 8192f75..9edad0f 100644 --- a/compiler/typecheck/TcMType.hs +++ b/compiler/typecheck/TcMType.hs @@ -1499,7 +1499,7 @@ defaultTyVar default_kind tv -- Do not default TyVarTvs. Doing so would violate the invariants -- on TyVarTvs; see Note [Signature skolems] in TcType. -- Trac #13343 is an example; #14555 is another - -- See Note [Kind generalisation and TyVarTvs] + -- See Note [Inferring kinds for type declarations] in TcTyClsDecls = return False diff --git a/compiler/typecheck/TcSimplify.hs b/compiler/typecheck/TcSimplify.hs index 750b621..e1a3532 100644 --- a/compiler/typecheck/TcSimplify.hs +++ b/compiler/typecheck/TcSimplify.hs @@ -2008,9 +2008,10 @@ promoteTyVarTcS tv defaultTyVarTcS :: TcTyVar -> TcS Bool defaultTyVarTcS the_tv | isRuntimeRepVar the_tv - , not (isTyVarTyVar the_tv) -- TyVarTvs should only be unified with a tyvar - -- never with a type; c.f. TcMType.defaultTyVar - -- See Note [Kind generalisation and TyVarTvs] + , not (isTyVarTyVar the_tv) + -- TyVarTvs should only be unified with a tyvar + -- never with a type; c.f. TcMType.defaultTyVar + -- and Note [Inferring kinds for type declarations] in TcTyClsDecls = do { traceTcS "defaultTyVarTcS RuntimeRep" (ppr the_tv) ; unifyTyVar the_tv liftedRepTy ; return True } From git at git.haskell.org Thu Nov 8 15:23:17 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 8 Nov 2018 15:23:17 +0000 (UTC) Subject: [commit: packages/array] master: Add a 'Read (UArray i e)' instance (2845463) Message-ID: <20181108152317.CC7863AC02@ghc.haskell.org> Repository : ssh://git at git.haskell.org/array On branch : master Link : http://git.haskell.org/packages/array.git/commitdiff/28454638ca681c4625f7c2fcf127821399d9ded3 >--------------------------------------------------------------- commit 28454638ca681c4625f7c2fcf127821399d9ded3 Author: Alec Theriault Date: Thu Nov 8 10:21:12 2018 -0500 Add a 'Read (UArray i e)' instance Summary: This matches exactly the 'Read (Array i e)' instance defined in base. Note that the same thing is being done for 'Show (UArray i e)'. Reviewers: RyanGlScott, bgamari GHC Trac Issues: #11335 Differential Revision: https://phabricator.haskell.org/D5156 >--------------------------------------------------------------- 28454638ca681c4625f7c2fcf127821399d9ded3 Data/Array/Base.hs | 23 +++++++++++++++++++++-- changelog.md | 4 ++++ 2 files changed, 25 insertions(+), 2 deletions(-) diff --git a/Data/Array/Base.hs b/Data/Array/Base.hs index 80e91ea..ed014cb 100644 --- a/Data/Array/Base.hs +++ b/Data/Array/Base.hs @@ -43,12 +43,16 @@ import GHC.ST ( ST(..), runST ) import GHC.Base ( IO(..), divInt# ) import GHC.Exts import GHC.Ptr ( nullPtr, nullFunPtr ) +import GHC.Show ( appPrec ) import GHC.Stable ( StablePtr(..) ) +import GHC.Read ( expectP, parens, Read(..) ) import GHC.Int ( Int8(..), Int16(..), Int32(..), Int64(..) ) import GHC.Word ( Word8(..), Word16(..), Word32(..), Word64(..) ) import GHC.IO ( stToIO ) import GHC.IOArray ( IOArray(..), newIOArray, unsafeReadIOArray, unsafeWriteIOArray ) +import Text.Read.Lex ( Lexeme(Ident) ) +import Text.ParserCombinators.ReadPrec ( prec, ReadPrec, step ) #include "MachDeps.h" @@ -479,7 +483,7 @@ cmpIntUArray arr1@(UArray l1 u1 n1 _) arr2@(UArray l2 u2 n2 _) = {-# RULES "cmpUArray/Int" cmpUArray = cmpIntUArray #-} ----------------------------------------------------------------------------- --- Showing IArrays +-- Showing and Reading IArrays {-# SPECIALISE showsIArray :: (IArray UArray e, Ix i, Show i, Show e) => @@ -488,12 +492,24 @@ cmpIntUArray arr1@(UArray l1 u1 n1 _) arr2@(UArray l2 u2 n2 _) = showsIArray :: (IArray a e, Ix i, Show i, Show e) => Int -> a i e -> ShowS showsIArray p a = - showParen (p > 9) $ + showParen (p > appPrec) $ showString "array " . shows (bounds a) . showChar ' ' . shows (assocs a) +{-# SPECIALISE + readIArray :: (IArray UArray e, Ix i, Read i, Read e) => + ReadPrec (UArray i e) + #-} + +readIArray :: (IArray a e, Ix i, Read i, Read e) => ReadPrec (a i e) +readIArray = parens $ prec appPrec $ + do expectP (Ident "array") + theBounds <- step readPrec + vals <- step readPrec + return (array theBounds vals) + ----------------------------------------------------------------------------- -- Flat unboxed arrays: instances @@ -785,6 +801,9 @@ instance (Ix ix, Ord e, IArray UArray e) => Ord (UArray ix e) where instance (Ix ix, Show ix, Show e, IArray UArray e) => Show (UArray ix e) where showsPrec = showsIArray +instance (Ix ix, Read ix, Read e, IArray UArray e) => Read (UArray ix e) where + readPrec = readIArray + ----------------------------------------------------------------------------- -- Mutable arrays diff --git a/changelog.md b/changelog.md index 8a3d149..0fd9289 100644 --- a/changelog.md +++ b/changelog.md @@ -1,5 +1,9 @@ # Changelog for [`array` package](http://hackage.haskell.org/package/array) +## Next + +* Add a `Read` instance for `UArray` + ## 0.5.3.0 *Oct 2018* * Bundled with GHC 8.6.2 From git at git.haskell.org Thu Nov 8 15:38:30 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 8 Nov 2018 15:38:30 +0000 (UTC) Subject: [commit: ghc] master: Fix #15845 by defining etaExpandFamInstLHS and using it (63a8170) Message-ID: <20181108153830.1BC663AC02@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/63a817074a8d49798bfd46a6545906fff143e924/ghc >--------------------------------------------------------------- commit 63a817074a8d49798bfd46a6545906fff143e924 Author: Ryan Scott Date: Thu Nov 8 10:26:48 2018 -0500 Fix #15845 by defining etaExpandFamInstLHS and using it Summary: Both #9692 and #14179 were caused by GHC being careless about using eta-reduced data family instance axioms. Each of those tickets were fixed by manually whipping up some code to eta-expand the axioms. The same sort of issue has now caused #15845, so I figured it was high time to factor out the code that each of these fixes have in common. This patch introduces the `etaExpandFamInstLHS` function, which takes a family instance's type variables, LHS types, and RHS type, and returns type variables and LHS types that have been eta-expanded if necessary, in the case of a data family instance. (If it's a type family instance, `etaExpandFamInstLHS` just returns the supplied type variables and LHS types unchanged). Along the way, I noticed that many references to `Note [Eta reduction for data families]` (in `FamInstEnv`) had slightly bitrotted (they either referred to a somewhat different name, or claimed that the Note lived in a different module), so I took the liberty of cleaning those up. Test Plan: make test TEST="T9692 T15845" Reviewers: goldfire, bgamari Reviewed By: goldfire Subscribers: rwbarton, carter GHC Trac Issues: #15845 Differential Revision: https://phabricator.haskell.org/D5294 >--------------------------------------------------------------- 63a817074a8d49798bfd46a6545906fff143e924 compiler/typecheck/TcSplice.hs | 23 ++++++++--------------- compiler/types/Coercion.hs | 18 ++++-------------- compiler/types/FamInstEnv.hs | 8 +++++++- compiler/types/TyCon.hs | 6 +++--- compiler/types/Type.hs | 39 +++++++++++++++++++++++++++++++++++++++ testsuite/tests/th/T15845.hs | 17 +++++++++++++++++ testsuite/tests/th/T15845.stderr | 5 +++++ testsuite/tests/th/T9692.stderr | 3 ++- testsuite/tests/th/all.T | 1 + 9 files changed, 86 insertions(+), 34 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 63a817074a8d49798bfd46a6545906fff143e924 From git at git.haskell.org Fri Nov 9 17:48:13 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Nov 2018 17:48:13 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Comments only (8484e28) Message-ID: <20181109174813.1DE893AC02@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/8484e28c383f3dff7ced83410f95547b537e55c1/ghc >--------------------------------------------------------------- commit 8484e28c383f3dff7ced83410f95547b537e55c1 Author: Simon Peyton Jones Date: Fri Nov 9 17:46:05 2018 +0000 Comments only >--------------------------------------------------------------- 8484e28c383f3dff7ced83410f95547b537e55c1 compiler/typecheck/TcMType.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/compiler/typecheck/TcMType.hs b/compiler/typecheck/TcMType.hs index 9edad0f..6d9f3ca 100644 --- a/compiler/typecheck/TcMType.hs +++ b/compiler/typecheck/TcMType.hs @@ -662,7 +662,8 @@ but this restriction was dropped, and ScopedTypeVariables can now refer to full types (GHC Proposal 29). The remaining uses of newTyVarTyVars are -* in kind signatures, see Note [Kind generalisation and TyVarTvs] +* In kind signatures, see + TcTyClsDecls Note [Inferring kinds for type declarations] and Note [Use TyVarTvs in kind-checking pass] * in partial type signatures, see Note [Quantified variables in partial type signatures] -} From git at git.haskell.org Fri Nov 9 18:12:47 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 9 Nov 2018 18:12:47 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Progress (3c9ce3e) Message-ID: <20181109181247.E09A23AC02@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/3c9ce3e8ad62e8ae64a910f919605f7c2b05667e/ghc >--------------------------------------------------------------- commit 3c9ce3e8ad62e8ae64a910f919605f7c2b05667e Author: Simon Peyton Jones Date: Fri Nov 9 18:11:25 2018 +0000 Progress Allocate result kind outside tcImplicit in tc_hs_sig_type_and_gen Plus comments In flight.. may not build (but it's a wip/ branch) >--------------------------------------------------------------- 3c9ce3e8ad62e8ae64a910f919605f7c2b05667e compiler/typecheck/TcHsType.hs | 49 +++++++++++++++++++++--------------------- compiler/typecheck/TcMType.hs | 18 ++++------------ 2 files changed, 29 insertions(+), 38 deletions(-) diff --git a/compiler/typecheck/TcHsType.hs b/compiler/typecheck/TcHsType.hs index dd2995e..7f5d4ff 100644 --- a/compiler/typecheck/TcHsType.hs +++ b/compiler/typecheck/TcHsType.hs @@ -229,19 +229,15 @@ tc_hs_sig_type_and_gen skol_info hs_sig_type ctxt_kind | HsIB { hsib_ext = sig_vars, hsib_body = hs_ty } <- hs_sig_type = do { (_inner_lvl, wanted, (tkvs, ty)) <- pushLevelAndCaptureConstraints $ - tcImplicitTKBndrs skol_info sig_vars $ - -- tcImplicitTKBndrs does a solveLocalEqualities - do { kind <- case ctxt_kind of + do { -- See Note [Levels and generalisation] + res_kind <- case ctxt_kind of TheKind k -> return k AnyKind -> newMetaKindVar OpenKind -> newOpenTypeKind - -- The kind is checked by checkValidType, and isn't necessarily - -- of kind * in a Template Haskell quote eg [t| Maybe |] - ; tc_lhs_type typeLevelMode hs_ty kind } - -- Any remaining variables (unsolved in the solveLocalEqualities - -- in the tcImplicitTKBndrs) should be in the global tyvars, - -- and therefore won't be quantified over + ; tcImplicitTKBndrs skol_info sig_vars $ + -- tcImplicitTKBndrs does a solveLocalEqualities + tc_lhs_type typeLevelMode hs_ty res_kind } ; let ty1 = mkSpecForAllTys tkvs ty ; kvs <- kindGeneralizeLocal wanted ty1 @@ -1467,20 +1463,6 @@ To avoid the double-zonk, we do two things: 2. When we are generalizing: kindGeneralize does not require a zonked type -- it zonks as it gathers free variables. So this way effectively sidesteps step 3. - -Note [TcLevel for CUSKs] -~~~~~~~~~~~~~~~~~~~~~~~~ -In getInitialKinds we are at level 1, busy making unification -variables over which we will subsequently generalise. - -But when we find a CUSK we want to jump back to top level (0) -because that's the right starting point for a completee, -stand-alone kind signature. - -More precisely, we want to make level-1 skolems, because -the end up as the TyConBinders of the TyCon, and are brought -into scope when we type-check the body of the type declaration -(in tcTyClDecl). -} tcWildCardBinders :: [Name] @@ -2003,7 +1985,26 @@ kindGeneralizeLocal wanted kind_or_type ; quantifyTyVars mono_tvs dvs } -{- +{- Note [Levels and generalisation] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Consider + f x = e +with no type signature. We are currently at level i. +We must + * Push the level to level (i+1) + * Allocate a fresh alpha[i+1] for the result type + * Check that e :: alpha[i+1], gathering constraint WC + * Solve WC as far as possible + * Zonking the result type alpha[i+1], say to beta[i-1] -> gamma[i] + * Find the free variables with level > i, in this case gamma[i] + * Skolemise those free variables and quantify over them, giving + f :: forall g. beta[i-1] -> g + * Emit the residiual constraint wrapped in an implication for g, + thus forall g. WC + +All of this happens for types too. Consider + f :: Int -> (forall a. Proxy a -> Int) + Note [Kind generalisation] ~~~~~~~~~~~~~~~~~~~~~~~~~~ We do kind generalisation only at the outer level of a type signature. diff --git a/compiler/typecheck/TcMType.hs b/compiler/typecheck/TcMType.hs index 6d9f3ca..a1cdf24 100644 --- a/compiler/typecheck/TcMType.hs +++ b/compiler/typecheck/TcMType.hs @@ -1342,16 +1342,6 @@ to be later converted to a list in a deterministic order. For more information about deterministic sets see Note [Deterministic UniqFM] in UniqDFM. - - ---------------- Note to tidy up -------- -Can we quantify over a non-unification variable? Sadly yes (Trac #15991b) - class C2 (a :: Type) (b :: Proxy a) (c :: Proxy b) where - type T4 a c - -When we come to T4 we have in Inferred b; but it is a skolem -from the (fully settled) C2. - -} quantifyTyVars @@ -1444,10 +1434,10 @@ quantifyTyVars gbl_tvs = return Nothing -- this can happen for a covar that's associated with -- a coercion hole. Test case: typecheck/should_compile/T2494 - | not (isTcTyVar tkv) - = WARN( True, text "quantifying over a TyVar" <+> ppr tkv) - return (Just tkv) -- For associated types, we have the class variables - -- in scope, and they are TyVars not TcTyVars + | not (isTcTyVar tkv) -- I don't think this can ever happen. + -- Hence the assert + = ASSERT2( False, text "quantifying over a TyVar" <+> ppr tkv) + return (Just tkv) | otherwise = do { deflt_done <- defaultTyVar default_kind tkv From git at git.haskell.org Sat Nov 10 09:20:30 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 10 Nov 2018 09:20:30 +0000 (UTC) Subject: [commit: ghc] branch 'wip/shnajd-TTG-SrcLocs' created Message-ID: <20181110092030.67D0F3AC03@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/shnajd-TTG-SrcLocs Referencing: 6741b78e1abef9f8df381261e541fcdbb30d0d48 From git at git.haskell.org Sat Nov 10 09:20:33 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 10 Nov 2018 09:20:33 +0000 (UTC) Subject: [commit: ghc] wip/shnajd-TTG-SrcLocs: [TTG: Handling Source Locations] Foundation and Pat Trac Issue: #15495 This patch removes the ping-pong style from `HsPat` (only, for now), using the plan laid out at https://ghc.haskell.org/trac/ghc/wiki/ImplementingTreesThatGrow/HandlingSourceLocations (solution A). (6be401f) Message-ID: <20181110092033.9BF903AC03@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/shnajd-TTG-SrcLocs Link : http://ghc.haskell.org/trac/ghc/changeset/6be401f9cb9cfc2fa0836fd1775e9d58b781c534/ghc >--------------------------------------------------------------- commit 6be401f9cb9cfc2fa0836fd1775e9d58b781c534 Author: Shayan-Najd Date: Thu Nov 8 22:09:13 2018 +0000 [TTG: Handling Source Locations] Foundation and Pat Trac Issue: #15495 This patch removes the ping-pong style from `HsPat` (only, for now), using the plan laid out at https://ghc.haskell.org/trac/ghc/wiki/ImplementingTreesThatGrow/HandlingSourceLocations (solution A). - the class `HasSrcSpan`, and its functions (e.g., `cL` and `dL`), are introduced - some instances of `HasSrcSpan` are introduced - some constructors `L` are replaced with `cL` - some patterns `L` are replaced with `dL` view pattern - some type annotation are necessarily updated updated (e.g., `Pat p` --> `Pat (GhcPass p)`) >--------------------------------------------------------------- 6be401f9cb9cfc2fa0836fd1775e9d58b781c534 compiler/basicTypes/Name.hs | 8 +- compiler/basicTypes/SrcLoc.hs | 125 ++++++++-- compiler/deSugar/Check.hs | 38 +-- compiler/deSugar/DsArrows.hs | 3 +- compiler/deSugar/DsExpr.hs | 2 +- compiler/deSugar/DsListComp.hs | 2 +- compiler/deSugar/DsMeta.hs | 3 +- compiler/deSugar/DsUtils.hs | 47 ++-- compiler/deSugar/ExtractDocs.hs | 4 +- compiler/deSugar/Match.hs | 24 +- compiler/deSugar/MatchCon.hs | 3 +- compiler/hsSyn/Convert.hs | 107 ++++---- compiler/hsSyn/HsPat.hs | 74 ++++-- compiler/hsSyn/HsPat.hs-boot | 3 +- compiler/hsSyn/HsTypes.hs | 4 +- compiler/hsSyn/HsUtils.hs | 172 +++++++------ compiler/main/GHC.hs | 4 + compiler/main/HeaderInfo.hs | 57 ++--- compiler/main/HscStats.hs | 3 +- compiler/main/HscTypes.hs | 3 +- compiler/parser/Lexer.x | 32 +-- compiler/parser/Parser.y | 103 ++++---- compiler/parser/RdrHsSyn.hs | 486 +++++++++++++++++++------------------ compiler/rename/RnBinds.hs | 10 +- compiler/rename/RnExpr.hs | 7 +- compiler/rename/RnPat.hs | 50 ++-- compiler/rename/RnSplice.hs | 8 +- compiler/rename/RnTypes.hs | 120 ++++----- compiler/typecheck/TcBinds.hs | 3 +- compiler/typecheck/TcErrors.hs | 3 +- compiler/typecheck/TcHsSyn.hs | 3 +- compiler/typecheck/TcHsType.hs | 1 + compiler/typecheck/TcPat.hs | 13 +- compiler/typecheck/TcPatSyn.hs | 41 ++-- compiler/typecheck/TcRnDriver.hs | 21 +- compiler/typecheck/TcRnExports.hs | 4 +- compiler/typecheck/TcRnMonad.hs | 27 ++- compiler/typecheck/TcTyClsDecls.hs | 27 ++- compiler/typecheck/TcTyDecls.hs | 31 +-- compiler/utils/Binary.hs | 2 +- ghc/GHCi/UI/Info.hs | 7 +- testsuite/tests/ghc-api/T6145.hs | 13 +- utils/ghctags/Main.hs | 2 +- utils/haddock | 2 +- 44 files changed, 968 insertions(+), 734 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 6be401f9cb9cfc2fa0836fd1775e9d58b781c534 From git at git.haskell.org Sat Nov 10 09:20:38 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 10 Nov 2018 09:20:38 +0000 (UTC) Subject: [commit: ghc] wip/shnajd-TTG-SrcLocs: Merge branch 'master' of git://github.com/ghc/ghc into wip/shnajd-TTG-SrcLocs (869d99b) Message-ID: <20181110092038.794233AC03@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/shnajd-TTG-SrcLocs Link : http://ghc.haskell.org/trac/ghc/changeset/869d99bcc8ef4aa69dfb79825e4ee73af96cab62/ghc >--------------------------------------------------------------- commit 869d99bcc8ef4aa69dfb79825e4ee73af96cab62 Merge: 6be401f 63a8170 Author: Shayan-Najd Date: Thu Nov 8 22:12:48 2018 +0000 Merge branch 'master' of git://github.com/ghc/ghc into wip/shnajd-TTG-SrcLocs >--------------------------------------------------------------- 869d99bcc8ef4aa69dfb79825e4ee73af96cab62 .circleci/config.yml | 43 +- .circleci/push-test-metrics.sh | 46 + compiler/codeGen/StgCmmPrim.hs | 6 +- compiler/llvmGen/Llvm/Types.hs | 2 +- compiler/llvmGen/LlvmCodeGen/Base.hs | 115 +-- compiler/llvmGen/LlvmCodeGen/CodeGen.hs | 64 +- compiler/typecheck/TcSplice.hs | 23 +- compiler/types/Coercion.hs | 18 +- compiler/types/FamInstEnv.hs | 8 +- compiler/types/TyCon.hs | 6 +- compiler/types/Type.hs | 39 + libraries/base/tests/all.T | 18 +- libraries/directory | 2 +- libraries/integer-gmp/changelog.md | 2 +- llvm-passes | 2 +- testsuite/driver/README.md | 133 +++ testsuite/driver/perf_notes.py | 382 ++++++++ testsuite/driver/runtests.py | 71 +- testsuite/driver/testglobals.py | 33 +- testsuite/driver/testlib.py | 228 +++-- testsuite/driver/testutil.py | 18 + testsuite/mk/test.mk | 12 + testsuite/tests/callarity/perf/all.T | 12 +- testsuite/tests/codeGen/should_run/all.T | 3 +- testsuite/tests/dependent/should_fail/T15859.hs | 13 + testsuite/tests/deriving/perf/all.T | 11 +- testsuite/tests/perf/compiler/all.T | 1056 ++--------------------- testsuite/tests/perf/haddock/all.T | 184 +--- testsuite/tests/perf/join_points/all.T | 16 +- testsuite/tests/perf/should_run/all.T | 374 ++------ testsuite/tests/perf/space_leaks/all.T | 75 +- testsuite/tests/pmcheck/should_compile/all.T | 27 +- testsuite/tests/primops/should_run/all.T | 6 +- testsuite/tests/simplCore/should_compile/all.T | 3 +- testsuite/tests/simplStg/should_run/all.T | 5 +- testsuite/tests/th/T15845.hs | 17 + testsuite/tests/th/T15845.stderr | 5 + testsuite/tests/th/T9692.stderr | 3 +- testsuite/tests/th/all.T | 1 + 39 files changed, 1187 insertions(+), 1895 deletions(-) From git at git.haskell.org Sat Nov 10 09:20:41 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 10 Nov 2018 09:20:41 +0000 (UTC) Subject: [commit: ghc] wip/shnajd-TTG-SrcLocs: Rebasing (4032519) Message-ID: <20181110092041.9E99A3AC03@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/shnajd-TTG-SrcLocs Link : http://ghc.haskell.org/trac/ghc/changeset/4032519866788b6de76d48d2187452b543a95197/ghc >--------------------------------------------------------------- commit 4032519866788b6de76d48d2187452b543a95197 Author: Shayan-Najd Date: Thu Nov 8 22:13:58 2018 +0000 Rebasing >--------------------------------------------------------------- 4032519866788b6de76d48d2187452b543a95197 libraries/directory | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/directory b/libraries/directory index 19d6dc0..e9debc1 160000 --- a/libraries/directory +++ b/libraries/directory @@ -1 +1 @@ -Subproject commit 19d6dc0d33366a8920bf8acc7a0fd3ef533d39c3 +Subproject commit e9debc1d4a9c4b608a32f60bae173ed10f89fdce From git at git.haskell.org Sat Nov 10 09:20:44 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 10 Nov 2018 09:20:44 +0000 (UTC) Subject: [commit: ghc] wip/shnajd-TTG-SrcLocs: [TTG: Handling Source Locations] Foundation and Pat (Part 2) - Fixing a bug (6741b78) Message-ID: <20181110092044.AD0983AC03@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/shnajd-TTG-SrcLocs Link : http://ghc.haskell.org/trac/ghc/changeset/6741b78e1abef9f8df381261e541fcdbb30d0d48/ghc >--------------------------------------------------------------- commit 6741b78e1abef9f8df381261e541fcdbb30d0d48 Author: Shayan-Najd Date: Fri Nov 9 19:29:49 2018 +0000 [TTG: Handling Source Locations] Foundation and Pat (Part 2) - Fixing a bug >--------------------------------------------------------------- 6741b78e1abef9f8df381261e541fcdbb30d0d48 compiler/hsSyn/HsPat.hs | 10 +++++----- testsuite/tests/parser/should_compile/KindSigs.stderr | 14 ++++++++------ 2 files changed, 13 insertions(+), 11 deletions(-) diff --git a/compiler/hsSyn/HsPat.hs b/compiler/hsSyn/HsPat.hs index ece051f..f7bb3c9 100644 --- a/compiler/hsSyn/HsPat.hs +++ b/compiler/hsSyn/HsPat.hs @@ -534,7 +534,7 @@ pprParendPat p pat = sdocWithDynFlags $ \ dflags -> -- is the pattern inside that matters. Sigh. pprPat :: (OutputableBndrId (GhcPass p)) => Pat (GhcPass p) -> SDoc -pprPat (VarPat _ (L _ var)) = pprPatBndr var +pprPat (VarPat _ (dL->(_ , var))) = pprPatBndr var pprPat (WildPat _) = char '_' pprPat (LazyPat _ pat) = char '~' <> pprParendLPat appPrec pat pprPat (BangPat _ pat) = char '!' <> pprParendLPat appPrec pat @@ -569,7 +569,7 @@ pprPat (ConPatOut { pat_con = con, pat_tvs = tvs, pat_dicts = dicts, , ppr binds]) <+> pprConArgs details else pprUserCon (unLoc con) details -pprPat (XPat x) = ppr x +pprPat (XPat (l , e)) = whenPprDebug (braces (ppr l)) $$ ppr e pprUserCon :: (OutputableBndr con, OutputableBndrId (GhcPass p)) @@ -714,12 +714,12 @@ isIrrefutableHsPat pat go1 (ListPat {}) = False go1 (ConPatIn {}) = False -- Conservative - go1 (ConPatOut{ pat_con = L _ (RealDataCon con), pat_args = details }) + go1 (ConPatOut{ pat_con = dL->(_ , RealDataCon con), pat_args = details }) = isJust (tyConSingleDataCon_maybe (dataConTyCon con)) -- NB: tyConSingleDataCon_maybe, *not* isProductTyCon, because -- the latter is false of existentials. See Trac #4439 && all go (hsConPatArgs details) - go1 (ConPatOut{ pat_con = L _ (PatSynCon _pat) }) + go1 (ConPatOut{}) = False -- Conservative go1 (LitPat {}) = False @@ -776,7 +776,7 @@ patNeedsParens p = go go (SumPat {}) = False go (ListPat {}) = False go (LitPat _ l) = hsLitNeedsParens p l - go (NPat _ (L _ ol) _ _) = hsOverLitNeedsParens p ol + go (NPat _ (dL->(_ , ol)) _ _) = hsOverLitNeedsParens p ol go (XPat {}) = True -- conservative default -- | @'conPatNeedsParens' p cp@ returns 'True' if the constructor patterns @cp@ diff --git a/testsuite/tests/parser/should_compile/KindSigs.stderr b/testsuite/tests/parser/should_compile/KindSigs.stderr index 71a54b0..c7d59b7 100644 --- a/testsuite/tests/parser/should_compile/KindSigs.stderr +++ b/testsuite/tests/parser/should_compile/KindSigs.stderr @@ -338,12 +338,16 @@ {OccName: qux})) (Prefix) (NoSrcStrict)) - [({ KindSigs.hs:23:5 } + [(XPat + ((,) + { KindSigs.hs:23:5 } (WildPat - (NoExt))) - ,({ KindSigs.hs:23:7 } + (NoExt)))) + ,(XPat + ((,) + { KindSigs.hs:23:7 } (WildPat - (NoExt)))] + (NoExt))))] (GRHSs (NoExt) [({ KindSigs.hs:23:9-12 } @@ -605,5 +609,3 @@ [])))] (Nothing) (Nothing))) - - From git at git.haskell.org Sun Nov 11 13:30:27 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 11 Nov 2018 13:30:27 +0000 (UTC) Subject: [commit: ghc] master: GHCi does not need a main function (400f3ed) Message-ID: <20181111133027.455B33AC03@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/400f3ed8ca830513ac6870d28bf46ed6b6bb720b/ghc >--------------------------------------------------------------- commit 400f3ed8ca830513ac6870d28bf46ed6b6bb720b Author: roland Date: Sun Nov 11 11:19:30 2018 +0100 GHCi does not need a main function Summary: In GHCi we don't check anymore, whether a main function is exported. Test Plan: make test TEST=T11647 Reviewers: hvr, osa1, monoidal, mpickering, bgamari Reviewed By: osa1, mpickering Subscribers: rwbarton, carter GHC Trac Issues: #11647 Differential Revision: https://phabricator.haskell.org/D5162 >--------------------------------------------------------------- 400f3ed8ca830513ac6870d28bf46ed6b6bb720b compiler/typecheck/TcRnDriver.hs | 8 +++++--- testsuite/tests/typecheck/should_run/T11647.hs | 1 + testsuite/tests/typecheck/should_run/T11647.script | 2 ++ .../{dynlibs/T5373B.hs => typecheck/should_run/T11647Sub.hs} | 2 +- testsuite/tests/typecheck/should_run/all.T | 1 + 5 files changed, 10 insertions(+), 4 deletions(-) diff --git a/compiler/typecheck/TcRnDriver.hs b/compiler/typecheck/TcRnDriver.hs index 4fa1723..a3e2a2f 100644 --- a/compiler/typecheck/TcRnDriver.hs +++ b/compiler/typecheck/TcRnDriver.hs @@ -1758,9 +1758,11 @@ checkMainExported tcg_env Just main_name -> do { dflags <- getDynFlags ; let main_mod = mainModIs dflags - ; checkTc (main_name `elem` concatMap availNames (tcg_exports tcg_env)) $ - text "The" <+> ppMainFn (nameRdrName main_name) <+> - text "is not exported by module" <+> quotes (ppr main_mod) } + ; when (ghcLink dflags /= LinkInMemory) $ -- #11647 + checkTc (main_name `elem` + concatMap availNames (tcg_exports tcg_env)) $ + text "The" <+> ppMainFn (nameRdrName main_name) <+> + text "is not exported by module" <+> quotes (ppr main_mod) } ppMainFn :: RdrName -> SDoc ppMainFn main_fn diff --git a/testsuite/tests/typecheck/should_run/T11647.hs b/testsuite/tests/typecheck/should_run/T11647.hs new file mode 100644 index 0000000..37ca876 --- /dev/null +++ b/testsuite/tests/typecheck/should_run/T11647.hs @@ -0,0 +1 @@ +import T11647Sub (main) diff --git a/testsuite/tests/typecheck/should_run/T11647.script b/testsuite/tests/typecheck/should_run/T11647.script new file mode 100644 index 0000000..7966e18 --- /dev/null +++ b/testsuite/tests/typecheck/should_run/T11647.script @@ -0,0 +1,2 @@ +:l T11647.hs +main diff --git a/testsuite/tests/dynlibs/T5373B.hs b/testsuite/tests/typecheck/should_run/T11647Sub.hs similarity index 51% copy from testsuite/tests/dynlibs/T5373B.hs copy to testsuite/tests/typecheck/should_run/T11647Sub.hs index 0570fb1..b807c95 100644 --- a/testsuite/tests/dynlibs/T5373B.hs +++ b/testsuite/tests/typecheck/should_run/T11647Sub.hs @@ -1,4 +1,4 @@ +module T11647Sub (main) where main :: IO () main = return () - diff --git a/testsuite/tests/typecheck/should_run/all.T b/testsuite/tests/typecheck/should_run/all.T index bdf70e0..a41df81 100755 --- a/testsuite/tests/typecheck/should_run/all.T +++ b/testsuite/tests/typecheck/should_run/all.T @@ -125,6 +125,7 @@ test('TestTypeableBinary', normal, compile_and_run, ['']) test('Typeable1', normal, compile_fail, ['-Werror']) test('TypeableEq', normal, compile_and_run, ['']) test('T13435', normal, compile_and_run, ['']) +test('T11647', normal, ghci_script, ['T11647.script']) test('T11715', exit_code(1), compile_and_run, ['']) test('T13594a', normal, ghci_script, ['T13594a.script']) From git at git.haskell.org Sun Nov 11 13:30:30 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 11 Nov 2018 13:30:30 +0000 (UTC) Subject: [commit: ghc] master: iserv: Fix typo in cabal file (aa88285) Message-ID: <20181111133030.3F3CE3AC03@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/aa88285e38081186a8c74ceca1332135af09bab3/ghc >--------------------------------------------------------------- commit aa88285e38081186a8c74ceca1332135af09bab3 Author: Matthew Pickering Date: Sun Nov 11 11:20:19 2018 +0100 iserv: Fix typo in cabal file Reviewers: bgamari, RyanGlScott Reviewed By: RyanGlScott Subscribers: RyanGlScott, rwbarton, carter Differential Revision: https://phabricator.haskell.org/D5311 >--------------------------------------------------------------- aa88285e38081186a8c74ceca1332135af09bab3 utils/iserv/iserv.cabal | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/utils/iserv/iserv.cabal b/utils/iserv/iserv.cabal index 0f45c8d..912734f 100644 --- a/utils/iserv/iserv.cabal +++ b/utils/iserv/iserv.cabal @@ -5,7 +5,7 @@ License: BSD3 -- XXX License-File: LICENSE Author: XXX Maintainer: XXX -Synopsis: iserv allows GHC to delegate Tempalte Haskell computations +Synopsis: iserv allows GHC to delegate Template Haskell computations Description: GHC can be provided with a path to the iserv binary with @-pgmi=/path/to/iserv-bin@, and will in combination with From git at git.haskell.org Sun Nov 11 13:30:33 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 11 Nov 2018 13:30:33 +0000 (UTC) Subject: [commit: ghc] master: Ignore .gdb_history files (b337906) Message-ID: <20181111133033.55FC23AC03@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b337906ca04c8ac6b9a5b11dcc0cbb954cb44cab/ghc >--------------------------------------------------------------- commit b337906ca04c8ac6b9a5b11dcc0cbb954cb44cab Author: Ben Gamari Date: Sun Nov 11 11:20:57 2018 +0100 Ignore .gdb_history files Summary: I tend to accumulate these and they are often quite useful to keep around. Reviewers: monoidal Reviewed By: monoidal Subscribers: rwbarton, carter Differential Revision: https://phabricator.haskell.org/D5320 >--------------------------------------------------------------- b337906ca04c8ac6b9a5b11dcc0cbb954cb44cab .gitignore | 1 + 1 file changed, 1 insertion(+) diff --git a/.gitignore b/.gitignore index 83fa7ec..59ca1cc 100644 --- a/.gitignore +++ b/.gitignore @@ -215,3 +215,4 @@ GIT_COMMIT_ID ghc.nix/ +.gdb_history \ No newline at end of file From git at git.haskell.org Sun Nov 11 13:30:36 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 11 Nov 2018 13:30:36 +0000 (UTC) Subject: [commit: ghc] master: Respect naming conventions in module RnUnbound.hs in fix for #15611 (98f8e1c) Message-ID: <20181111133036.503CF3AC03@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/98f8e1c2454b8c99cbb225e4a8a544288eeb082a/ghc >--------------------------------------------------------------- commit 98f8e1c2454b8c99cbb225e4a8a544288eeb082a Author: Roland Senn Date: Sun Nov 11 11:21:26 2018 +0100 Respect naming conventions in module RnUnbound.hs in fix for #15611 Summary: The patch https://phabricator.haskell.org/D5284 didn't respect the local naming conventions in module compiler/rename/RnUnbound.hs: - Top level functions names are written in camelCase. - Local function names in where clauses are written as names_with_underscores. This patch restores these conventions. Test Plan: make test TESTS="T15611a T15611b" Reviewers: DavidEichmann, monoidal, hvr, mpickering, bgamari Reviewed By: mpickering Subscribers: rwbarton, carter GHC Trac Issues: #15611 Differential Revision: https://phabricator.haskell.org/D5308 >--------------------------------------------------------------- 98f8e1c2454b8c99cbb225e4a8a544288eeb082a compiler/rename/RnUnbound.hs | 22 +++++++++++----------- 1 file changed, 11 insertions(+), 11 deletions(-) diff --git a/compiler/rename/RnUnbound.hs b/compiler/rename/RnUnbound.hs index 97d3fd7..bf481c5 100644 --- a/compiler/rename/RnUnbound.hs +++ b/compiler/rename/RnUnbound.hs @@ -238,7 +238,7 @@ importSuggestions where_look hpt currMod imports rdr_name | not (isQual rdr_name || isUnqual rdr_name) = Outputable.empty | null interesting_imports , Just name <- mod_name - , showNotImportedLine (fromJust mod_name) + , show_not_imported_line name = hsep [ text "No module named" , quotes (ppr name) @@ -341,18 +341,18 @@ importSuggestions where_look hpt currMod imports rdr_name (helpful_imports_hiding, helpful_imports_non_hiding) = partition (imv_is_hiding . snd) helpful_imports - -- See note [showNotImportedLine] - showNotImportedLine :: ModuleName -> Bool -- #15611 - showNotImportedLine modnam + -- See note [When to show/hide the module-not-imported line] + show_not_imported_line :: ModuleName -> Bool -- #15611 + show_not_imported_line modnam | modnam `elem` fmap moduleName (moduleEnvKeys (imp_mods imports)) = False -- 1 - | moduleName currMod == modnam = False -- 2.1 - | isLastLoadedMod modnam hptUniques = False -- 2.2 - | otherwise = True + | moduleName currMod == modnam = False -- 2.1 + | is_last_loaded_mod modnam hpt_uniques = False -- 2.2 + | otherwise = True where - hptUniques = map fst (udfmToList hpt) - isLastLoadedMod _ [] = False - isLastLoadedMod modnam uniqs = last uniqs == getUnique modnam + hpt_uniques = map fst (udfmToList hpt) + is_last_loaded_mod _ [] = False + is_last_loaded_mod modnam uniqs = last uniqs == getUnique modnam extensionSuggestions :: RdrName -> SDoc extensionSuggestions rdrName @@ -366,7 +366,7 @@ perhapsForallMsg = vcat [ text "Perhaps you intended to use ExplicitForAll or similar flag" , text "to enable explicit-forall syntax: forall . "] -{- Note [showNotImportedLine] -- #15611 +{- Note [When to show/hide the module-not-imported line] -- #15611 For the error message: Not in scope X.Y Module X does not export Y From git at git.haskell.org Mon Nov 12 03:40:02 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 12 Nov 2018 03:40:02 +0000 (UTC) Subject: [commit: ghc] master: Fix #15594 (--abi-hash with Backpack sometimes fails) (13ff0b7) Message-ID: <20181112034002.58DD13AC03@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/13ff0b7ced097286e0d7b054f050871effe07f86/ghc >--------------------------------------------------------------- commit 13ff0b7ced097286e0d7b054f050871effe07f86 Author: Edward Z. Yang Date: Sun Nov 11 22:39:29 2018 -0500 Fix #15594 (--abi-hash with Backpack sometimes fails) Summary: For holes, its necessary to "see through" the instantiation of the hole to get accurate family instance dependencies. For example, if B imports , and is instantiated with F, we must grab and include all of the dep_finsts from F to have an accurate transitive dep_finsts list. However, we MUST NOT do this for regular modules. First, for efficiency reasons, doing this bloats the the dep_finsts list, because we *already* had those modules in the list (it wasn't a hole module, after all). But there's a second, more important correctness consideration: we perform module renaming when running --abi-hash. In this case, GHC's contract to the user is that it will NOT go and read out interfaces of any dependencies (https://github.com/haskell/cabal/issues/3633); the point of --abi-hash is just to get a hash of the on-disk interfaces for this *specific* package. If we go off and tug on the interface for /everything/ in dep_finsts, we're gonna have a bad time. (It's safe to do do this for hole modules, though, because the hmap for --abi-hash is always trivial, so the interface we request is local. Though, maybe we ought not to do it in this case either...) Signed-off-by: Edward Z. Yang Test Plan: validate Reviewers: alexbiehl, goldfire, bgamari Subscribers: ppk, shlevy, rwbarton, carter GHC Trac Issues: #15594 Differential Revision: https://phabricator.haskell.org/D5123 >--------------------------------------------------------------- 13ff0b7ced097286e0d7b054f050871effe07f86 compiler/backpack/RnModIface.hs | 32 ++++++++++++++++++++-- .../backpack/cabal/{bkpcabal07 => T15594}/Makefile | 10 +++---- .../backpack/cabal/{T14304 => T15594}/Setup.hs | 0 .../cabal/{T14304/indef => T15594}/Sig.hsig | 3 +- testsuite/tests/backpack/cabal/T15594/Stuff.hs | 10 +++++++ testsuite/tests/backpack/cabal/T15594/all.T | 9 ++++++ testsuite/tests/backpack/cabal/T15594/pkg.cabal | 19 +++++++++++++ testsuite/tests/backpack/cabal/T15594/src/Lib.hs | 7 +++++ 8 files changed, 80 insertions(+), 10 deletions(-) diff --git a/compiler/backpack/RnModIface.hs b/compiler/backpack/RnModIface.hs index 3ae01d7..896303b 100644 --- a/compiler/backpack/RnModIface.hs +++ b/compiler/backpack/RnModIface.hs @@ -138,10 +138,36 @@ rnDepModules sel deps = do -- in these dependencies. fmap (nubSort . concat) . T.forM (sel deps) $ \mod -> do dflags <- getDynFlags + -- For holes, its necessary to "see through" the instantiation + -- of the hole to get accurate family instance dependencies. + -- For example, if B imports , and is instantiated with + -- F, we must grab and include all of the dep_finsts from + -- F to have an accurate transitive dep_finsts list. + -- + -- However, we MUST NOT do this for regular modules. + -- First, for efficiency reasons, doing this + -- bloats the the dep_finsts list, because we *already* had + -- those modules in the list (it wasn't a hole module, after + -- all). But there's a second, more important correctness + -- consideration: we perform module renaming when running + -- --abi-hash. In this case, GHC's contract to the user is that + -- it will NOT go and read out interfaces of any dependencies + -- (https://github.com/haskell/cabal/issues/3633); the point of + -- --abi-hash is just to get a hash of the on-disk interfaces + -- for this *specific* package. If we go off and tug on the + -- interface for /everything/ in dep_finsts, we're gonna have a + -- bad time. (It's safe to do do this for hole modules, though, + -- because the hmap for --abi-hash is always trivial, so the + -- interface we request is local. Though, maybe we ought + -- not to do it in this case either...) + -- + -- This mistake was bug #15594. let mod' = renameHoleModule dflags hmap mod - iface <- liftIO . initIfaceCheck (text "rnDepModule") hsc_env - $ loadSysInterface (text "rnDepModule") mod' - return (mod' : sel (mi_deps iface)) + if isHoleModule mod + then do iface <- liftIO . initIfaceCheck (text "rnDepModule") hsc_env + $ loadSysInterface (text "rnDepModule") mod' + return (mod' : sel (mi_deps iface)) + else return [mod'] {- ************************************************************************ diff --git a/testsuite/tests/backpack/cabal/bkpcabal07/Makefile b/testsuite/tests/backpack/cabal/T15594/Makefile similarity index 73% copy from testsuite/tests/backpack/cabal/bkpcabal07/Makefile copy to testsuite/tests/backpack/cabal/T15594/Makefile index 346ac32..57ef67f 100644 --- a/testsuite/tests/backpack/cabal/bkpcabal07/Makefile +++ b/testsuite/tests/backpack/cabal/T15594/Makefile @@ -1,19 +1,17 @@ -TOP=../../../.. +TOP=/home/ezyang/Dev/ghc-known-nat/testsuite include $(TOP)/mk/boilerplate.mk include $(TOP)/mk/test.mk SETUP='$(PWD)/Setup' -v0 CONFIGURE=$(SETUP) configure $(CABAL_MINIMAL_BUILD) --with-ghc='$(TEST_HC)' --ghc-options='$(TEST_HC_OPTS)' --package-db='$(PWD)/tmp.d' --prefix='$(PWD)/inst' -# This test checks that instantiating an indefinite package -# with a wired in package works. - -bkpcabal07: clean - $(MAKE) -s --no-print-directory clean +T15594: clean '$(GHC_PKG)' init tmp.d '$(TEST_HC)' $(TEST_HC_OPTS) -v0 --make Setup $(CONFIGURE) $(SETUP) build + $(SETUP) copy + $(SETUP) register ifneq "$(CLEANUP)" "" $(MAKE) -s --no-print-directory clean endif diff --git a/testsuite/tests/backpack/cabal/T14304/Setup.hs b/testsuite/tests/backpack/cabal/T15594/Setup.hs similarity index 100% copy from testsuite/tests/backpack/cabal/T14304/Setup.hs copy to testsuite/tests/backpack/cabal/T15594/Setup.hs diff --git a/testsuite/tests/backpack/cabal/T14304/indef/Sig.hsig b/testsuite/tests/backpack/cabal/T15594/Sig.hsig similarity index 57% copy from testsuite/tests/backpack/cabal/T14304/indef/Sig.hsig copy to testsuite/tests/backpack/cabal/T15594/Sig.hsig index a37b190..1342a7b 100644 --- a/testsuite/tests/backpack/cabal/T14304/indef/Sig.hsig +++ b/testsuite/tests/backpack/cabal/T15594/Sig.hsig @@ -1,2 +1,3 @@ signature Sig where -data B + +foo :: String diff --git a/testsuite/tests/backpack/cabal/T15594/Stuff.hs b/testsuite/tests/backpack/cabal/T15594/Stuff.hs new file mode 100644 index 0000000..053949b --- /dev/null +++ b/testsuite/tests/backpack/cabal/T15594/Stuff.hs @@ -0,0 +1,10 @@ +{-# LANGUAGE TypeFamilies #-} +module Stuff where + +data family T a + +data instance T Int = T Int + +test :: String +test = + "test" diff --git a/testsuite/tests/backpack/cabal/T15594/all.T b/testsuite/tests/backpack/cabal/T15594/all.T new file mode 100644 index 0000000..1978865 --- /dev/null +++ b/testsuite/tests/backpack/cabal/T15594/all.T @@ -0,0 +1,9 @@ +if config.cleanup: + cleanup = 'CLEANUP=1' +else: + cleanup = 'CLEANUP=0' + +test('T15594', + extra_files(['Setup.hs', 'Stuff.hs', 'Sig.hsig', 'pkg.cabal', 'src']), + run_command, + ['$MAKE -s --no-print-directory T15594 ' + cleanup]) diff --git a/testsuite/tests/backpack/cabal/T15594/pkg.cabal b/testsuite/tests/backpack/cabal/T15594/pkg.cabal new file mode 100644 index 0000000..cf6fdda --- /dev/null +++ b/testsuite/tests/backpack/cabal/T15594/pkg.cabal @@ -0,0 +1,19 @@ +cabal-version: 2.0 +name: backpack-trans +version: 0.1.0.0 +license: BSD3 +author: Alex Biehl +maintainer: alex.biehl at target.com +build-type: Simple + +library indef + signatures: Sig + exposed-modules: Stuff + build-depends: base + default-language: Haskell2010 + +library + exposed-modules: Lib + build-depends: base, indef + default-language: Haskell2010 + hs-source-dirs: src diff --git a/testsuite/tests/backpack/cabal/T15594/src/Lib.hs b/testsuite/tests/backpack/cabal/T15594/src/Lib.hs new file mode 100644 index 0000000..73cc27c --- /dev/null +++ b/testsuite/tests/backpack/cabal/T15594/src/Lib.hs @@ -0,0 +1,7 @@ +module Lib where + +import Stuff + +doSomeStuff :: String +doSomeStuff = + test From git at git.haskell.org Mon Nov 12 04:17:39 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 12 Nov 2018 04:17:39 +0000 (UTC) Subject: [commit: ghc] master: Remove StgBinderInfo and related computation in CoreToStg (d30352a) Message-ID: <20181112041739.3485E3AC03@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d30352add1da67dd0346613853cd423c7becbaeb/ghc >--------------------------------------------------------------- commit d30352add1da67dd0346613853cd423c7becbaeb Author: Ömer Sinan Ağacan Date: Mon Nov 12 06:50:54 2018 +0300 Remove StgBinderInfo and related computation in CoreToStg - The StgBinderInfo type was never used in the code gen, so the type, related computation in CoreToStg, and some comments about it are removed. See #15770 for more details. - Simplified CoreToStg after removing the StgBinderInfo computation: removed StgBinderInfo arguments and mfix stuff. The StgBinderInfo values were not used in the code gen, but I still run nofib just to make sure: 0.0% change in allocations and binary sizes. Test Plan: Validated locally Reviewers: simonpj, simonmar, bgamari, sgraf Reviewed By: sgraf Subscribers: AndreasK, sgraf, rwbarton, carter Differential Revision: https://phabricator.haskell.org/D5232 >--------------------------------------------------------------- d30352add1da67dd0346613853cd423c7becbaeb compiler/codeGen/StgCmm.hs | 4 +- compiler/codeGen/StgCmmBind.hs | 15 ++-- compiler/codeGen/StgCmmClosure.hs | 86 ----------------------- compiler/codeGen/StgCmmExpr.hs | 2 +- compiler/simplStg/StgCse.hs | 8 +-- compiler/simplStg/StgStats.hs | 2 +- compiler/simplStg/UnariseStg.hs | 4 +- compiler/stgSyn/CoreToStg.hs | 140 ++++++++++---------------------------- compiler/stgSyn/StgLint.hs | 4 +- compiler/stgSyn/StgSyn.hs | 44 ++---------- 10 files changed, 61 insertions(+), 248 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 d30352add1da67dd0346613853cd423c7becbaeb From git at git.haskell.org Mon Nov 12 08:55:05 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 12 Nov 2018 08:55:05 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Combine kcImplicitTKBndrs and tcImplicitTKBndrs (9ed634c) Message-ID: <20181112085505.B608B3AC04@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/9ed634ce6e1c5996217b7c8d81e638e1b9a6e231/ghc >--------------------------------------------------------------- commit 9ed634ce6e1c5996217b7c8d81e638e1b9a6e231 Author: Simon Peyton Jones Date: Mon Nov 12 08:30:33 2018 +0000 Combine kcImplicitTKBndrs and tcImplicitTKBndrs Based on a conversation with Richard on Friday, this patch * Abolishes the distinction between kcImplicitTKBndrs and tcImplicitTKBndrs; now it is bindImplicitTKBndrs * Same for kc/tcExplicitTKBndrs * tcImplicitTKBndrs no longer does a solveLocalEqualities and sort; the caller does that Much nicer. Not quite working yet though >--------------------------------------------------------------- 9ed634ce6e1c5996217b7c8d81e638e1b9a6e231 compiler/typecheck/TcBackpack.hs | 2 +- compiler/typecheck/TcDerivInfer.hs | 2 +- compiler/typecheck/TcHsType.hs | 238 +++++++++------------ compiler/typecheck/TcInstDcls.hs | 2 +- compiler/typecheck/TcRnMonad.hs | 4 +- compiler/typecheck/TcRules.hs | 34 ++- compiler/typecheck/TcSMonad.hs | 4 +- compiler/typecheck/TcSigs.hs | 46 ++-- compiler/typecheck/TcSimplify.hs | 18 +- compiler/typecheck/TcSplice.hs | 4 +- compiler/typecheck/TcTyClsDecls.hs | 205 +++++++++++------- compiler/typecheck/TcUnify.hs | 33 +-- testsuite/tests/dependent/should_compile/T13910.hs | 10 +- .../tests/indexed-types/should_compile/T12369.hs | 10 + testsuite/tests/indexed-types/should_fail/T7938.hs | 6 +- 15 files changed, 331 insertions(+), 287 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 9ed634ce6e1c5996217b7c8d81e638e1b9a6e231 From git at git.haskell.org Mon Nov 12 12:09:03 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 12 Nov 2018 12:09:03 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Get rid of kcLHsQTyVarBndrs (38d34b8) Message-ID: <20181112120903.DDF9F3AC04@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/38d34b806b2a14dd3823fb1e5dd52e379b0f7e2b/ghc >--------------------------------------------------------------- commit 38d34b806b2a14dd3823fb1e5dd52e379b0f7e2b Author: Simon Peyton Jones Date: Mon Nov 12 12:08:33 2018 +0000 Get rid of kcLHsQTyVarBndrs >--------------------------------------------------------------- 38d34b806b2a14dd3823fb1e5dd52e379b0f7e2b compiler/typecheck/TcHsType.hs | 289 +++++++++++++++++++-------------------- compiler/typecheck/TcMType.hs | 2 +- compiler/typecheck/TcValidity.hs | 21 --- 3 files changed, 138 insertions(+), 174 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 38d34b806b2a14dd3823fb1e5dd52e379b0f7e2b From git at git.haskell.org Mon Nov 12 13:44:25 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 12 Nov 2018 13:44:25 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Start to eliminate tcFamTyPats (772cae6) Message-ID: <20181112134425.0E43B3AC04@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/772cae68b2668c5790ff173ab0151c4aeca5c55e/ghc >--------------------------------------------------------------- commit 772cae68b2668c5790ff173ab0151c4aeca5c55e Author: Simon Peyton Jones Date: Mon Nov 12 13:41:33 2018 +0000 Start to eliminate tcFamTyPats >--------------------------------------------------------------- 772cae68b2668c5790ff173ab0151c4aeca5c55e compiler/typecheck/TcHsType.hs | 1 + compiler/typecheck/TcTyClsDecls.hs | 20 ++++++++------------ 2 files changed, 9 insertions(+), 12 deletions(-) diff --git a/compiler/typecheck/TcHsType.hs b/compiler/typecheck/TcHsType.hs index 7f637b7..fe8c1a0 100644 --- a/compiler/typecheck/TcHsType.hs +++ b/compiler/typecheck/TcHsType.hs @@ -21,6 +21,7 @@ module TcHsType ( UserTypeCtxt(..), bindImplicitTKBndrs_Skol, bindImplicitTKBndrs_Q_Skol, bindExplicitTKBndrs_Skol, bindExplicitTKBndrs_Q_Skol, + ContextKind(..), -- Type checking type and class decls kcLookupTcTyCon, kcTyClTyVars, tcTyClTyVars, diff --git a/compiler/typecheck/TcTyClsDecls.hs b/compiler/typecheck/TcTyClsDecls.hs index 5b5d858..b9227de 100644 --- a/compiler/typecheck/TcTyClsDecls.hs +++ b/compiler/typecheck/TcTyClsDecls.hs @@ -1760,6 +1760,7 @@ tcTyFamInstEqn :: TcTyCon -> Maybe ClsInstInfo -> LTyFamInstEqn GhcRn -- (typechecked here) have TyFamInstEqns +{- tcTyFamInstEqn fam_tc mb_clsinfo (L loc (HsIB { hsib_ext = imp_vars , hsib_body = FamEqn { feqn_tycon = L _ eqn_tc_name @@ -1780,8 +1781,8 @@ tcTyFamInstEqn fam_tc mb_clsinfo ; return (mkCoAxBranch tvs' [] pats' rhs_ty' (map (const Nominal) tvs') loc) } +-} -{- tcTyFamInstEqn fam_tc mb_clsinfo eqn@(L loc (HsIB { hsib_ext = imp_vars , hsib_body = FamEqn { feqn_tycon = L _ eqn_tc_name @@ -1790,12 +1791,12 @@ tcTyFamInstEqn fam_tc mb_clsinfo , feqn_rhs = hs_ty }})) = ASSERT( getName fam_tc == eqn_tc_name ) setSrcSpan loc $ - do { traceTc "tcTyFamInstEqn {" (ppr eqn) - ; (imp_tvs, (exp_tvs, ((pats, rhs_ty)))) + do { traceTc "tcTyFamInstEqn {" (ppr eqn_tc_name <+> ppr hs_pats) + ; (_imp_tvs, (_exp_tvs, ((pats, rhs_ty)))) <- pushTcLevelM_ $ solveEqualities $ bindImplicitTKBndrs_Q_Skol imp_vars $ - bindExplicitTKBndrs_Q_Skol (mb_expl_bndrs `orElse` []) $ + bindExplicitTKBndrs_Q_Skol AnyKind (mb_expl_bndrs `orElse` []) $ do { let fam_name = tyConName fam_tc lhs_fun = L loc (HsTyVar noExt NotPromoted (L loc fam_name)) @@ -1808,21 +1809,16 @@ tcTyFamInstEqn fam_tc mb_clsinfo ; rhs_ty <- tcCheckLHsType hs_ty res_kind ; return (pats, rhs_ty) } - ; imp_tvs <- zonkAndScopedSort imp_tvs - ; let spec_req_tkvs = imp_tvs ++ exp_tvs - ; dvs <- candidateQTyVarsOfKinds $ - typeKind rhs_ty : map tyVarKind (spec_req_tkvs) - ; let final_dvs = dvs `delCandidates` spec_req_tkvs - ; inferred_kvs <- quantifyTyVars emptyVarSet final_dvs + ; dvs <- candidateQTyVarsOfTypes (rhs_ty : pats) + ; qtkvs <- quantifyTyVars emptyVarSet dvs - ; (ze, tvs') <- zonkTyBndrs (inferred_kvs ++ spec_req_tkvs) + ; (ze, tvs') <- zonkTyBndrs qtkvs ; pats' <- zonkTcTypesToTypesX ze pats ; rhs_ty' <- zonkTcTypeToTypeX ze rhs_ty ; traceTc "tcTyFamInstEqn }" (ppr fam_tc <+> pprTyVars tvs') ; return (mkCoAxBranch tvs' [] pats' rhs_ty' (map (const Nominal) tvs') loc) } --} tcTyFamInstEqn _ _ (L _ (XHsImplicitBndrs _)) = panic "tcTyFamInstEqn" From git at git.haskell.org Mon Nov 12 16:57:48 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 12 Nov 2018 16:57:48 +0000 (UTC) Subject: [commit: ghc] master: compareByPreference: handle the integer-gmp vs -simple case (86ee74d) Message-ID: <20181112165748.55E703AC04@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/86ee74dc999db6030874ddaf5d10adec23108c02/ghc >--------------------------------------------------------------- commit 86ee74dc999db6030874ddaf5d10adec23108c02 Author: Alp Mestanogullari Date: Mon Nov 12 15:38:46 2018 +0100 compareByPreference: handle the integer-gmp vs -simple case Currently, it assumes the package names are identical and this breaks in the case where integer-gmp is in one package db and integer-simple in another. This became a problem with the commit: fc2ff6dd7496a33bf68165b28f37f40b7d647418. Instead of following the precedence information, leading to the right choice, the current code would compare the integer-gmp and integer-simple versions and pick integer-gmp because it happened to have a greater version, despite having a lower precedence. See https://github.com/snowleopard/hadrian/issues/702 for a comprehensive report about the problem. This effectively un-breaks integer-simple builds with hadrian. Test Plan: hadrian/build.sh --integer-simple Reviewers: snowleopard, bgamari Reviewed By: bgamari Subscribers: snowleopard, rwbarton, carter Differential Revision: https://phabricator.haskell.org/D5266 >--------------------------------------------------------------- 86ee74dc999db6030874ddaf5d10adec23108c02 compiler/main/Packages.hs | 25 ++++++++++++++++++++++--- 1 file changed, 22 insertions(+), 3 deletions(-) diff --git a/compiler/main/Packages.hs b/compiler/main/Packages.hs index fadcd31..78d5961 100644 --- a/compiler/main/Packages.hs +++ b/compiler/main/Packages.hs @@ -891,15 +891,28 @@ sortByPreference prec_map = sortBy (flip (compareByPreference prec_map)) -- -- Pursuant to #12518, we could change this policy to, for example, remove -- the version preference, meaning that we would always prefer the packages --- in alter package database. +-- in later package database. -- +-- Instead, we use that preference based policy only when one of the packages +-- is integer-gmp and the other is integer-simple. +-- This currently only happens when we're looking up which concrete +-- package to use in place of @integer-wired-in@ and that two different +-- package databases supply a different integer library. For more about +-- the fake @integer-wired-in@ package, see Note [The integer library] +-- in the @PrelNames@ module. compareByPreference :: PackagePrecedenceIndex -> PackageConfig -> PackageConfig -> Ordering -compareByPreference prec_map pkg pkg' = - case comparing packageVersion pkg pkg' of +compareByPreference prec_map pkg pkg' + | Just prec <- Map.lookup (unitId pkg) prec_map + , Just prec' <- Map.lookup (unitId pkg') prec_map + , differentIntegerPkgs pkg pkg' + = compare prec prec' + + | otherwise + = case comparing packageVersion pkg pkg' of GT -> GT EQ | Just prec <- Map.lookup (unitId pkg) prec_map , Just prec' <- Map.lookup (unitId pkg') prec_map @@ -910,6 +923,12 @@ compareByPreference prec_map pkg pkg' = -> EQ LT -> LT + where isIntegerPkg p = packageNameString p `elem` + ["integer-simple", "integer-gmp"] + differentIntegerPkgs p p' = + isIntegerPkg p && isIntegerPkg p' && + (packageName p /= packageName p') + comparing :: Ord a => (t -> a) -> t -> t -> Ordering comparing f a b = f a `compare` f b From git at git.haskell.org Mon Nov 12 17:44:15 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 12 Nov 2018 17:44:15 +0000 (UTC) Subject: [commit: ghc] wip/T15809: More progress on tcFamTyPats (033030e) Message-ID: <20181112174415.3BB563AC04@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/033030ef5be04c9f1f58894eb247ac8e621b6389/ghc >--------------------------------------------------------------- commit 033030ef5be04c9f1f58894eb247ac8e621b6389 Author: Simon Peyton Jones Date: Mon Nov 12 17:21:55 2018 +0000 More progress on tcFamTyPats This fixes Trac #15740 >--------------------------------------------------------------- 033030ef5be04c9f1f58894eb247ac8e621b6389 compiler/typecheck/TcHsType.hs | 26 ++++++++++------- compiler/typecheck/TcMType.hs | 4 +-- compiler/typecheck/TcTyClsDecls.hs | 51 +++++++++++++++++++++++++++------ compiler/typecheck/TcValidity.hs | 23 ++++++++------- testsuite/tests/polykinds/T13985.stderr | 10 ++----- testsuite/tests/polykinds/T15740.hs | 15 ++++++++++ testsuite/tests/polykinds/T15740.stderr | 6 ++++ testsuite/tests/polykinds/T15740a.hs | 12 ++++++++ testsuite/tests/polykinds/all.T | 2 ++ 9 files changed, 109 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 033030ef5be04c9f1f58894eb247ac8e621b6389 From git at git.haskell.org Mon Nov 12 17:44:18 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 12 Nov 2018 17:44:18 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Wibbles (5233e4f) Message-ID: <20181112174418.335633AC04@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/5233e4f77df6f2fe6426afdbb471191ac13f7070/ghc >--------------------------------------------------------------- commit 5233e4f77df6f2fe6426afdbb471191ac13f7070 Author: Simon Peyton Jones Date: Mon Nov 12 17:43:48 2018 +0000 Wibbles >--------------------------------------------------------------- 5233e4f77df6f2fe6426afdbb471191ac13f7070 testsuite/tests/indexed-types/should_fail/T7536.stderr | 8 ++++---- testsuite/tests/indexed-types/should_fail/T7938.hs | 6 ++---- testsuite/tests/indexed-types/should_fail/T7938.stderr | 2 +- 3 files changed, 7 insertions(+), 9 deletions(-) diff --git a/testsuite/tests/indexed-types/should_fail/T7536.stderr b/testsuite/tests/indexed-types/should_fail/T7536.stderr index 9e7ed30..34a393e 100644 --- a/testsuite/tests/indexed-types/should_fail/T7536.stderr +++ b/testsuite/tests/indexed-types/should_fail/T7536.stderr @@ -1,5 +1,5 @@ -T7536.hs:8:15: - Family instance purports to bind type variable ‘a’ - but the real LHS (expanding synonyms) is: TF Int = ... - In the type instance declaration for ‘TF’ +T7536.hs:8:15: error: + • LHS of family instance fails to bind type variable ‘a’ + The real LHS (expanding synonyms) is: TF Int + • In the type instance declaration for ‘TF’ diff --git a/testsuite/tests/indexed-types/should_fail/T7938.hs b/testsuite/tests/indexed-types/should_fail/T7938.hs index f1e8266..246015d 100644 --- a/testsuite/tests/indexed-types/should_fail/T7938.hs +++ b/testsuite/tests/indexed-types/should_fail/T7938.hs @@ -8,7 +8,5 @@ data KProxy (a :: *) = KP class Foo (a :: k1) (b :: k2) where type Bar a --- instance Foo (a :: k1) (b :: k2) where --- type Bar a = (KP :: KProxy k2) - --- \ No newline at end of file +instance Foo (a :: k1) (b :: k2) where + type Bar a = (KP :: KProxy k2) diff --git a/testsuite/tests/indexed-types/should_fail/T7938.stderr b/testsuite/tests/indexed-types/should_fail/T7938.stderr index 890be7b..5751c4e 100644 --- a/testsuite/tests/indexed-types/should_fail/T7938.stderr +++ b/testsuite/tests/indexed-types/should_fail/T7938.stderr @@ -1,6 +1,6 @@ T7938.hs:12:17: error: - • Expected a type, but ‘KP :: KProxy k2’ has kind ‘KProxy k4’ + • Expected a type, but ‘KP :: KProxy k2’ has kind ‘KProxy k2’ • In the type ‘(KP :: KProxy k2)’ In the type instance declaration for ‘Bar’ In the instance declaration for ‘Foo (a :: k1) (b :: k2)’ From git at git.haskell.org Mon Nov 12 18:32:01 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 12 Nov 2018 18:32:01 +0000 (UTC) Subject: [commit: ghc] branch 'wip/az-namemap' created Message-ID: <20181112183201.9F0103AC04@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/az-namemap Referencing: 2745981fb8a558cd486b674e4b15db8528f0cc78 From git at git.haskell.org Mon Nov 12 18:32:04 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 12 Nov 2018 18:32:04 +0000 (UTC) Subject: [commit: ghc] wip/az-namemap: Introduce map from RdrName to Name for GHC API (2745981) Message-ID: <20181112183204.9FEAA3AC04@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/az-namemap Link : http://ghc.haskell.org/trac/ghc/changeset/2745981fb8a558cd486b674e4b15db8528f0cc78/ghc >--------------------------------------------------------------- commit 2745981fb8a558cd486b674e4b15db8528f0cc78 Author: Alan Zimmerman Date: Mon Nov 12 20:26:40 2018 +0200 Introduce map from RdrName to Name for GHC API Tools need to work with the ParsedSource as a accurate representation of the compiled source, but sometimes need access to the actual Names used from the renaming phase. Introduce a function that initialises a NameMap from a TypechedModule, for use by GHC API consumers. >--------------------------------------------------------------- 2745981fb8a558cd486b674e4b15db8528f0cc78 compiler/main/GHC.hs | 133 +++++++++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 133 insertions(+) diff --git a/compiler/main/GHC.hs b/compiler/main/GHC.hs index cf9c74f..9d9cf17 100644 --- a/compiler/main/GHC.hs +++ b/compiler/main/GHC.hs @@ -1,5 +1,6 @@ {-# LANGUAGE CPP, NondecreasingIndentation, ScopedTypeVariables #-} {-# LANGUAGE TupleSections, NamedFieldPuns #-} +{-# LANGUAGE RankNTypes #-} -- ----------------------------------------------------------------------------- -- @@ -125,6 +126,7 @@ module GHC ( -- ** Looking up a Name parseName, lookupName, + initRdrNameMap, NameMap, -- ** Compiling expressions HValue, parseExpr, compileParsedExpr, @@ -306,6 +308,7 @@ import TcRnTypes import Packages import NameSet import RdrName +import Var import HsSyn import Type hiding( typeKind ) import TcType hiding( typeKind ) @@ -352,7 +355,9 @@ import TcRnDriver import Inst import FamInst import FileCleanup +import Unique ( mkUnique ) +import Data.Data ( Data, gmapQ, cast ) import Data.Foldable import qualified Data.Map.Strict as Map import Data.Set (Set) @@ -1531,6 +1536,134 @@ lookupName :: GhcMonad m => Name -> m (Maybe TyThing) lookupName name = withSession $ \hsc_env -> liftIO $ hscTcRcLookupName hsc_env name +-- ----------------------------------------------------------------------------- + +-- | Map of 'SrcSpan's from 'Located' 'RdrName's in the 'ParsedSource' +-- to the corresponding 'Name' from renaming. +type NameMap = Map.Map SrcSpan Name + +-- | Tools prefer to work with the 'ParsedSource' because it more +-- closely reflects the actual source code, but must be able to work +-- with the renamed representation of the names involved. This +-- function constructs a map from every 'Located' 'RdrName' in the +-- 'ParsedSource' to its corresponding name in the 'RenamedSource' and +-- 'TypecheckedSource'. +initRdrNameMap :: TypecheckedModule -> NameMap +initRdrNameMap tm = r + where + parsed = pm_parsed_source $ tm_parsed_module tm + renamed = tm_renamed_source tm + typechecked = tm_typechecked_source tm + + checkRdr :: Located RdrName -> Maybe [(SrcSpan,RdrName)] + checkRdr (L l n@(Unqual _)) = Just [(l,n)] + checkRdr (L l n@(Qual _ _)) = Just [(l,n)] + checkRdr (L _ _)= Nothing + + checkName :: Located Name -> Maybe [Located Name] + checkName ln = Just [ln] + + rdrNames = fromMaybe (panic "initRdrNameMap") + $ everything mappend (nameSybQuery checkRdr ) parsed + names1 = fromMaybe (panic "initRdrNameMap") + $ everything mappend (nameSybQuery checkName) renamed + names2 = names1 ++ everything (++) ([] `mkQ` fieldOcc + `extQ` hsRecFieldN) renamed + names = names2 ++ everything (++) ([] `mkQ` hsRecFieldT) typechecked + + fieldOcc :: FieldOcc GhcRn -> [Located Name] + fieldOcc (FieldOcc n (L l _)) = [(L l n)] + fieldOcc XFieldOcc {} = [] + + hsRecFieldN :: LHsExpr GhcRn -> [Located Name] + hsRecFieldN (L _ (HsRecFld _ (Unambiguous n (L l _) ))) = [L l n] + hsRecFieldN _ = [] + + hsRecFieldT :: LHsExpr GhcTc -> [Located Name] + hsRecFieldT (L _ (HsRecFld _ (Ambiguous n (L l _)) )) + = [L l (Var.varName n)] + hsRecFieldT _ = [] + + nameMap = Map.fromList $ map (\(L l n) -> (l,n)) names + + -- If the name does not exist (e.g. a TH Splice that has been + -- expanded, make a new one) + -- No attempt is made to make sure that equivalent ones have + -- equivalent names. + lookupName l n i = case Map.lookup l nameMap of + Just v -> v + Nothing -> + case n of + Unqual u -> mkNewGhcNamePure 'h' i Nothing (occNameString u) + Qual q u -> mkNewGhcNamePure 'h' i + (Just (Module (stringToUnitId "") q)) (occNameString u) + _ -> panic "initRdrNameMap" + + r = Map.fromList $ map (\((l,n),i) -> (l,lookupName l n i)) + $ zip rdrNames [1..] + + nameSybQuery :: (Typeable a, Typeable t) + => (Located a -> Maybe r) -> t -> Maybe r + nameSybQuery checker = q + where + q = Nothing `mkQ` worker + + worker (pnt :: (Located a)) + = checker pnt + + mkNewGhcNamePure :: Char -> Int -> Maybe Module -> String -> Name + mkNewGhcNamePure c i maybeMod name = + let un = mkUnique c i -- H for HaRe :) + n = case maybeMod of + Nothing -> mkInternalName un (mkVarOcc name) noSrcSpan + Just modu -> mkExternalName un modu (mkVarOcc name) noSrcSpan + in n + + +-- Copied from SYB + + +-- | Generic queries of type \"r\", +-- i.e., take any \"a\" and return an \"r\" +-- +type GenericQ r = forall a. Data a => a -> r + + +-- | Make a generic query; +-- start from a type-specific case; +-- return a constant otherwise +-- +mkQ :: ( Typeable a + , Typeable b + ) + => r + -> (b -> r) + -> a + -> r +(r `mkQ` br) a = case cast a of + Just b -> br b + Nothing -> r + +-- | Extend a generic query by a type-specific case +extQ :: ( Typeable a + , Typeable b + ) + => (a -> q) + -> (b -> q) + -> a + -> q +extQ f g a = maybe (f a) g (cast a) + + + +-- | Summarise all nodes in top-down, left-to-right order +everything :: (r -> r -> r) -> GenericQ r -> GenericQ r + +-- Apply f to x to summarise top-level node; +-- use gmapQ to recurse into immediate subterms; +-- use ordinary foldl to reduce list of intermediate results + +everything k f x = foldl k (f x) (gmapQ (everything k f) x) -- ----------------------------------------------------------------------------- -- Pure API From git at git.haskell.org Mon Nov 12 19:13:05 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 12 Nov 2018 19:13:05 +0000 (UTC) Subject: [commit: ghc] master: Correct link to GHC API in docs index. (89bf7d5) Message-ID: <20181112191305.850DC3AC04@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/89bf7d546a209bb3decc5b677fce18dd5cf79478/ghc >--------------------------------------------------------------- commit 89bf7d546a209bb3decc5b677fce18dd5cf79478 Author: Shao Cheng Date: Mon Nov 12 18:45:06 2018 +0800 Correct link to GHC API in docs index. >--------------------------------------------------------------- 89bf7d546a209bb3decc5b677fce18dd5cf79478 docs/index.html.in | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/docs/index.html.in b/docs/index.html.in index 4c1be82..4c103fe 100644 --- a/docs/index.html.in +++ b/docs/index.html.in @@ -39,7 +39,7 @@
  • - GHC API + GHC API

    Documentation for the GHC API. From git at git.haskell.org Mon Nov 12 19:13:08 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 12 Nov 2018 19:13:08 +0000 (UTC) Subject: [commit: ghc] master: circleci: Disable pushing of test metrics if not validating upstream (0f2ac24) Message-ID: <20181112191308.82A0B3AC04@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0f2ac24c26fb951cc81100085c7773906a241523/ghc >--------------------------------------------------------------- commit 0f2ac24c26fb951cc81100085c7773906a241523 Author: Ben Gamari Date: Mon Nov 12 14:11:05 2018 -0500 circleci: Disable pushing of test metrics if not validating upstream >--------------------------------------------------------------- 0f2ac24c26fb951cc81100085c7773906a241523 .circleci/push-test-metrics.sh | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/.circleci/push-test-metrics.sh b/.circleci/push-test-metrics.sh index 4ea6958..d8222b7 100755 --- a/.circleci/push-test-metrics.sh +++ b/.circleci/push-test-metrics.sh @@ -7,6 +7,10 @@ fail() { exit 1 } +if [ "$CIRCLE_REPOSITORY_URL" != "git at github.com:ghc/ghc.git" ]; then + exit 0 +fi + GHC_ORIGIN=git at git.haskell.org:ghc # Add git.haskell.org as a known host. From git at git.haskell.org Tue Nov 13 14:48:00 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Nov 2018 14:48:00 +0000 (UTC) Subject: [commit: ghc] master: Make `UniqDSet` a newtype (5b98a38) Message-ID: <20181113144800.89AD33AC05@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5b98a38a32f2bc8491dc897631be8892919e2143/ghc >--------------------------------------------------------------- commit 5b98a38a32f2bc8491dc897631be8892919e2143 Author: Sebastian Graf Date: Tue Nov 13 14:54:54 2018 +0100 Make `UniqDSet` a newtype Summary: This brings the situation of `UniqDSet` in line with `UniqSet`. @dfeuer said in D3146#92820 that he would do this, but probably never got around to it. Validated locally. Reviewers: AndreasK, mpickering, bgamari, dfeuer, simonpj Reviewed By: simonpj Subscribers: simonpj, rwbarton, carter, dfeuer GHC Trac Issues: #15879, #13114 Differential Revision: https://phabricator.haskell.org/D5313 >--------------------------------------------------------------- 5b98a38a32f2bc8491dc897631be8892919e2143 compiler/basicTypes/Module.hs | 2 +- compiler/basicTypes/VarSet.hs | 8 ++--- compiler/deSugar/DsArrows.hs | 23 ++++++------ compiler/simplCore/SetLevels.hs | 3 +- compiler/utils/UniqDFM.hs | 8 ++++- compiler/utils/UniqDSet.hs | 79 +++++++++++++++++++++++++++-------------- compiler/utils/UniqFM.hs | 2 +- 7 files changed, 79 insertions(+), 46 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 5b98a38a32f2bc8491dc897631be8892919e2143 From git at git.haskell.org Tue Nov 13 15:37:48 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 13 Nov 2018 15:37:48 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Much more progress on tcFamTyPats (be48394) Message-ID: <20181113153748.351103AC05@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/be48394f903ebce1469e54885f6416508001eab1/ghc >--------------------------------------------------------------- commit be48394f903ebce1469e54885f6416508001eab1 Author: Simon Peyton Jones Date: Tue Nov 13 15:36:28 2018 +0000 Much more progress on tcFamTyPats Main thing left to do: data family instances A handful of validate failures Reporting unused binders correctly polykinds/T13985 indexed-types/should_fail/ExplicitForAllFams4a indexed-types/should_fail/ExplicitForAllFams4b extra error (ok) polykinds/T8616 polykinds/T14846 >--------------------------------------------------------------- be48394f903ebce1469e54885f6416508001eab1 compiler/prelude/TysPrim.hs | 19 +- compiler/typecheck/TcHsType.hs | 4 +- compiler/typecheck/TcInstDcls.hs | 14 +- compiler/typecheck/TcTyClsDecls.hs | 257 +++++++++------------ compiler/types/Type.hs | 32 ++- testsuite/tests/ghci/scripts/T6018ghcifail.stderr | 2 +- .../tests/th/TH_reifyExplicitForAllFams.stderr | 6 +- .../typecheck/should_fail/LevPolyBounded.stderr | 5 + testsuite/tests/typecheck/should_fail/T14607.hs | 2 +- .../tests/typecheck/should_fail/T14607.stderr | 13 +- .../tests/typecheck/should_fail/T6018fail.stderr | 2 +- testsuite/tests/typecheck/should_fail/all.T | 2 +- 12 files changed, 166 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 be48394f903ebce1469e54885f6416508001eab1 From git at git.haskell.org Wed Nov 14 11:38:43 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 14 Nov 2018 11:38:43 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Data family instances working, I think (738c79b) Message-ID: <20181114113843.E9B083A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/738c79b2fc941d0bbfcd23f2e4aaaf25cedc855a/ghc >--------------------------------------------------------------- commit 738c79b2fc941d0bbfcd23f2e4aaaf25cedc855a Author: Simon Peyton Jones Date: Wed Nov 14 11:36:22 2018 +0000 Data family instances working, I think >--------------------------------------------------------------- 738c79b2fc941d0bbfcd23f2e4aaaf25cedc855a compiler/typecheck/TcInstDcls.hs | 154 +++++++++++++++++++++++++++++++++++++ compiler/typecheck/TcTyClsDecls.hs | 68 ++++++++-------- 2 files changed, 191 insertions(+), 31 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 738c79b2fc941d0bbfcd23f2e4aaaf25cedc855a From git at git.haskell.org Wed Nov 14 14:46:00 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 14 Nov 2018 14:46:00 +0000 (UTC) Subject: [commit: ghc] master: hadrian: build ghc-iserv-dyn (89fa34e) Message-ID: <20181114144600.B8D683A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/89fa34ecd326de879145e6d854306eb17722bf6c/ghc >--------------------------------------------------------------- commit 89fa34ecd326de879145e6d854306eb17722bf6c Author: David Eichmann Date: Wed Nov 14 15:43:57 2018 +0100 hadrian: build ghc-iserv-dyn ... in addition to ghc-iserv and ghc-iserv-prof, as it is required to get 10+ tests to pass Reviewers: bgamari, alpmestan Reviewed By: alpmestan Subscribers: alpmestan, rwbarton, carter Differential Revision: https://phabricator.haskell.org/D5327 >--------------------------------------------------------------- 89fa34ecd326de879145e6d854306eb17722bf6c hadrian/src/Packages.hs | 12 ++++++++---- hadrian/src/Rules/Program.hs | 23 +++++++++++++---------- hadrian/src/Rules/Test.hs | 2 +- 3 files changed, 22 insertions(+), 15 deletions(-) diff --git a/hadrian/src/Packages.hs b/hadrian/src/Packages.hs index 4ce1a2c..24f5690 100644 --- a/hadrian/src/Packages.hs +++ b/hadrian/src/Packages.hs @@ -139,10 +139,14 @@ programName Context {..} = do return $ prefix ++ case package of p | p == ghc -> "ghc" | p == hpcBin -> "hpc" - | p == iserv -> - if Profiling `wayUnit` way - then "ghc-iserv-prof" - else "ghc-iserv" + | p == iserv -> "ghc-iserv" ++ concat [ + if wayUnit' `wayUnit` way + then suffix + else "" + | (wayUnit', suffix) <- [ + (Profiling, "-prof"), + (Dynamic, "-dyn") + ]] _ -> pkgName package -- | The 'FilePath' to a program executable in a given 'Context'. diff --git a/hadrian/src/Rules/Program.hs b/hadrian/src/Rules/Program.hs index 7128a75..aeed026 100644 --- a/hadrian/src/Rules/Program.hs +++ b/hadrian/src/Rules/Program.hs @@ -29,18 +29,21 @@ buildProgram rs = do let allPackages = sPackages ++ if stage == Stage1 then tPackages else [] nameToCtxList <- fmap concat . forM allPackages $ \pkg -> do - -- the iserv pkg results in two different programs at - -- the moment, ghc-iserv (built the vanilla way) - -- and ghc-iserv-prof (built the profiling way), and - -- the testsuite requires both to be present, so we + -- the iserv pkg results in three different programs at + -- the moment, ghc-iserv (built the vanilla way), + -- ghc-iserv-prof (built the profiling way), and + -- ghc-iserv-dyn (built the dynamic way). + -- The testsuite requires all to be present, so we -- make sure that we cover these -- "prof-build-under-other-name" cases. - -- iserv gets its two names from Packages.hs:programName - let ctxV = vanillaContext stage pkg - ctxProf = Context stage pkg profiling - nameV <- programName ctxV - nameProf <- programName ctxProf - return [ (nameV <.> exe, ctxV), (nameProf <.> exe, ctxProf) ] + -- iserv gets its names from Packages.hs:programName + let allCtxs = [ vanillaContext stage pkg + , Context stage pkg profiling + , Context stage pkg dynamic + ] + forM allCtxs $ \ctx -> do + name <- programName ctx + return (name <.> exe, ctx) case lookup (takeFileName bin) nameToCtxList of Nothing -> error $ "Unknown program " ++ show bin diff --git a/hadrian/src/Rules/Test.hs b/hadrian/src/Rules/Test.hs index 6a02ce6..de73390 100644 --- a/hadrian/src/Rules/Test.hs +++ b/hadrian/src/Rules/Test.hs @@ -106,7 +106,7 @@ timeoutProgBuilder = do needIservBins :: Action () needIservBins = need =<< traverse programPath - [ Context Stage1 iserv w | w <- [vanilla, profiling] ] + [ Context Stage1 iserv w | w <- [vanilla, profiling, dynamic] ] needTestBuilders :: Action () needTestBuilders = do From git at git.haskell.org Wed Nov 14 15:27:26 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 14 Nov 2018 15:27:26 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Print tycon arity in -ddump-types (74602f5) Message-ID: <20181114152726.D0EB73A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/74602f5cdcf832b35c5aedb09a11755c67957b95/ghc >--------------------------------------------------------------- commit 74602f5cdcf832b35c5aedb09a11755c67957b95 Author: Simon Peyton Jones Date: Wed Nov 14 14:57:08 2018 +0000 Print tycon arity in -ddump-types >--------------------------------------------------------------- 74602f5cdcf832b35c5aedb09a11755c67957b95 compiler/typecheck/TcRnDriver.hs | 2 +- testsuite/tests/dependent/should_compile/T15743.stderr | 2 +- testsuite/tests/dependent/should_compile/T15743e.stderr | 4 ++-- .../tests/indexed-types/should_compile/T15711.stderr | 4 ++-- .../tests/indexed-types/should_compile/T3017.stderr | 6 +++--- testsuite/tests/partial-sigs/should_compile/ADT.stderr | 2 +- .../should_compile/DataFamilyInstanceLHS.stderr | 4 ++-- .../tests/partial-sigs/should_compile/Meltdown.stderr | 2 +- .../NamedWildcardInDataFamilyInstanceLHS.stderr | 4 ++-- .../NamedWildcardInTypeFamilyInstanceLHS.stderr | 2 +- .../tests/partial-sigs/should_compile/SkipMany.stderr | 2 +- .../should_compile/TypeFamilyInstanceLHS.stderr | 2 +- testsuite/tests/polykinds/T15592.stderr | 2 +- testsuite/tests/polykinds/T15592b.stderr | 4 ++-- testsuite/tests/roles/should_compile/Roles1.stderr | 14 +++++++------- testsuite/tests/roles/should_compile/Roles14.stderr | 2 +- testsuite/tests/roles/should_compile/Roles2.stderr | 4 ++-- testsuite/tests/roles/should_compile/Roles3.stderr | 16 ++++++++-------- testsuite/tests/roles/should_compile/Roles4.stderr | 6 +++--- testsuite/tests/roles/should_compile/T8958.stderr | 6 +++--- testsuite/tests/th/TH_Roles2.stderr | 2 +- testsuite/tests/typecheck/should_compile/T12763.stderr | 2 +- testsuite/tests/typecheck/should_compile/tc231.stderr | 6 +++--- 23 files changed, 50 insertions(+), 50 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 74602f5cdcf832b35c5aedb09a11755c67957b95 From git at git.haskell.org Wed Nov 14 15:27:29 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 14 Nov 2018 15:27:29 +0000 (UTC) Subject: [commit: ghc] wip/T15809: More progress with data instances (0849475) Message-ID: <20181114152729.C93153A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/084947591fc538e67d8e40211685a5cb2ff6b575/ghc >--------------------------------------------------------------- commit 084947591fc538e67d8e40211685a5cb2ff6b575 Author: Simon Peyton Jones Date: Wed Nov 14 15:25:45 2018 +0000 More progress with data instances Slightly controversially, I adjusted T15725 to have data Sing :: k -> * rather than data Sing :: forall k. k -> * See a fc-call thread. We could revisit this if need be; it's not fundamental to the line of progress. >--------------------------------------------------------------- 084947591fc538e67d8e40211685a5cb2ff6b575 compiler/typecheck/TcDeriv.hs | 2 +- compiler/typecheck/TcInstDcls.hs | 1 - compiler/typecheck/TcTyClsDecls.hs | 17 +++++++++++------ testsuite/tests/dependent/should_compile/T15725.hs | 6 +++--- testsuite/tests/ghci/scripts/T10059.stdout | 6 +++--- testsuite/tests/ghci/scripts/ghci059.stdout | 2 +- 6 files changed, 19 insertions(+), 15 deletions(-) diff --git a/compiler/typecheck/TcDeriv.hs b/compiler/typecheck/TcDeriv.hs index bb9c76b..147191b 100644 --- a/compiler/typecheck/TcDeriv.hs +++ b/compiler/typecheck/TcDeriv.hs @@ -786,7 +786,7 @@ deriveTyData tvs tc tc_args mb_deriv_strat deriv_pred -- we want to drop type variables from T so that (C d (T a)) is well-kinded let (arg_kinds, _) = splitFunTys cls_arg_kind n_args_to_drop = length arg_kinds - n_args_to_keep = tyConArity tc - n_args_to_drop + n_args_to_keep = length tc_args - n_args_to_drop (tc_args_to_keep, args_to_drop) = splitAt n_args_to_keep tc_args inst_ty_kind = typeKind (mkTyConApp tc tc_args_to_keep) diff --git a/compiler/typecheck/TcInstDcls.hs b/compiler/typecheck/TcInstDcls.hs index 86ed84a..d1081a2 100644 --- a/compiler/typecheck/TcInstDcls.hs +++ b/compiler/typecheck/TcInstDcls.hs @@ -738,7 +738,6 @@ tcDataFamInstDecl mb_clsinfo -- Kind check type patterns ; let exp_bndrs = mb_bndrs `orElse` [] data_ctxt = DataKindCtxt (unLoc fam_name) - ; ; (_, (_, (pats, stupid_theta, res_kind))) <- pushTcLevelM_ $ diff --git a/compiler/typecheck/TcTyClsDecls.hs b/compiler/typecheck/TcTyClsDecls.hs index c8a182a..4de2238 100644 --- a/compiler/typecheck/TcTyClsDecls.hs +++ b/compiler/typecheck/TcTyClsDecls.hs @@ -1485,17 +1485,22 @@ tcFamDecl1 parent (FamilyDecl { fdInfo = fam_info, fdLName = tc_lname@(L _ tc_na { traceTc "data family:" (ppr tc_name) ; checkFamFlag tc_name - -- Check the kind signature, if any. - -- Data families might have a variable return kind. - -- See See Note [Arity of data families] in FamInstEnv. - ; (extra_binders, final_res_kind) <- tcDataKindSig binders res_kind + -- Check that the result kind is OK + -- We allow things like + -- data family T (a :: Type) :: forall k. k -> Type + -- We treat T as having arity 1, but result kind forall k. k -> Type + -- But we want to check that the result kind finishes in + -- Type or a kind-variable + -- For the latter, consider + -- data family D a :: forall k. Type -> k + ; let (_, final_res_kind) = splitPiTys res_kind ; checkTc (tcIsLiftedTypeKind final_res_kind || isJust (tcGetCastedTyVar_maybe final_res_kind)) (badKindSig False res_kind) ; tc_rep_name <- newTyConRepName tc_name - ; let tycon = mkFamilyTyCon tc_name (binders `chkAppend` extra_binders) - final_res_kind + ; let tycon = mkFamilyTyCon tc_name binders + res_kind (resultVariableName sig) (DataFamilyTyCon tc_rep_name) parent NotInjective diff --git a/testsuite/tests/dependent/should_compile/T15725.hs b/testsuite/tests/dependent/should_compile/T15725.hs index a5f259e..1e2e171 100644 --- a/testsuite/tests/dependent/should_compile/T15725.hs +++ b/testsuite/tests/dependent/should_compile/T15725.hs @@ -23,12 +23,12 @@ instance SC Identity ------------------------------------------------------------------------------- -data family Sing :: forall k. k -> Type -data instance Sing :: forall a. Identity a -> Type where +data family Sing :: k -> Type +data instance Sing :: Identity a -> Type where SIdentity :: Sing x -> Sing ('Identity x) newtype Par1 p = Par1 p -data instance Sing :: forall p. Par1 p -> Type where +data instance Sing :: Par1 p -> Type where SPar1 :: Sing x -> Sing ('Par1 x) type family Rep1 (f :: Type -> Type) :: Type -> Type diff --git a/testsuite/tests/ghci/scripts/T10059.stdout b/testsuite/tests/ghci/scripts/T10059.stdout index 92fbb45..955c95a 100644 --- a/testsuite/tests/ghci/scripts/T10059.stdout +++ b/testsuite/tests/ghci/scripts/T10059.stdout @@ -1,4 +1,4 @@ -class (a ~ b) => (~) (a :: k0) (b :: k0) -- Defined in ‘GHC.Types’ -(~) :: k0 -> k0 -> Constraint -class (a GHC.Prim.~# b) => (~) (a :: k0) (b :: k0) +class (a ~ b) => (~) (a :: k) (b :: k) -- Defined in ‘GHC.Types’ +(~) :: k -> k -> Constraint +class (a GHC.Prim.~# b) => (~) (a :: k) (b :: k) -- Defined in ‘GHC.Types’ diff --git a/testsuite/tests/ghci/scripts/ghci059.stdout b/testsuite/tests/ghci/scripts/ghci059.stdout index 9e9adb9..7e734f1 100644 --- a/testsuite/tests/ghci/scripts/ghci059.stdout +++ b/testsuite/tests/ghci/scripts/ghci059.stdout @@ -4,6 +4,6 @@ It is not a class. Please see section 9.14.4 of the user's guide for details. -} type role Coercible representational representational -class Coercible a b => Coercible (a :: k0) (b :: k0) +class Coercible a b => Coercible (a :: k) (b :: k) -- Defined in ‘GHC.Types’ coerce :: Coercible a b => a -> b -- Defined in ‘GHC.Prim’ From git at git.haskell.org Wed Nov 14 17:12:22 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 14 Nov 2018 17:12:22 +0000 (UTC) Subject: [commit: nofib] master: Adjust normal runtimes for nofib along with related changes (08cc9b6) Message-ID: <20181114171222.874EA3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/nofib On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/08cc9b6b2c7f7fdaaaf80361ab84a501f0a573c5/nofib >--------------------------------------------------------------- commit 08cc9b6b2c7f7fdaaaf80361ab84a501f0a573c5 Author: klebinger.andreas at gmx.at Date: Wed Nov 14 18:07:43 2018 +0100 Adjust normal runtimes for nofib along with related changes Runtime for nofib benchmarks was all over the place. This patch adjusts runtime for most benchmarks such that it falls into the 0.2-2s range. This means that: * A default run will take longer * Time spent will be better distributed among benchmarks. * More benchmarks have runtimes long enough to be used for runtime analysis. Some more changes were done which go hand in hand with changing runtimes. * Some benchmarks now create their input files during boot. * Moved input files for anna in their own directory. * Remove printing of output for some of the floating point heavy benchmarks. * Added a comment about desired runtimes to README. * Made grep actually benchmark something. * Throw cachgrind out of the default benchmarks. The nondeterministic behaviour has been an issue for a while and it doesn't seem like an essential benchmark. Test Plan: run nofib in modes slow/normal/fast Reviewers: O26 nofib, alpmestan Reviewed By: alpmestan Subscribers: sgraf, alpmestan Differential Revision: https://phabricator.haskell.org/D4989 >--------------------------------------------------------------- 08cc9b6b2c7f7fdaaaf80361ab84a501f0a573c5 .gitignore | 4 + README.md | 11 + gc/circsim/Makefile | 2 +- gc/circsim/{circsim.stdout => circsim.slowstdout} | 0 gc/circsim/circsim.stdout | 2 +- gc/constraints/Makefile | 2 +- .../{constraints.stdout => constraints.slowstdout} | 0 gc/constraints/constraints.stdout | 10 +- gc/gc_bench/Makefile | 5 +- gc/happy/TestInput.hs | 0 gc/hash/Makefile | 2 +- gc/lcss/Makefile | 4 +- gc/lcss/lcss.faststdout | 2 +- gc/lcss/lcss.slowstdout | 2 +- gc/lcss/lcss.stdout | 2 +- gc/mutstore1/Makefile | 4 +- gc/power/Makefile | 4 +- .../power.stdout => gc/power/power.faststdout | 0 gc/power/power.slowstdout | 8 +- gc/power/power.stdout | 8 +- imaginary/bernouilli/Makefile | 5 +- .../{bernouilli.stdout => bernouilli.faststdout} | 0 imaginary/bernouilli/bernouilli.stdout | 2 +- imaginary/digits-of-e1/Makefile | 4 +- imaginary/digits-of-e1/digits-of-e1.slowstdout | 2 +- imaginary/digits-of-e1/digits-of-e1.stdout | 2 +- imaginary/digits-of-e2/Makefile | 4 +- imaginary/digits-of-e2/digits-of-e2.slowstdout | 2 +- imaginary/digits-of-e2/digits-of-e2.stdout | 2 +- imaginary/exp3_8/Makefile | 2 +- .../exp3_8/{exp3_8.stdout => exp3_8.faststdout} | 0 imaginary/exp3_8/exp3_8.slowstdout | 1 - imaginary/exp3_8/exp3_8.stdout | 2 +- imaginary/gen_regexps/gen_regexps.faststdin | 1 + imaginary/gen_regexps/gen_regexps.faststdout | 1 + imaginary/gen_regexps/gen_regexps.slowstdin | 1 - imaginary/gen_regexps/gen_regexps.slowstdout | 1 - imaginary/gen_regexps/gen_regexps.stdin | 2 +- imaginary/gen_regexps/gen_regexps.stdout | 2 +- imaginary/integrate/Makefile | 6 +- .../{integrate.slowstdout => integrate.faststdout} | 0 imaginary/integrate/integrate.slowstdout | 2 +- imaginary/integrate/integrate.stdout | 2 +- imaginary/paraffins/Makefile | 4 +- .../{paraffins.stdout => paraffins.faststdout} | 0 imaginary/paraffins/paraffins.slowstdout | 4 - imaginary/paraffins/paraffins.stdout | 8 +- imaginary/primes/Makefile | 6 +- imaginary/primes/primes.slowstdout | 2 +- imaginary/primes/primes.stdout | 2 +- imaginary/queens/Makefile | 4 +- .../queens/{queens.stdout => queens.faststdout} | 0 imaginary/queens/queens.slowstdout | 1 - imaginary/queens/queens.stdout | 2 +- imaginary/rfib/Makefile | 6 +- .../rfib/{rfib.slowstdout => rfib.faststdout} | 0 imaginary/rfib/rfib.stdout | 2 +- imaginary/tak/Makefile | 2 +- imaginary/tak/tak.slowstdout | 1 - imaginary/wheel-sieve1/Makefile | 4 +- imaginary/wheel-sieve1/wheel-sieve1.slowstdout | 2 +- imaginary/wheel-sieve1/wheel-sieve1.stdout | 2 +- imaginary/wheel-sieve2/Makefile | 6 +- imaginary/wheel-sieve2/wheel-sieve2.slowstdout | 1 - imaginary/wheel-sieve2/wheel-sieve2.stdout | 2 +- imaginary/x2n1/Makefile | 4 +- imaginary/x2n1/{x2n1.stdout => x2n1.faststdout} | 0 imaginary/x2n1/x2n1.slowstdout | 1 - imaginary/x2n1/x2n1.stdout | 2 +- real/Makefile | 5 +- real/anna/Makefile | 2 - real/anna/{big.cor => anna.faststdin} | 0 real/anna/{anna.stdout => anna.faststdout} | 0 real/anna/anna.stdin | 1262 + real/anna/anna.stdout | 5015 +- real/anna/{ => cor_files}/ap_CaseAlts.cor | 0 real/anna/{ => cor_files}/ap_CaseArgs.cor | 0 real/anna/{ => cor_files}/ap_CaseOfCase.cor | 0 real/anna/{ => cor_files}/ap_CaseOfCase2.cor | 0 real/anna/{ => cor_files}/ap_CaseOfCase3.cor | 0 real/anna/{ => cor_files}/ap_FuncCall.cor | 0 real/anna/{ => cor_files}/ap_ListOfList.cor | 0 real/anna/{ => cor_files}/ap_SemiLazyAdd.cor | 0 real/anna/{ => cor_files}/ap_SemiLazyCase.cor | 0 real/anna/{ => cor_files}/ap_SimpleLazy.cor | 0 real/anna/{ => cor_files}/ap_SimpleStrict.cor | 0 real/anna/{ => cor_files}/ap_Unzip.cor | 0 real/anna/{ => cor_files}/ap_Zip.cor | 0 real/anna/{ => cor_files}/append.cor | 0 real/anna/{ => cor_files}/avlTree.cor | 0 real/anna/{ => cor_files}/big.cor | 0 real/anna/{ => cor_files}/bmark.cor | 0 real/anna/{ => cor_files}/bomb.cor | 0 real/anna/{ => cor_files}/bomb2.cor | 0 real/anna/{ => cor_files}/bug.cor | 0 real/anna/{ => cor_files}/bug_Anna1.cor | 0 real/anna/{ => cor_files}/bug_Anna2.cor | 0 real/anna/{ => cor_files}/bug_Anna3.cor | 0 real/anna/{ => cor_files}/bug_Anna4.cor | 0 real/anna/{ => cor_files}/bug_Anna5.cor | 0 real/anna/{ => cor_files}/bug_Anna6.cor | 0 real/anna/{ => cor_files}/bug_types1.cor | 0 real/anna/{ => cor_files}/bug_types2.cor | 0 real/anna/{ => cor_files}/bury.cor | 0 real/anna/{ => cor_files}/cfoldr.cor | 0 real/anna/{ => cor_files}/concat.cor | 0 real/anna/{ => cor_files}/concat22.cor | 0 real/anna/{ => cor_files}/concat24.cor | 0 real/anna/{ => cor_files}/concat44.cor | 0 real/anna/{ => cor_files}/coreExpr.cor | 0 real/anna/{ => cor_files}/coreExpr0.cor | 0 real/anna/{ => cor_files}/divide.cor | 0 real/anna/{ => cor_files}/dividetree.cor | 0 real/anna/{ => cor_files}/dot_3.cor | 0 real/anna/{ => cor_files}/dot_4.cor | 0 real/anna/{ => cor_files}/eta.cor | 0 real/anna/{ => cor_files}/filter.cor | 0 real/anna/{ => cor_files}/foldrFoldl.cor | 0 real/anna/{ => cor_files}/fourier.cor | 0 real/anna/{ => cor_files}/funcDomain.cor | 0 real/anna/{ => cor_files}/higherOrder.cor | 0 real/anna/{ => cor_files}/john.cor | 0 real/anna/{ => cor_files}/llfiasco.cor | 0 real/anna/{ => cor_files}/manyIterate.cor | 0 real/anna/{ => cor_files}/mutualRec.cor | 0 real/anna/{ => cor_files}/ol_num.cor | 0 real/anna/{ => cor_files}/pairid.cor | 0 real/anna/{ => cor_files}/parallelOr.cor | 0 real/anna/{ => cor_files}/poly_loseGain.cor | 0 real/anna/{ => cor_files}/poly_simple.cor | 0 real/anna/{ => cor_files}/preludeList.cor | 0 real/anna/{ => cor_files}/realNasties.cor | 0 real/anna/{ => cor_files}/reverse.cor | 0 real/anna/{ => cor_files}/sebastian1.cor | 0 real/anna/{ => cor_files}/sebastian2.cor | 0 real/anna/{ => cor_files}/sets.cor | 0 real/anna/{ => cor_files}/standardTest.cor | 0 real/anna/{ => cor_files}/treeDepth.cor | 0 real/compress/Makefile | 11 + .../{compress.stdin => compress.faststdin} | 0 .../{compress.stdout => compress.faststdout} | Bin real/compress/compress.stdout-mingw | Bin 95823 -> 0 bytes real/compress2/Makefile | 14 + .../{compress2.stdin => compress2.faststdin} | 0 .../{compress2.stdout => compress2.faststdout} | Bin real/fulsom/Makefile | 4 +- gc/fulsom/out => real/fulsom/fulsom.faststdout | Bin real/fulsom/fulsom.stdout | Bin 87916 -> 346864 bytes real/fulsom/fulsom.stdout-mingw | Bin 185 -> 0 bytes real/gamteb/{gamteb.stdin => gamteb.faststdin} | 0 real/gamteb/{gamteb.stdout => gamteb.faststdout} | 0 real/gamteb/{gamteb.stdout1 => gamteb.faststdout1} | 0 real/gamteb/gamteb.stdin | 2 +- real/gamteb/gamteb.stdout | 78779 +++++- real/grep/Makefile | 3 +- real/grep/grep.stdout | 19 + real/hpg/Env.lhs | 5 +- real/hpg/Makefile | 8 +- real/hpg/README.nofib | 4 + real/hpg/{hpg.stdout => hpg.faststdout} | 0 real/hpg/hpg.stderr | 1 - real/hpg/hpg.stdout | 28280 +- real/rsa/rsa.stdin | 3503 +- real/rsa/rsa.stdout | 1378 +- real/scs/Main.hs | 3 +- real/scs/Makefile | 6 +- real/scs/scs.stdout | 744 +- real/scs/scs.stdout-x86-linux | 743 - real/scs/scs.stdout-x86_64 | 743 - real/symalg/{symalg.stdin => symalg.faststdin} | 0 real/symalg/{symalg.stdout => symalg.faststdout} | 0 real/symalg/symalg.stdin | 2 +- real/symalg/symalg.stdout | 6 +- shootout/binary-trees/Makefile | 4 +- shootout/binary-trees/binary-trees.stdout | 18 +- shootout/fasta/Makefile | 2 +- shootout/k-nucleotide/Makefile | 2 +- shootout/k-nucleotide/k-nucleotide.stdout | 44 +- shootout/pidigits/Makefile | 2 +- shootout/pidigits/pidigits.stdout | 200 + shootout/reverse-complement/Makefile | 2 +- spectral/atom/Makefile | 4 +- spectral/atom/atom.slowstdout | 1700 - spectral/atom/atom.stdout | 1000 + spectral/boyer/Makefile | 4 +- spectral/circsim/Makefile | 4 +- .../circsim/circsim.slowstdout | 0 spectral/circsim/circsim.stdout | 2 +- spectral/clausify/Makefile | 4 +- .../{clausify.stdout => clausify.faststdout} | 0 spectral/clausify/clausify.slowstdout | 100 - spectral/clausify/clausify.stdout | 193 + spectral/fft2/Main.lhs | 18 +- spectral/fft2/Makefile | 4 +- spectral/fft2/README.nofib | 11 + spectral/fft2/fft2.stdout | 4 +- spectral/fft2/{ => old}/Makefile | 0 spectral/fft2/{ => old}/fft2.slowstdout | 0 spectral/fft2/{ => old}/fft2.slowstdout-x86-linux | 0 spectral/fft2/{ => old}/fft2.slowstdout-x86-mingw | 0 spectral/fft2/{ => old}/fft2.slowstdout-x86_64 | 0 spectral/fft2/{ => old}/fft2.stdout | 0 spectral/fft2/{ => old}/fft2.stdout-mingw | 0 spectral/fft2/{ => old}/fft2.stdout-x86_64 | 0 spectral/fft2/{ => old}/fft2.stdout1 | 0 spectral/fft2/{ => old}/fft2.stdout2 | 0 spectral/fft2/{ => old}/fft2.stdout3 | 0 spectral/fft2/{ => old}/fft2.stdout4 | 0 spectral/fft2/{ => old}/fft2.stdout5 | 0 spectral/fft2/{ => old}/fft2.stdout6 | 0 spectral/fft2/{ => old}/fft2.stdout7 | 0 spectral/fibheaps/Makefile | 4 +- spectral/gcd/Makefile | 4 +- spectral/gcd/{gcd.stdout => gcd.faststdout} | 0 spectral/gcd/gcd.slowstdout | 1 - spectral/gcd/gcd.stdout | 2 +- spectral/hartel/comp_lab_zift/Makefile | 4 +- ...mp_lab_zift.stdout => comp_lab_zift.faststdout} | 0 .../hartel/comp_lab_zift/comp_lab_zift.slowstdout | 1 - spectral/hartel/comp_lab_zift/comp_lab_zift.stdout | 2 +- spectral/hartel/event/Makefile | 4 +- spectral/hartel/fft/Makefile | 4 +- spectral/hartel/fft/{fft.stdout => fft.faststdout} | 0 spectral/hartel/fft/fft.slowstdout | 1 - spectral/hartel/fft/fft.stdout | 2 +- spectral/hartel/genfft/Makefile | 4 +- .../genfft/{genfft.stdout => genfft.faststdout} | 0 spectral/hartel/genfft/genfft.slowstdout | 1 - spectral/hartel/genfft/genfft.stdout | 2 +- spectral/hartel/ida/Makefile | 4 +- spectral/hartel/ida/{ida.stdout => ida.faststdout} | 0 spectral/hartel/ida/ida.slowstdout | 2 - spectral/hartel/ida/ida.stdout | 4 +- spectral/hartel/sched/Makefile | 2 +- .../sched/{sched.stdout => sched.faststdout} | 0 spectral/hartel/sched/sched.slowstdout | 1 - spectral/hartel/sched/sched.stdout | 2 +- spectral/hartel/solid/Makefile | 4 +- .../solid/{solid.stdout => solid.faststdout} | 0 spectral/hartel/solid/solid.slowstdout | 4 + spectral/hartel/solid/solid.stdout | 6 + spectral/hartel/transform/Makefile | 4 +- .../{transform.stdout => transform.faststdout} | 0 spectral/hartel/transform/transform.slowstdout | 1 - spectral/hartel/transform/transform.stdout | 2 +- spectral/hartel/typecheck/Makefile | 4 +- .../{typecheck.stdout => typecheck.faststdout} | 0 spectral/hartel/typecheck/typecheck.slowstdout | 1 - spectral/hartel/typecheck/typecheck.stdout | 2 +- spectral/hartel/wang/Makefile | 4 +- .../hartel/wang/{wang.stdout => wang.faststdout} | 0 spectral/hartel/wang/wang.slowstdout | 1 - spectral/hartel/wang/wang.stdout | 2 +- spectral/hartel/wave4main/Makefile | 6 +- .../{wave4main.stdout2 => wave4main.faststdout} | 0 spectral/hartel/wave4main/wave4main.slowstdout | 1 - .../wave4main/wave4main.slowstdout-x86-linux | 1 - spectral/hartel/wave4main/wave4main.stdout | 2 +- spectral/hartel/wave4main/wave4main.stdout3 | 1 - spectral/knights/Makefile | 4 +- .../knights/{knights.stdout => knights.faststdout} | 0 spectral/knights/knights.slowstdout | 484 +- spectral/knights/knights.stdout | 64 +- spectral/lcss/Makefile | 2 +- spectral/lcss/lcss.slowstdout | 1 - spectral/lcss/lcss.stdout | 2 +- spectral/multiplier/Makefile | 4 +- spectral/power/Makefile | 4 +- spectral/power/{power.stdout => power.faststdout} | 0 spectral/power/power.slowstdout | 4 - spectral/power/power.stdout | 8 +- .../primetest/{mersenne607 => primetest.faststdin} | 0 .../{primetest.stdout => primetest.faststdout} | 0 spectral/primetest/primetest.slowstdin | 2 - spectral/primetest/primetest.slowstdout | 1 - spectral/primetest/primetest.stdin | 29 + spectral/primetest/primetest.stdout | 2 +- spectral/rewrite/Makefile | 4 +- spectral/sphere/Makefile | 4 +- .../sphere/{sphere.stdout => sphere.faststdout} | 0 spectral/sphere/sphere.slowstdout | 40003 --- spectral/sphere/sphere.stdout | 244460 +++++++++++++++++- 282 files changed, 358703 insertions(+), 50526 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 08cc9b6b2c7f7fdaaaf80361ab84a501f0a573c5 From git at git.haskell.org Wed Nov 14 17:29:43 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 14 Nov 2018 17:29:43 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Wibbles (f3b3275) Message-ID: <20181114172943.948FB3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/f3b32750ec17994d76dd5caf20ca246142aa373d/ghc >--------------------------------------------------------------- commit f3b32750ec17994d76dd5caf20ca246142aa373d Author: Simon Peyton Jones Date: Wed Nov 14 17:28:35 2018 +0000 Wibbles >--------------------------------------------------------------- f3b32750ec17994d76dd5caf20ca246142aa373d compiler/typecheck/TcHsType.hs | 2 +- compiler/typecheck/TcInstDcls.hs | 188 ++++++++------------------------------- 2 files changed, 36 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 f3b32750ec17994d76dd5caf20ca246142aa373d From git at git.haskell.org Thu Nov 15 01:17:54 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 15 Nov 2018 01:17:54 +0000 (UTC) Subject: [commit: ghc] wip/T15809: More progress on reporting unbound variables (4c251b2) Message-ID: <20181115011754.A52F53A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/4c251b20e0d3c734ba1bd9515bcced7876dcf398/ghc >--------------------------------------------------------------- commit 4c251b20e0d3c734ba1bd9515bcced7876dcf398 Author: Simon Peyton Jones Date: Thu Nov 15 01:16:12 2018 +0000 More progress on reporting unbound variables >--------------------------------------------------------------- 4c251b20e0d3c734ba1bd9515bcced7876dcf398 compiler/typecheck/TcHsType.hs | 16 +- compiler/typecheck/TcInstDcls.hs | 64 ++-- compiler/typecheck/TcTyClsDecls.hs | 352 +++++---------------- compiler/typecheck/TcValidity.hs | 19 +- .../should_fail/ExplicitForAllFams4a.stderr | 6 +- .../should_fail/ExplicitForAllFams4b.stderr | 30 +- testsuite/tests/polykinds/T13985.stderr | 25 +- 7 files changed, 164 insertions(+), 348 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 4c251b20e0d3c734ba1bd9515bcced7876dcf398 From git at git.haskell.org Thu Nov 15 03:35:48 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 15 Nov 2018 03:35:48 +0000 (UTC) Subject: [commit: ghc] master: Fix a bug in SRT generation (#15892) (eb46345) Message-ID: <20181115033548.22BF63A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/eb46345d37ee61575e6fed04da718c1b7ee0bb99/ghc >--------------------------------------------------------------- commit eb46345d37ee61575e6fed04da718c1b7ee0bb99 Author: Simon Marlow Date: Thu Nov 15 06:31:35 2018 +0300 Fix a bug in SRT generation (#15892) Summary: The logic in `Note [recursive SRTs]` was correct. However, my implementation of it wasn't: I got the associativity of `Set.difference` wrong, which led to an extremely subtle and difficult to find bug. Fortunately now we have a test case. I was able to cut down the code to something manageable, and I've added it to the test suite. Test Plan: Before (using my stage 1 compiler without the fix): ``` ====> T15892(normal) 1 of 1 [0, 0, 0] cd "T15892.run" && "/home/smarlow/ghc/inplace/bin/ghc-stage1" -o T15892 T15892.hs -dcore-lint -dcmm-lint -no-user-package-db -rtsopts -fno-warn-missed-specialisations -fshow-warning-groups -fdiagnostics-color=never -fno-diagnostics-show-caret -Werror=compat -dno-debug-output -O cd "T15892.run" && ./T15892 +RTS -G1 -A32k -RTS Wrong exit code for T15892(normal)(expected 0 , actual 134 ) Stderr ( T15892 ): T15892: internal error: evacuate: strange closure type 0 (GHC version 8.7.20181113 for x86_64_unknown_linux) Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug Aborted (core dumped) *** unexpected failure for T15892(normal) =====> T15892(g1) 1 of 1 [0, 1, 0] cd "T15892.run" && "/home/smarlow/ghc/inplace/bin/ghc-stage1" -o T15892 T15892.hs -dcore-lint -dcmm-lint -no-user-package-db -rtsopts -fno-warn-missed-specialisations -fshow-warning-groups -fdiagnostics-color=never -fno-diagnostics-show-caret -Werror=compat -dno-debug-output -O cd "T15892.run" && ./T15892 +RTS -G1 -RTS +RTS -G1 -A32k -RTS Wrong exit code for T15892(g1)(expected 0 , actual 134 ) Stderr ( T15892 ): T15892: internal error: evacuate: strange closure type 0 (GHC version 8.7.20181113 for x86_64_unknown_linux) Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug Aborted (core dumped) ``` After (using my stage 2 compiler with the fix): ``` =====> T15892(normal) 1 of 1 [0, 0, 0] cd "T15892.run" && "/home/smarlow/ghc/inplace/test spaces/ghc-stage2" -o T15892 T15892.hs -dcore-lint -dcmm-lint -no-user-package-db -rtsopts -fno-warn-missed-specialisations -fshow-warning-groups -fdiagnostics-color=never -fno-diagnostics-show-caret -Werror=compat -dno-debug-output cd "T15892.run" && ./T15892 +RTS -G1 -A32k -RTS =====> T15892(g1) 1 of 1 [0, 0, 0] cd "T15892.run" && "/home/smarlow/ghc/inplace/test spaces/ghc-stage2" -o T15892 T15892.hs -dcore-lint -dcmm-lint -no-user-package-db -rtsopts -fno-warn-missed-specialisations -fshow-warning-groups -fdiagnostics-color=never -fno-diagnostics-show-caret -Werror=compat -dno-debug-output cd "T15892.run" && ./T15892 +RTS -G1 -RTS +RTS -G1 -A32k -RTS ``` Reviewers: bgamari, osa1, erikd Reviewed By: osa1 Subscribers: rwbarton, carter GHC Trac Issues: #15892 Differential Revision: https://phabricator.haskell.org/D5334 >--------------------------------------------------------------- eb46345d37ee61575e6fed04da718c1b7ee0bb99 compiler/cmm/CmmBuildInfoTables.hs | 2 +- testsuite/tests/codeGen/should_run/T15892.hs | 67 ++++++++++++++++++++++++++++ testsuite/tests/codeGen/should_run/all.T | 7 +++ 3 files changed, 75 insertions(+), 1 deletion(-) diff --git a/compiler/cmm/CmmBuildInfoTables.hs b/compiler/cmm/CmmBuildInfoTables.hs index a8f89a1..be96fba 100644 --- a/compiler/cmm/CmmBuildInfoTables.hs +++ b/compiler/cmm/CmmBuildInfoTables.hs @@ -703,7 +703,7 @@ oneSRT dflags staticFuns blockids lbls isCAF cafs = do -- Remove recursive references from the SRT, except for (all but -- one of the) static functions. See Note [recursive SRTs]. nonRec = cafs `Set.difference` - Set.fromList lbls `Set.difference` Set.fromList otherFunLabels + (Set.fromList lbls `Set.difference` Set.fromList otherFunLabels) -- First resolve all the CAFLabels to SRTEntries -- Implements the [Inline] optimisation. diff --git a/testsuite/tests/codeGen/should_run/T15892.hs b/testsuite/tests/codeGen/should_run/T15892.hs new file mode 100644 index 0000000..d132943 --- /dev/null +++ b/testsuite/tests/codeGen/should_run/T15892.hs @@ -0,0 +1,67 @@ +{-# LANGUAGE RankNTypes #-} +{-# LANGUAGE BangPatterns #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE MagicHash, UnboxedTuples #-} + +module Main (enumFromCallbackCatch, consume, next, main) where + +import Control.Monad +import Foreign +import GHC.ForeignPtr +import GHC.Base (realWorld#) +import Data.Word (Word8) +import Foreign.Storable (peek) +import GHC.IO + +data ByteString = PS {-# UNPACK #-} !(ForeignPtr Word8) {-# UNPACK #-} !Int + +instance Show ByteString where + showsPrec p ps r = showsPrec p (unpackAppendCharsStrict ps []) r + +unpackAppendCharsStrict :: ByteString -> [Char] -> [Char] +unpackAppendCharsStrict (PS fp len) xs = + unsafeDupablePerformIO $ withForeignPtr fp $ \base -> + loop (base `plusPtr` (-1)) (base `plusPtr` 960) xs + where + loop !sentinal !p acc + | p == sentinal = return acc + | otherwise = do x <- peek p + loop sentinal (p `plusPtr` (-1)) (w2c x:acc) + +w2c :: Word8 -> Char +w2c = toEnum . fromEnum + +packCStringLen :: Int -> IO ByteString +packCStringLen l = do + p <- callocBytes bufsize + fp <- newForeignPtr finalizerFree p + return $! PS fp l +{-# NOINLINE packCStringLen #-} + +bufsize :: Int +bufsize = 8192 + +{-# NOINLINE readFromPtr #-} +readFromPtr :: IO ByteString +readFromPtr = do + bs <- packCStringLen bufsize + length (show bs) `seq` return bs + +newtype Iteratee s = Iteratee { runIter :: forall r. + ((s -> Iteratee s) -> IO r) -> + IO r} + +enumFromCallbackCatch :: IO () +enumFromCallbackCatch = produce 500 consume + where + produce 0 (Iteratee f) = return () + produce n (Iteratee f) = f onCont + where onCont k = do bs <- readFromPtr; produce (n-1) (k bs) + +consume = Iteratee $ \onCont -> onCont next +next x = Iteratee $ \onCont -> print x >> onCont (\_ -> consume) + +main :: IO () +main = do + _ <- enumFromCallbackCatch + pure () diff --git a/testsuite/tests/codeGen/should_run/all.T b/testsuite/tests/codeGen/should_run/all.T index 3935574..1dec2a6 100644 --- a/testsuite/tests/codeGen/should_run/all.T +++ b/testsuite/tests/codeGen/should_run/all.T @@ -181,3 +181,10 @@ test('T15696_1', normal, compile_and_run, ['-O']) test('T15696_2', normal, compile_and_run, ['-O']) # This requires -O test('T15696_3', normal, compile_and_run, ['-O']) + +test('T15892', + [ ignore_stdout, + # we want to do lots of major GC to make the bug more likely to + # happen, so -G1 -A32k: + extra_run_opts('+RTS -G1 -A32k -RTS') ], + compile_and_run, ['-O']) From git at git.haskell.org Thu Nov 15 11:53:27 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 15 Nov 2018 11:53:27 +0000 (UTC) Subject: [commit: ghc] master: Comments only, about polykinded TyConApps (fe05764) Message-ID: <20181115115327.204143A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/fe0576426d3ef07d7743c65e34c8b04ce0616426/ghc >--------------------------------------------------------------- commit fe0576426d3ef07d7743c65e34c8b04ce0616426 Author: Simon Peyton Jones Date: Mon Nov 5 13:48:27 2018 +0000 Comments only, about polykinded TyConApps See Trac #15704 comment:8ff >--------------------------------------------------------------- fe0576426d3ef07d7743c65e34c8b04ce0616426 compiler/types/Unify.hs | 14 +++++++++++++- 1 file changed, 13 insertions(+), 1 deletion(-) diff --git a/compiler/types/Unify.hs b/compiler/types/Unify.hs index 951a3f9..62d53dc 100644 --- a/compiler/types/Unify.hs +++ b/compiler/types/Unify.hs @@ -888,6 +888,17 @@ Note that * One better way is to ensure that type patterns (the template in the matching process) have no casts. See Trac #14119. +Note [Polykinded tycon applications] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Suppose T :: forall k. Type -> K +and we are unifying + ty1: T @Type Int :: Type + ty2: T @(Type->Type) Int Int :: Type + +These two TyConApps have the same TyCon at the front but they +(legitimately) have different numbers of arguments. They +are surelyApart, so we can report that without looking any +further (see Trac #15704). -} -------------- unify_ty: the main workhorse ----------- @@ -1025,7 +1036,8 @@ unify_tys env orig_xs orig_ys = do { unify_ty env x y (mkNomReflCo $ typeKind x) ; go xs ys } go _ _ = surelyApart - -- Possibly different saturations of a polykinded tycon (See Trac #15704) + -- Possibly different saturations of a polykinded tycon + -- See Note [Polykinded tycon applications] --------------------------------- uVar :: UMEnv From git at git.haskell.org Thu Nov 15 11:53:30 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 15 Nov 2018 11:53:30 +0000 (UTC) Subject: [commit: ghc] master: Comments adding to the fix for Trac #15859 (0ce66be) Message-ID: <20181115115330.1495A3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0ce66be953becf7c9de3cbea406953306b4db3b1/ghc >--------------------------------------------------------------- commit 0ce66be953becf7c9de3cbea406953306b4db3b1 Author: Simon Peyton Jones Date: Tue Nov 6 09:10:30 2018 +0000 Comments adding to the fix for Trac #15859 >--------------------------------------------------------------- 0ce66be953becf7c9de3cbea406953306b4db3b1 compiler/typecheck/TcExpr.hs | 28 ++++++++++++++++++++++++---- compiler/types/TyCoRep.hs | 5 ++++- 2 files changed, 28 insertions(+), 5 deletions(-) diff --git a/compiler/typecheck/TcExpr.hs b/compiler/typecheck/TcExpr.hs index a087917..9eaead5 100644 --- a/compiler/typecheck/TcExpr.hs +++ b/compiler/typecheck/TcExpr.hs @@ -1331,8 +1331,9 @@ tcArgs fun orig_fun_ty fun_orig orig_args herald ; case tcSplitForAllTy_maybe upsilon_ty of Just (tvb, inner_ty) | binderArgFlag tvb == Specified -> - -- It really can't be Inferred, because we've just instantiated those - -- But, oddly, it might just be Required. See #15859. + -- It really can't be Inferred, because we've justn + -- instantiated those. But, oddly, it might just be Required. + -- See Note [Required quantifiers in the type of a term] do { let tv = binderVar tvb kind = tyVarKind tv ; ty_arg <- tcHsTypeApp hs_ty_arg kind @@ -1381,8 +1382,27 @@ tcArgs fun orig_fun_ty fun_orig orig_args herald text "Cannot apply expression of type" <+> quotes (ppr ty) $$ text "to a visible type argument" <+> quotes (ppr arg) } -{- Note [Visible type application zonk] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +{- Note [Required quantifiers in the type of a term] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Consider (Trac #15859) + + data A k :: k -> Type -- A :: forall k -> k -> Type + type KindOf (a :: k) = k -- KindOf :: forall k. k -> Type + a = (undefind :: KindOf A) @Int + +With ImpredicativeTypes (thin ice, I know), we instantiate +KindOf at type (forall k -> k -> Type), so + KindOf A = forall k -> k -> Type +whose first argument is Required + +We want to reject this type application to Int, but in earlier +GHCs we had an ASSERT that Required could not occur here. + +The ice is thin; c.f. Note [No Required TyCoBinder in terms] +in TyCoRep. + +Note [Visible type application zonk] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ * Substitutions should be kind-preserving, so we need kind(tv) = kind(ty_arg). * tcHsTypeApp only guarantees that diff --git a/compiler/types/TyCoRep.hs b/compiler/types/TyCoRep.hs index 1c0d5f9..d6c0f33 100644 --- a/compiler/types/TyCoRep.hs +++ b/compiler/types/TyCoRep.hs @@ -711,7 +711,7 @@ See also Note [Required, Specified, and Inferred for types] in TcTyClsDecls Visible Type Applications paper (ESOP'16). Note [No Required TyCoBinder in terms] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ We don't allow Required foralls for term variables, including pattern synonyms and data constructors. Why? Because then an application would need a /compulsory/ type argument (possibly without an "@"?), @@ -719,6 +719,9 @@ thus (f Int); and we don't have concrete syntax for that. We could change this decision, but Required, Named TyCoBinders are rare anyway. (Most are Anons.) + +However the type of a term can (just about) have a required quantifier; +see Note [Required quantifiers in the type of a term] in TcExpr. -} From git at git.haskell.org Thu Nov 15 11:53:33 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 15 Nov 2018 11:53:33 +0000 (UTC) Subject: [commit: ghc] master: Smarter HsType pretty-print for promoted datacons (ae2c9b4) Message-ID: <20181115115333.C75AB3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ae2c9b40f5b6bf272251d1f4107c60003f541b62/ghc >--------------------------------------------------------------- commit ae2c9b40f5b6bf272251d1f4107c60003f541b62 Author: Simon Peyton Jones Date: Thu Nov 15 09:02:11 2018 +0000 Smarter HsType pretty-print for promoted datacons Fix Trac #15898, by being smarter about when to print a space before a promoted data constructor, in a HsType. I had to implement a mildly tiresome function HsType.lhsTypeHasLeadingPromotionQuote It has multiple cases, of course, but it's very simple. The patch improves the error-message output in a bunch of cases, and (to my surprise) actually fixes a bug in the output of T14343 (Trac #14343), thus - In the expression: _ :: Proxy '('( 'True, 'False), 'False) + In the expression: _ :: Proxy '( '( 'True, 'False), 'False) I discovered that there were two copies of the PromotionFlag type (a boolean, with helpfully named data cons), one in IfaceType and one in HsType. So I combined into one, PromotionFlag, and moved it to BasicTypes. That's why quite a few files are touched, but it's all routine. >--------------------------------------------------------------- ae2c9b40f5b6bf272251d1f4107c60003f541b62 compiler/basicTypes/BasicTypes.hs | 19 ++++++ compiler/hsSyn/Convert.hs | 12 ++-- compiler/hsSyn/HsTypes.hs | 75 +++++++++++++++------- compiler/iface/IfaceType.hs | 44 ++++++------- compiler/iface/TcIface.hs | 6 +- compiler/iface/ToIface.hs | 8 +-- compiler/parser/Parser.y | 6 +- compiler/utils/Binary.hs | 11 ++++ .../dependent/should_fail/PromotedClass.stderr | 4 +- .../tests/dependent/should_fail/T15245.stderr | 6 +- testsuite/tests/ghci/scripts/T15898.script | 6 ++ .../T5472.stdout => ghci/scripts/T15898.stdout} | 0 testsuite/tests/ghci/scripts/all.T | 1 + .../parser/should_compile/DumpParsedAst.stderr | 2 +- .../parser/should_compile/DumpRenamedAst.stderr | 2 +- .../tests/parser/should_compile/KindSigs.stderr | 2 +- testsuite/tests/polykinds/PolyKinds07.stderr | 12 ++-- testsuite/tests/polykinds/T10503.stderr | 2 +- testsuite/tests/polykinds/T15116a.stderr | 4 +- testsuite/tests/polykinds/T7433.stderr | 2 +- testsuite/tests/printer/T14343.stderr | 8 +-- testsuite/tests/printer/T14343b.stderr | 12 ++-- .../tests/typecheck/should_fail/T14607.stderr | 12 ++-- 23 files changed, 161 insertions(+), 95 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 ae2c9b40f5b6bf272251d1f4107c60003f541b62 From git at git.haskell.org Thu Nov 15 17:43:45 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 15 Nov 2018 17:43:45 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Nearly there... (c0dd1f4) Message-ID: <20181115174345.6FE3C3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/c0dd1f473d5d5d0fce90a05972e2e4138ada88af/ghc >--------------------------------------------------------------- commit c0dd1f473d5d5d0fce90a05972e2e4138ada88af Author: Simon Peyton Jones Date: Thu Nov 15 17:43:18 2018 +0000 Nearly there... >--------------------------------------------------------------- c0dd1f473d5d5d0fce90a05972e2e4138ada88af compiler/typecheck/TcGenDeriv.hs | 8 +- compiler/typecheck/TcHsType.hs | 2 - compiler/typecheck/TcInstDcls.hs | 12 +- compiler/typecheck/TcTyClsDecls.hs | 100 ++-------------- compiler/typecheck/TcValidity.hs | 132 +++++++++++++++++---- testsuite/tests/ghci/scripts/T6018ghcifail.stderr | 4 +- .../should_fail/ExplicitForAllFams4a.stderr | 10 +- .../should_fail/ExplicitForAllFams4b.stderr | 20 ++-- .../indexed-types/should_fail/SimpleFail13.stderr | 2 +- .../indexed-types/should_fail/SimpleFail2a.hs | 12 +- .../indexed-types/should_fail/SimpleFail9.stderr | 4 +- .../tests/indexed-types/should_fail/T7536.stderr | 5 +- testsuite/tests/polykinds/T13985.stderr | 10 +- .../tests/th/TH_reifyExplicitForAllFams.stderr | 6 +- .../tests/typecheck/should_fail/T6018fail.stderr | 4 +- 15 files changed, 169 insertions(+), 162 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 c0dd1f473d5d5d0fce90a05972e2e4138ada88af From git at git.haskell.org Thu Nov 15 23:30:50 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 15 Nov 2018 23:30:50 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Better validity checks, simplification (a498723) Message-ID: <20181115233050.667603A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/a4987231d782c136a8af2d5d70d7e5dbc493b9b4/ghc >--------------------------------------------------------------- commit a4987231d782c136a8af2d5d70d7e5dbc493b9b4 Author: Simon Peyton Jones Date: Thu Nov 15 23:29:34 2018 +0000 Better validity checks, simplification >--------------------------------------------------------------- a4987231d782c136a8af2d5d70d7e5dbc493b9b4 compiler/typecheck/TcGenDeriv.hs | 3 +- compiler/typecheck/TcHsType.hs | 66 +++--- compiler/typecheck/TcInstDcls.hs | 43 +++- compiler/typecheck/TcTyClsDecls.hs | 223 ++++++++++++++++++- compiler/typecheck/TcValidity.hs | 238 ++------------------- .../should_fail/ExplicitForAllFams4b.stderr | 63 ++++-- .../indexed-types/should_fail/SimpleFail2a.stderr | 2 +- .../tests/indexed-types/should_fail/T14045a.stderr | 2 +- testsuite/tests/polykinds/T13985.hs | 1 + testsuite/tests/polykinds/T13985.stderr | 10 +- 10 files changed, 338 insertions(+), 313 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 a4987231d782c136a8af2d5d70d7e5dbc493b9b4 From git at git.haskell.org Fri Nov 16 08:53:31 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Nov 2018 08:53:31 +0000 (UTC) Subject: [commit: ghc] master: bump haddock submodule (4efd1b4) Message-ID: <20181116085331.F07B33A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4efd1b487e10c8cdbc1bca10c45f0887642a5c48/ghc >--------------------------------------------------------------- commit 4efd1b487e10c8cdbc1bca10c45f0887642a5c48 Author: Alp Mestanogullari Date: Fri Nov 16 09:50:27 2018 +0100 bump haddock submodule Summary: ae2c9b40f5b6bf272251d1f4107c60003f541b62 introduced some changes that broke haddock, [1] fixed them and this patch bumps the haddock submodule to include the fixes. [1]: https://github.com/haskell/haddock/pull/970 Test Plan: build haddock (make or hadrian) Reviewers: bgamari, AndreasK Reviewed By: AndreasK Subscribers: osa1, AndreasK, rwbarton, carter GHC Trac Issues: #15900 Differential Revision: https://phabricator.haskell.org/D5341 >--------------------------------------------------------------- 4efd1b487e10c8cdbc1bca10c45f0887642a5c48 utils/haddock | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/utils/haddock b/utils/haddock index f345505..0b37998 160000 --- a/utils/haddock +++ b/utils/haddock @@ -1 +1 @@ -Subproject commit f3455051b59c99d26e0cf040be45f5916463ae55 +Subproject commit 0b379984f7898ab0656f71f05fb0163a6a2ddb2c From git at git.haskell.org Fri Nov 16 10:52:57 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Nov 2018 10:52:57 +0000 (UTC) Subject: [commit: ghc] master: More efficient, non-allocating unsafeLookupStaticPtr (a50a59a) Message-ID: <20181116105257.DF8293A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a50a59a9603425fafb1fac33addb201c19546808/ghc >--------------------------------------------------------------- commit a50a59a9603425fafb1fac33addb201c19546808 Author: Ömer Sinan Ağacan Date: Fri Nov 16 13:52:11 2018 +0300 More efficient, non-allocating unsafeLookupStaticPtr We now allocate the key to spt on C stack rather than in Haskell heap, avoiding allocating in `unsafeLookupStaticPtr`. This should be slightly more efficient. Test Plan: Validated locally Reviewers: simonmar, hvr, bgamari, erikd Reviewed By: simonmar Subscribers: rwbarton, carter Differential Revision: https://phabricator.haskell.org/D5333 >--------------------------------------------------------------- a50a59a9603425fafb1fac33addb201c19546808 includes/HsFFI.h | 2 +- libraries/base/GHC/StaticPtr.hs | 7 +++---- rts/StaticPtrTable.c | 3 ++- 3 files changed, 6 insertions(+), 6 deletions(-) diff --git a/includes/HsFFI.h b/includes/HsFFI.h index 8497647..4b6278b 100644 --- a/includes/HsFFI.h +++ b/includes/HsFFI.h @@ -126,7 +126,7 @@ extern void hs_free_stable_ptr_unsafe (HsStablePtr sp); extern void hs_free_stable_ptr (HsStablePtr sp); extern void hs_free_fun_ptr (HsFunPtr fp); -extern StgPtr hs_spt_lookup(StgWord64 key[2]); +extern StgPtr hs_spt_lookup(StgWord64 key1, StgWord64 key2); extern int hs_spt_keys(StgPtr keys[], int szKeys); extern int hs_spt_key_count (void); diff --git a/libraries/base/GHC/StaticPtr.hs b/libraries/base/GHC/StaticPtr.hs index 42ca092..14ff3e0 100644 --- a/libraries/base/GHC/StaticPtr.hs +++ b/libraries/base/GHC/StaticPtr.hs @@ -48,8 +48,7 @@ module GHC.StaticPtr ) where import Foreign.C.Types (CInt(..)) -import Foreign.Marshal (allocaArray, peekArray, withArray) -import Foreign.Ptr (castPtr) +import Foreign.Marshal (allocaArray, peekArray) import GHC.Exts (addrToAny#) import GHC.Ptr (Ptr(..), nullPtr) import GHC.Fingerprint (Fingerprint(..)) @@ -89,13 +88,13 @@ staticKey (StaticPtr w0 w1 _ _) = Fingerprint (W64# w0) (W64# w1) -- unsafeLookupStaticPtr :: StaticKey -> IO (Maybe (StaticPtr a)) unsafeLookupStaticPtr (Fingerprint w1 w2) = do - ptr@(Ptr addr) <- withArray [w1,w2] (hs_spt_lookup . castPtr) + ptr@(Ptr addr) <- hs_spt_lookup w1 w2 if (ptr == nullPtr) then return Nothing else case addrToAny# addr of (# spe #) -> return (Just spe) -foreign import ccall unsafe hs_spt_lookup :: Ptr () -> IO (Ptr a) +foreign import ccall unsafe hs_spt_lookup :: Word64 -> Word64 -> IO (Ptr a) -- | A class for things buildable from static pointers. class IsStatic p where diff --git a/rts/StaticPtrTable.c b/rts/StaticPtrTable.c index 0b22440..997987a 100644 --- a/rts/StaticPtrTable.c +++ b/rts/StaticPtrTable.c @@ -76,9 +76,10 @@ void hs_spt_remove(StgWord64 key[2]) { } } -StgPtr hs_spt_lookup(StgWord64 key[2]) { +StgPtr hs_spt_lookup(StgWord64 key1, StgWord64 key2) { if (spt) { ACQUIRE_LOCK(&spt_lock); + StgWord64 key[2] = { key1, key2 }; const StgStablePtr * entry = lookupHashTable(spt, (StgWord)key); const StgPtr ret = entry ? deRefStablePtr(*entry) : NULL; RELEASE_LOCK(&spt_lock); From git at git.haskell.org Fri Nov 16 11:39:57 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Nov 2018 11:39:57 +0000 (UTC) Subject: [commit: ghc] master: Add missing stderr file for Trac #15898 (32e7738) Message-ID: <20181116113957.333CD3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/32e7738bb1a1df5133fd775312e7fb5ae6823099/ghc >--------------------------------------------------------------- commit 32e7738bb1a1df5133fd775312e7fb5ae6823099 Author: Simon Peyton Jones Date: Fri Nov 16 11:39:09 2018 +0000 Add missing stderr file for Trac #15898 >--------------------------------------------------------------- 32e7738bb1a1df5133fd775312e7fb5ae6823099 testsuite/tests/ghci/scripts/T15898.stderr | 52 ++++++++++++++++++++++++++++++ 1 file changed, 52 insertions(+) diff --git a/testsuite/tests/ghci/scripts/T15898.stderr b/testsuite/tests/ghci/scripts/T15898.stderr new file mode 100644 index 0000000..11ca6cc --- /dev/null +++ b/testsuite/tests/ghci/scripts/T15898.stderr @@ -0,0 +1,52 @@ + +:3:1: error: + • Couldn't match kind ‘()’ with ‘*’ + When matching types + a0 :: * + '() :: () + • In the expression: undefined :: '() + In an equation for ‘it’: it = undefined :: '() + +:3:14: error: + • Expected a type, but ‘'()’ has kind ‘()’ + • In an expression type signature: '() + In the expression: undefined :: '() + In an equation for ‘it’: it = undefined :: '() + +:4:14: error: + • Expected kind ‘* -> *’, but ‘Proxy '()’ has kind ‘*’ + • In an expression type signature: Proxy '() Int + In the expression: undefined :: Proxy '() Int + In an equation for ‘it’: it = undefined :: Proxy '() Int + +:5:1: error: + • Couldn't match kind ‘[*]’ with ‘*’ + When matching types + a0 :: * + '[(), ()] :: [*] + • In the expression: undefined :: [(), ()] + In an equation for ‘it’: it = undefined :: [(), ()] + +:5:14: error: + • Expected a type, but ‘[(), ()]’ has kind ‘[*]’ + • In an expression type signature: [(), ()] + In the expression: undefined :: [(), ()] + In an equation for ‘it’: it = undefined :: [(), ()] + +:6:1: error: + • Couldn't match kind ‘([k0], [k1])’ with ‘*’ + When matching types + a0 :: * + '( '[], '[]) :: ([k0], [k1]) + • In the expression: undefined :: '( '[], '[]) + In an equation for ‘it’: it = undefined :: '( '[], '[]) + • Relevant bindings include + it :: '( '[], '[]) (bound at :6:1) + +:6:14: error: + • Expected a type, but ‘'( '[], '[])’ has kind ‘([k0], [k1])’ + • In an expression type signature: '( '[], '[]) + In the expression: undefined :: '( '[], '[]) + In an equation for ‘it’: it = undefined :: '( '[], '[]) + • Relevant bindings include + it :: '( '[], '[]) (bound at :6:1) From git at git.haskell.org Fri Nov 16 12:34:16 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Nov 2018 12:34:16 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Finally, validate-clean (44c2d3c) Message-ID: <20181116123416.A907E3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/44c2d3c2b7974c88ecaee1434fdcab64ee1f4072/ghc >--------------------------------------------------------------- commit 44c2d3c2b7974c88ecaee1434fdcab64ee1f4072 Author: Simon Peyton Jones Date: Fri Nov 16 12:03:59 2018 +0000 Finally, validate-clean Except for polykinds/T14846, where there is an extra error message. I actually tnink it's correct, but have not checked yet. >--------------------------------------------------------------- 44c2d3c2b7974c88ecaee1434fdcab64ee1f4072 compiler/typecheck/TcBinds.hs | 24 ---- compiler/typecheck/TcClassDcl.hs | 3 - compiler/typecheck/TcDeriv.hs | 3 - compiler/typecheck/TcEnv.hs | 8 -- compiler/typecheck/TcHsType.hs | 87 +++++++++----- compiler/typecheck/TcInstDcls.hs | 81 ++++++------- compiler/typecheck/TcPat.hs | 2 +- compiler/typecheck/TcTyClsDecls.hs | 132 +++++++++++++-------- compiler/types/TyCoRep.hs | 7 +- .../indexed-types/should_fail/SimpleFail9.stderr | 2 +- .../tests/indexed-types/should_fail/T10817.stderr | 9 +- .../tests/indexed-types/should_fail/T10899.stderr | 3 +- testsuite/tests/polykinds/T8616.stderr | 9 ++ testsuite/tests/printer/Ppr040.hs | 10 +- 14 files changed, 202 insertions(+), 178 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 44c2d3c2b7974c88ecaee1434fdcab64ee1f4072 From git at git.haskell.org Fri Nov 16 16:53:55 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Nov 2018 16:53:55 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Tc-tracing, and order of arguments only (2683496) Message-ID: <20181116165355.553D03A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/268349689168e0c3dc0c7f619a33db991ad7d8c0/ghc >--------------------------------------------------------------- commit 268349689168e0c3dc0c7f619a33db991ad7d8c0 Author: Simon Peyton Jones Date: Wed Oct 31 08:31:38 2018 +0000 Tc-tracing, and order of arguments only I changed the order of arguments to reportAllUnsolved, and the tc-tracing that surrounds it. No change in behaviour >--------------------------------------------------------------- 268349689168e0c3dc0c7f619a33db991ad7d8c0 compiler/typecheck/TcErrors.hs | 29 ++++++++++++++++------------- compiler/typecheck/TcRnMonad.hs | 2 ++ compiler/typecheck/TcSimplify.hs | 4 ---- 3 files changed, 18 insertions(+), 17 deletions(-) diff --git a/compiler/typecheck/TcErrors.hs b/compiler/typecheck/TcErrors.hs index c692b7b..9bca25f 100644 --- a/compiler/typecheck/TcErrors.hs +++ b/compiler/typecheck/TcErrors.hs @@ -146,8 +146,9 @@ reportUnsolved wanted | warn_out_of_scope = HoleWarn | otherwise = HoleDefer - ; report_unsolved binds_var type_errors expr_holes - type_holes out_of_scope_holes wanted + ; report_unsolved type_errors expr_holes + type_holes out_of_scope_holes + binds_var wanted ; ev_binds <- getTcEvBindsMap binds_var ; return (evBindMapBinds ev_binds)} @@ -162,8 +163,8 @@ reportUnsolved wanted reportAllUnsolved :: WantedConstraints -> TcM () reportAllUnsolved wanted = do { ev_binds <- newNoTcEvBinds - ; report_unsolved ev_binds TypeError - HoleError HoleError HoleError wanted } + ; report_unsolved TypeError HoleError HoleError HoleError + ev_binds wanted } -- | Report all unsolved goals as warnings (but without deferring any errors to -- run-time). See Note [Safe Haskell Overlapping Instances Implementation] in @@ -171,22 +172,23 @@ reportAllUnsolved wanted warnAllUnsolved :: WantedConstraints -> TcM () warnAllUnsolved wanted = do { ev_binds <- newTcEvBinds - ; report_unsolved ev_binds (TypeWarn NoReason) - HoleWarn HoleWarn HoleWarn wanted } + ; report_unsolved (TypeWarn NoReason) HoleWarn HoleWarn HoleWarn + ev_binds wanted } -- | Report unsolved goals as errors or warnings. -report_unsolved :: EvBindsVar -- cec_binds - -> TypeErrorChoice -- Deferred type errors +report_unsolved :: TypeErrorChoice -- Deferred type errors -> HoleChoice -- Expression holes -> HoleChoice -- Type holes -> HoleChoice -- Out of scope holes + -> EvBindsVar -- cec_binds -> WantedConstraints -> TcM () -report_unsolved mb_binds_var type_errors expr_holes - type_holes out_of_scope_holes wanted +report_unsolved type_errors expr_holes + type_holes out_of_scope_holes binds_var wanted | isEmptyWC wanted = return () | otherwise - = do { traceTc "reportUnsolved warning/error settings:" $ + = do { traceTc "reportUnsolved {" empty + ; traceTc "reportUnsolved warning/error settings:" $ vcat [ text "type errors:" <+> ppr type_errors , text "expr holes:" <+> ppr expr_holes , text "type holes:" <+> ppr type_holes @@ -219,10 +221,11 @@ report_unsolved mb_binds_var type_errors expr_holes -- See Trac #15539 and c.f. setting ic_status -- in TcSimplify.setImplicationStatus , cec_warn_redundant = warn_redundant - , cec_binds = mb_binds_var } + , cec_binds = binds_var } ; tc_lvl <- getTcLevel - ; reportWanteds err_ctxt tc_lvl wanted } + ; reportWanteds err_ctxt tc_lvl wanted + ; traceTc "reportUnsolved }" empty } -------------------------------------------- -- Internal functions diff --git a/compiler/typecheck/TcRnMonad.hs b/compiler/typecheck/TcRnMonad.hs index bef1044..5e6cb8f 100644 --- a/compiler/typecheck/TcRnMonad.hs +++ b/compiler/typecheck/TcRnMonad.hs @@ -1532,8 +1532,10 @@ pushLevelAndCaptureConstraints :: TcM a -> TcM (TcLevel, WantedConstraints, a) pushLevelAndCaptureConstraints thing_inside = do { env <- getLclEnv ; let tclvl' = pushTcLevel (tcl_tclvl env) + ; traceTc "pushLevelAndCaptureConstraints {" (ppr tclvl') ; (res, lie) <- setLclEnv (env { tcl_tclvl = tclvl' }) $ captureConstraints thing_inside + ; traceTc "pushLevelAndCaptureConstraints }" (ppr tclvl') ; return (tclvl', lie, res) } pushTcLevelM_ :: TcM a -> TcM a diff --git a/compiler/typecheck/TcSimplify.hs b/compiler/typecheck/TcSimplify.hs index 6ef62c8..c424a02 100644 --- a/compiler/typecheck/TcSimplify.hs +++ b/compiler/typecheck/TcSimplify.hs @@ -178,9 +178,7 @@ solveEqualities thing_inside -- vars to LiftedRep. This is needed to avoid #14991. ; traceTc "End solveEqualities }" empty - ; traceTc "reportAllUnsolved {" empty ; reportAllUnsolved final_wc - ; traceTc "reportAllUnsolved }" empty ; return result } -- | Simplify top-level constraints, but without reporting any unsolved @@ -514,9 +512,7 @@ simplifyDefault theta = do { traceTc "simplifyDefault" empty ; wanteds <- newWanteds DefaultOrigin theta ; unsolved <- runTcSDeriveds (solveWantedsAndDrop (mkSimpleWC wanteds)) - ; traceTc "reportUnsolved {" empty ; reportAllUnsolved unsolved - ; traceTc "reportUnsolved }" empty ; return () } ------------------ From git at git.haskell.org Fri Nov 16 16:53:58 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Nov 2018 16:53:58 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Further progress (304d65f) Message-ID: <20181116165358.579C43A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/304d65f21e2bff900bb8579c9eb02d67167b2594/ghc >--------------------------------------------------------------- commit 304d65f21e2bff900bb8579c9eb02d67167b2594 Author: Simon Peyton Jones Date: Mon Nov 5 17:43:08 2018 +0000 Further progress >--------------------------------------------------------------- 304d65f21e2bff900bb8579c9eb02d67167b2594 compiler/typecheck/TcHsSyn.hs | 28 ++++++----- compiler/typecheck/TcHsType.hs | 7 ++- compiler/typecheck/TcMType.hs | 95 ++++++++++++++++++++++++-------------- compiler/typecheck/TcRules.hs | 2 +- compiler/typecheck/TcSimplify.hs | 6 +-- compiler/typecheck/TcTyClsDecls.hs | 43 +++++++++-------- 6 files changed, 111 insertions(+), 70 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 304d65f21e2bff900bb8579c9eb02d67167b2594 From git at git.haskell.org Fri Nov 16 16:54:01 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Nov 2018 16:54:01 +0000 (UTC) Subject: [commit: ghc] wip/T15809: WIP on using level numbers for generalisation (2fa5bf1) Message-ID: <20181116165401.5C4A83A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/2fa5bf15b7e4ca347549ec6d3cd7483f3092e486/ghc >--------------------------------------------------------------- commit 2fa5bf15b7e4ca347549ec6d3cd7483f3092e486 Author: Simon Peyton Jones Date: Wed Oct 31 08:40:40 2018 +0000 WIP on using level numbers for generalisation This mostly works. So far I simply have a WARNING in quantifyTyVars which fires if the two methods (old "global-tyvars" and new "level-numbers") give different answers. Some modest but important refactoring along the way. Main thing that is still wrong: in instance declarations we are not skoelmising. Here's a partial patch to TcInstDcls, that /doesn't/ yet work -- Next, process any associated types. ; traceTc "tcLocalInstDecl" (ppr poly_ty) - ; tyfam_insts0 <- scopeTyVars InstSkol tyvars $ - mapAndRecoverM (tcTyFamInstDecl mb_info) ats - ; datafam_stuff <- scopeTyVars InstSkol tyvars $ - mapAndRecoverM (tcDataFamInstDecl mb_info) adts + ; (_subst, skol_tvs) <- tcInstSkolTyVars tyvars + ; (tyfam_insts0, datafam_stuff) + <- tcExtendNameTyVarEnv (map tyVarName tyvars `zip` skol_tvs) $ + do { tfs <- mapAndRecoverM (tcTyFamInstDecl mb_info) ats + ; dfs <- mapAndRecoverM (tcDataFamInstDecl mb_info) adts + ; return (tfs, dfs) } ; let (datafam_insts, m_deriv_infos) = unzip datafam_stuff >--------------------------------------------------------------- 2fa5bf15b7e4ca347549ec6d3cd7483f3092e486 compiler/typecheck/TcHsType.hs | 95 ++++++++++++++++++++++++------------ compiler/typecheck/TcMType.hs | 99 ++++++++++++++++++++++++++------------ compiler/typecheck/TcSimplify.hs | 19 +++++--- compiler/typecheck/TcTyClsDecls.hs | 86 ++++++++++++++++----------------- compiler/typecheck/TcValidity.hs | 12 ++--- 5 files changed, 192 insertions(+), 119 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 2fa5bf15b7e4ca347549ec6d3cd7483f3092e486 From git at git.haskell.org Fri Nov 16 16:54:04 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Nov 2018 16:54:04 +0000 (UTC) Subject: [commit: ghc] wip/T15809: More progress on using level numbers for gen (8707f2d) Message-ID: <20181116165404.5FBA23A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/8707f2d78f53c62e6528d5e702eb50371e426453/ghc >--------------------------------------------------------------- commit 8707f2d78f53c62e6528d5e702eb50371e426453 Author: Simon Peyton Jones Date: Wed Oct 31 15:00:16 2018 +0000 More progress on using level numbers for gen >--------------------------------------------------------------- 8707f2d78f53c62e6528d5e702eb50371e426453 compiler/typecheck/TcHsType.hs | 196 ++++++++++++++++++------------------- compiler/typecheck/TcInstDcls.hs | 11 +-- compiler/typecheck/TcMType.hs | 5 +- compiler/typecheck/TcSimplify.hs | 11 ++- compiler/typecheck/TcTyClsDecls.hs | 8 +- 5 files changed, 112 insertions(+), 119 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 8707f2d78f53c62e6528d5e702eb50371e426453 From git at git.haskell.org Fri Nov 16 16:54:07 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Nov 2018 16:54:07 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Further work on TyCon generalisation (d0772e7) Message-ID: <20181116165407.653673A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/d0772e7093da2acc9856062a5283df4551c7c046/ghc >--------------------------------------------------------------- commit d0772e7093da2acc9856062a5283df4551c7c046 Author: Simon Peyton Jones Date: Fri Nov 2 18:06:16 2018 +0000 Further work on TyCon generalisation >--------------------------------------------------------------- d0772e7093da2acc9856062a5283df4551c7c046 compiler/typecheck/TcHsType.hs | 109 +++++++++++---------- compiler/typecheck/TcMType.hs | 54 +++++++--- compiler/typecheck/TcRnTypes.hs | 8 +- compiler/typecheck/TcTyClsDecls.hs | 93 +++++------------- compiler/types/TyCoRep.hs | 16 ++- compiler/types/Type.hs | 2 +- testsuite/tests/dependent/should_compile/T14880.hs | 1 + .../tests/dependent/should_compile/T15743e.stderr | 6 +- .../tests/indexed-types/should_fail/T13972.stderr | 2 +- testsuite/tests/polykinds/T12593.stderr | 8 +- 10 files changed, 147 insertions(+), 152 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 d0772e7093da2acc9856062a5283df4551c7c046 From git at git.haskell.org Fri Nov 16 16:54:11 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Nov 2018 16:54:11 +0000 (UTC) Subject: [commit: ghc] wip/T15809: More progress on tcFamTyPats (e547695) Message-ID: <20181116165411.52D293A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/e5476950bdc82da3124f06dc9f099c2b61527542/ghc >--------------------------------------------------------------- commit e5476950bdc82da3124f06dc9f099c2b61527542 Author: Simon Peyton Jones Date: Mon Nov 12 17:21:55 2018 +0000 More progress on tcFamTyPats This fixes Trac #15740 >--------------------------------------------------------------- e5476950bdc82da3124f06dc9f099c2b61527542 compiler/typecheck/TcHsType.hs | 26 ++++++++++------- compiler/typecheck/TcMType.hs | 4 +-- compiler/typecheck/TcTyClsDecls.hs | 51 +++++++++++++++++++++++++++------ compiler/typecheck/TcValidity.hs | 23 ++++++++------- testsuite/tests/polykinds/T13985.stderr | 10 ++----- testsuite/tests/polykinds/T15740.hs | 15 ++++++++++ testsuite/tests/polykinds/T15740.stderr | 6 ++++ testsuite/tests/polykinds/T15740a.hs | 12 ++++++++ testsuite/tests/polykinds/all.T | 2 ++ 9 files changed, 109 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 e5476950bdc82da3124f06dc9f099c2b61527542 From git at git.haskell.org Fri Nov 16 16:54:14 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Nov 2018 16:54:14 +0000 (UTC) Subject: [commit: ghc] wip/T15809: More progress (6ddf2d1) Message-ID: <20181116165414.52D373A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/6ddf2d189e03f52c35a94b0a0da51e27be8f4d8f/ghc >--------------------------------------------------------------- commit 6ddf2d189e03f52c35a94b0a0da51e27be8f4d8f Author: Simon Peyton Jones Date: Wed Nov 7 07:52:16 2018 +0000 More progress A fixup in TcPatSyn >--------------------------------------------------------------- 6ddf2d189e03f52c35a94b0a0da51e27be8f4d8f compiler/typecheck/TcMType.hs | 48 ++++++++++++++++---------------- compiler/typecheck/TcPatSyn.hs | 56 +++++++++++++++++++++++++++++++------- compiler/typecheck/TcSimplify.hs | 7 +++-- compiler/typecheck/TcTyClsDecls.hs | 1 + 4 files changed, 75 insertions(+), 37 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 6ddf2d189e03f52c35a94b0a0da51e27be8f4d8f From git at git.haskell.org Fri Nov 16 16:54:17 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Nov 2018 16:54:17 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Comments and alpha-renaming (0cd583c) Message-ID: <20181116165417.4B9C53A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/0cd583c281506dab51ff00d3672e737b6c648868/ghc >--------------------------------------------------------------- commit 0cd583c281506dab51ff00d3672e737b6c648868 Author: Simon Peyton Jones Date: Wed Nov 7 23:26:05 2018 +0000 Comments and alpha-renaming >--------------------------------------------------------------- 0cd583c281506dab51ff00d3672e737b6c648868 compiler/typecheck/TcHsType.hs | 2 -- compiler/typecheck/TcInstDcls.hs | 10 +++++----- compiler/typecheck/TcMType.hs | 2 +- compiler/typecheck/TcSimplify.hs | 7 ++++--- 4 files changed, 10 insertions(+), 11 deletions(-) diff --git a/compiler/typecheck/TcHsType.hs b/compiler/typecheck/TcHsType.hs index 2ce23e7..dd2995e 100644 --- a/compiler/typecheck/TcHsType.hs +++ b/compiler/typecheck/TcHsType.hs @@ -1744,7 +1744,6 @@ kcImplicitTKBndrs = kcImplicitTKBndrsX newFlexiKindedTyVarTyVar -- | Bring implicitly quantified type/kind variables into scope during -- kind checking. The returned TcTyVars are in 1-1 correspondence --- with the names passed in. --- Note [Use TyVarTvs in kind-checking pass] in TcTyClsDecls. kcImplicitTKBndrsX :: (Name -> TcM TcTyVar) -- new_tv function -> [Name] -- of the vars -> TcM a @@ -2065,7 +2064,6 @@ kcLookupTcTyCon nm -- Never emits constraints, though the thing_inside might. kcTyClTyVars :: Name -> TcM a -> TcM a kcTyClTyVars tycon_name thing_inside - -- See Note [Use TyVarTvs in kind-checking pass] in TcTyClsDecls = do { tycon <- kcLookupTcTyCon tycon_name ; tcExtendNameTyVarEnv (tcTyConScopedTyVars tycon) $ thing_inside } diff --git a/compiler/typecheck/TcInstDcls.hs b/compiler/typecheck/TcInstDcls.hs index 84f43e9..63c565d 100644 --- a/compiler/typecheck/TcInstDcls.hs +++ b/compiler/typecheck/TcInstDcls.hs @@ -465,14 +465,14 @@ tcLocalInstDecl (L _ (XInstDecl _)) = panic "tcLocalInstDecl" tcClsInstDecl :: LClsInstDecl GhcRn -> TcM ([InstInfo GhcRn], [FamInst], [DerivInfo]) -- The returned DerivInfos are for any associated data families -tcClsInstDecl (L loc (ClsInstDecl { cid_poly_ty = poly_ty, cid_binds = binds +tcClsInstDecl (L loc (ClsInstDecl { cid_poly_ty = hs_ty, cid_binds = binds , cid_sigs = uprags, cid_tyfam_insts = ats , cid_overlap_mode = overlap_mode , cid_datafam_insts = adts })) = setSrcSpan loc $ - addErrCtxt (instDeclCtxt1 poly_ty) $ + addErrCtxt (instDeclCtxt1 hs_ty) $ do { (tyvars, theta, clas, inst_tys) - <- tcHsClsInstType (InstDeclCtxt False) poly_ty + <- tcHsClsInstType (InstDeclCtxt False) hs_ty -- NB: tcHsClsInstType does checkValidInstance ; tcExtendTyVarEnv tyvars $ @@ -481,7 +481,7 @@ tcClsInstDecl (L loc (ClsInstDecl { cid_poly_ty = poly_ty, cid_binds = binds mb_info = Just (clas, tyvars, mini_env) -- Next, process any associated types. - ; traceTc "tcLocalInstDecl" (ppr poly_ty) + ; traceTc "tcLocalInstDecl" (ppr hs_ty) ; tyfam_insts0 <- mapAndRecoverM (tcTyFamInstDecl mb_info) ats ; datafam_stuff <- mapAndRecoverM (tcDataFamInstDecl mb_info) adts ; let (datafam_insts, m_deriv_infos) = unzip datafam_stuff @@ -500,7 +500,7 @@ tcClsInstDecl (L loc (ClsInstDecl { cid_poly_ty = poly_ty, cid_binds = binds -- Finally, construct the Core representation of the instance. -- (This no longer includes the associated types.) - ; dfun_name <- newDFunName clas inst_tys (getLoc (hsSigType poly_ty)) + ; dfun_name <- newDFunName clas inst_tys (getLoc (hsSigType hs_ty)) -- Dfun location is that of instance *header* ; ispec <- newClsInst (fmap unLoc overlap_mode) dfun_name tyvars theta diff --git a/compiler/typecheck/TcMType.hs b/compiler/typecheck/TcMType.hs index 8192f75..9edad0f 100644 --- a/compiler/typecheck/TcMType.hs +++ b/compiler/typecheck/TcMType.hs @@ -1499,7 +1499,7 @@ defaultTyVar default_kind tv -- Do not default TyVarTvs. Doing so would violate the invariants -- on TyVarTvs; see Note [Signature skolems] in TcType. -- Trac #13343 is an example; #14555 is another - -- See Note [Kind generalisation and TyVarTvs] + -- See Note [Inferring kinds for type declarations] in TcTyClsDecls = return False diff --git a/compiler/typecheck/TcSimplify.hs b/compiler/typecheck/TcSimplify.hs index 750b621..e1a3532 100644 --- a/compiler/typecheck/TcSimplify.hs +++ b/compiler/typecheck/TcSimplify.hs @@ -2008,9 +2008,10 @@ promoteTyVarTcS tv defaultTyVarTcS :: TcTyVar -> TcS Bool defaultTyVarTcS the_tv | isRuntimeRepVar the_tv - , not (isTyVarTyVar the_tv) -- TyVarTvs should only be unified with a tyvar - -- never with a type; c.f. TcMType.defaultTyVar - -- See Note [Kind generalisation and TyVarTvs] + , not (isTyVarTyVar the_tv) + -- TyVarTvs should only be unified with a tyvar + -- never with a type; c.f. TcMType.defaultTyVar + -- and Note [Inferring kinds for type declarations] in TcTyClsDecls = do { traceTcS "defaultTyVarTcS RuntimeRep" (ppr the_tv) ; unifyTyVar the_tv liftedRepTy ; return True } From git at git.haskell.org Fri Nov 16 16:54:20 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Nov 2018 16:54:20 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Start to eliminate tcFamTyPats (4d6a157) Message-ID: <20181116165420.427593A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/4d6a157ad87404588b080e7f17e5f4bc3ebd0fd2/ghc >--------------------------------------------------------------- commit 4d6a157ad87404588b080e7f17e5f4bc3ebd0fd2 Author: Simon Peyton Jones Date: Mon Nov 12 13:41:33 2018 +0000 Start to eliminate tcFamTyPats >--------------------------------------------------------------- 4d6a157ad87404588b080e7f17e5f4bc3ebd0fd2 compiler/typecheck/TcHsType.hs | 1 + compiler/typecheck/TcTyClsDecls.hs | 20 ++++++++------------ 2 files changed, 9 insertions(+), 12 deletions(-) diff --git a/compiler/typecheck/TcHsType.hs b/compiler/typecheck/TcHsType.hs index 7f637b7..fe8c1a0 100644 --- a/compiler/typecheck/TcHsType.hs +++ b/compiler/typecheck/TcHsType.hs @@ -21,6 +21,7 @@ module TcHsType ( UserTypeCtxt(..), bindImplicitTKBndrs_Skol, bindImplicitTKBndrs_Q_Skol, bindExplicitTKBndrs_Skol, bindExplicitTKBndrs_Q_Skol, + ContextKind(..), -- Type checking type and class decls kcLookupTcTyCon, kcTyClTyVars, tcTyClTyVars, diff --git a/compiler/typecheck/TcTyClsDecls.hs b/compiler/typecheck/TcTyClsDecls.hs index 5b5d858..b9227de 100644 --- a/compiler/typecheck/TcTyClsDecls.hs +++ b/compiler/typecheck/TcTyClsDecls.hs @@ -1760,6 +1760,7 @@ tcTyFamInstEqn :: TcTyCon -> Maybe ClsInstInfo -> LTyFamInstEqn GhcRn -- (typechecked here) have TyFamInstEqns +{- tcTyFamInstEqn fam_tc mb_clsinfo (L loc (HsIB { hsib_ext = imp_vars , hsib_body = FamEqn { feqn_tycon = L _ eqn_tc_name @@ -1780,8 +1781,8 @@ tcTyFamInstEqn fam_tc mb_clsinfo ; return (mkCoAxBranch tvs' [] pats' rhs_ty' (map (const Nominal) tvs') loc) } +-} -{- tcTyFamInstEqn fam_tc mb_clsinfo eqn@(L loc (HsIB { hsib_ext = imp_vars , hsib_body = FamEqn { feqn_tycon = L _ eqn_tc_name @@ -1790,12 +1791,12 @@ tcTyFamInstEqn fam_tc mb_clsinfo , feqn_rhs = hs_ty }})) = ASSERT( getName fam_tc == eqn_tc_name ) setSrcSpan loc $ - do { traceTc "tcTyFamInstEqn {" (ppr eqn) - ; (imp_tvs, (exp_tvs, ((pats, rhs_ty)))) + do { traceTc "tcTyFamInstEqn {" (ppr eqn_tc_name <+> ppr hs_pats) + ; (_imp_tvs, (_exp_tvs, ((pats, rhs_ty)))) <- pushTcLevelM_ $ solveEqualities $ bindImplicitTKBndrs_Q_Skol imp_vars $ - bindExplicitTKBndrs_Q_Skol (mb_expl_bndrs `orElse` []) $ + bindExplicitTKBndrs_Q_Skol AnyKind (mb_expl_bndrs `orElse` []) $ do { let fam_name = tyConName fam_tc lhs_fun = L loc (HsTyVar noExt NotPromoted (L loc fam_name)) @@ -1808,21 +1809,16 @@ tcTyFamInstEqn fam_tc mb_clsinfo ; rhs_ty <- tcCheckLHsType hs_ty res_kind ; return (pats, rhs_ty) } - ; imp_tvs <- zonkAndScopedSort imp_tvs - ; let spec_req_tkvs = imp_tvs ++ exp_tvs - ; dvs <- candidateQTyVarsOfKinds $ - typeKind rhs_ty : map tyVarKind (spec_req_tkvs) - ; let final_dvs = dvs `delCandidates` spec_req_tkvs - ; inferred_kvs <- quantifyTyVars emptyVarSet final_dvs + ; dvs <- candidateQTyVarsOfTypes (rhs_ty : pats) + ; qtkvs <- quantifyTyVars emptyVarSet dvs - ; (ze, tvs') <- zonkTyBndrs (inferred_kvs ++ spec_req_tkvs) + ; (ze, tvs') <- zonkTyBndrs qtkvs ; pats' <- zonkTcTypesToTypesX ze pats ; rhs_ty' <- zonkTcTypeToTypeX ze rhs_ty ; traceTc "tcTyFamInstEqn }" (ppr fam_tc <+> pprTyVars tvs') ; return (mkCoAxBranch tvs' [] pats' rhs_ty' (map (const Nominal) tvs') loc) } --} tcTyFamInstEqn _ _ (L _ (XHsImplicitBndrs _)) = panic "tcTyFamInstEqn" From git at git.haskell.org Fri Nov 16 16:54:23 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Nov 2018 16:54:23 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Comemnts only (9a902e8) Message-ID: <20181116165423.39D283A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/9a902e8fbc9ae25996bfabf6849b7543f2f17236/ghc >--------------------------------------------------------------- commit 9a902e8fbc9ae25996bfabf6849b7543f2f17236 Author: Simon Peyton Jones Date: Wed Nov 7 11:40:50 2018 +0000 Comemnts only >--------------------------------------------------------------- 9a902e8fbc9ae25996bfabf6849b7543f2f17236 compiler/typecheck/TcTyClsDecls.hs | 74 +++++++++++++++++++++++--------------- 1 file changed, 46 insertions(+), 28 deletions(-) diff --git a/compiler/typecheck/TcTyClsDecls.hs b/compiler/typecheck/TcTyClsDecls.hs index 3f90c42..cefc9ca 100644 --- a/compiler/typecheck/TcTyClsDecls.hs +++ b/compiler/typecheck/TcTyClsDecls.hs @@ -637,37 +637,55 @@ generaliseTcTyCon tc {- Note [Required, Specified, and Inferred for types] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -We have some design choices in how we classify the tyvars bound -in a type declaration. (Here, I use "type" to refer to any TyClDecl.) -Much of the debate is memorialized in #15743. This Note documents -the final conclusion. - -First, a reminder: - * a Required argument is one that must be provided at every call site - * a Specified argument is one that can be inferred at call sites, but - may be instantiated with visible type application - * an Inferred argument is one that must be inferred at call sites; it - is unavailable for use with visible type application. - -Why have Inferred at all? Because we just can't make user-facing promises -about the ordering of some variables. These might swizzle around even between -minor released. By forbidding visible type application, we ensure users -aren't caught unawares. See also -Note [VarBndrs, TyCoVarBinders, TyConBinders, and visibility] in TyCoRep. - -When inferring the ordering of variables (that is, for those -variables that he user has not specified the order with an explicit `forall`) -we use the following order: - - 1. Inferred variables from an enclosing class (associated types only) - 2. Specified variables from an enclosing class (associated types only) - 3. Inferred variables not from an enclosing class - 4. Specified variables not from an enclosing class - 5. Required variables before a top-level :: - 6. All variables after a top-level :: +Each forall'd type variable in a type or kind is one of + + * Required: an argument must be provided at every call site + + * Specified: the argument can be inferred at call sites, but + may be instantiated with visible type/kind application + + * Inferred: the must be inferred at call sites; it + is unavailable for use with visible type/kind application. + +Why have Inferred at all? Because we just can't make user-facing +promises about the ordering of some variables. These might swizzle +around even between minor released. By forbidding visible type +application, we ensure users aren't caught unawares. + +Go read Note [VarBndrs, TyCoVarBinders, TyConBinders, and visibility] in TyCoRep. + +The question for this Note is this: + given a TyClDecl, how are its quantified type variables classified? +Much of the debate is memorialized in #15743. + +Here is our design choice. When inferring the ordering of variables +for a TyCl declaration (that is, for those variables that he user +has not specified the order with an explicit `forall`), we use the +following order: + + 1. Inferred variables + 2. Specified variables; in the left-to-right order in which + the user wrote them, modified by scopedSort (see below) + to put them in depdendency order. + 3. Required variables before a top-level :: + 4. All variables after a top-level :: If this ordering does not make a valid telescope, we reject the definition. +Example: + data SameKind :: k -> k -> * + data X a (b :: SameKind a b) (c :: k) d + +For X: + - a, b, c, d are Required; they are explicitly listed by the user + as the positional arguments of X + - k is Specified; it appears explicitly in a kind signature + - k2, the kind of d, is Inferred; it is not mentioned explicitly at all + +Putting variables in the order Inferred, Specified, Required gives us + Inferred: k2 + Specified: k (a ::kb + This idea is implemented in the generalise function within kcTyClGroup (for declarations without CUSKs), and in kcLHsQTyVars (for declarations with CUSKs). Note that neither definition worries about point (6) above, as this From git at git.haskell.org Fri Nov 16 16:54:26 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Nov 2018 16:54:26 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Get rid of kcLHsQTyVarBndrs (9f41010) Message-ID: <20181116165426.382593A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/9f410109988546c033553cc644d4d9887893812c/ghc >--------------------------------------------------------------- commit 9f410109988546c033553cc644d4d9887893812c Author: Simon Peyton Jones Date: Mon Nov 12 12:08:33 2018 +0000 Get rid of kcLHsQTyVarBndrs >--------------------------------------------------------------- 9f410109988546c033553cc644d4d9887893812c compiler/typecheck/TcHsType.hs | 289 +++++++++++++++++++-------------------- compiler/typecheck/TcMType.hs | 2 +- compiler/typecheck/TcValidity.hs | 21 --- 3 files changed, 138 insertions(+), 174 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 9f410109988546c033553cc644d4d9887893812c From git at git.haskell.org Fri Nov 16 16:54:29 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Nov 2018 16:54:29 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Finally done (a7a6672) Message-ID: <20181116165429.39C9A3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/a7a6672ec339cbe366525cd8b91f4817ee420cf3/ghc >--------------------------------------------------------------- commit a7a6672ec339cbe366525cd8b91f4817ee420cf3 Author: Simon Peyton Jones Date: Wed Nov 7 12:51:32 2018 +0000 Finally done >--------------------------------------------------------------- a7a6672ec339cbe366525cd8b91f4817ee420cf3 compiler/typecheck/TcHsType.hs | 128 +++----------- compiler/typecheck/TcMType.hs | 63 +++---- compiler/typecheck/TcTyClsDecls.hs | 188 ++++++++++++++++----- compiler/typecheck/TcValidity.hs | 77 ++++++--- .../dependent/should_fail/BadTelescope.stderr | 7 +- .../dependent/should_fail/BadTelescope3.stderr | 6 +- .../dependent/should_fail/BadTelescope4.stderr | 13 +- .../tests/dependent/should_fail/T13895.stderr | 37 +--- .../tests/dependent/should_fail/T14066f.stderr | 6 +- .../tests/dependent/should_fail/T14066g.stderr | 8 +- .../tests/dependent/should_fail/T15591b.stderr | 9 +- .../tests/dependent/should_fail/T15591c.stderr | 9 +- .../tests/dependent/should_fail/T15743c.stderr | 13 +- .../tests/dependent/should_fail/T15743d.stderr | 13 +- testsuite/tests/ghci/scripts/T15591.hs | 9 +- testsuite/tests/ghci/scripts/T15591.stdout | 6 +- 16 files changed, 312 insertions(+), 280 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 a7a6672ec339cbe366525cd8b91f4817ee420cf3 From git at git.haskell.org Fri Nov 16 16:54:32 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Nov 2018 16:54:32 +0000 (UTC) Subject: [commit: ghc] wip/T15809: More progress (1284033) Message-ID: <20181116165432.3E0A33A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/128403374fdf31058c0c5b248b9f939105d6acc9/ghc >--------------------------------------------------------------- commit 128403374fdf31058c0c5b248b9f939105d6acc9 Author: Simon Peyton Jones Date: Tue Nov 6 17:44:25 2018 +0000 More progress >--------------------------------------------------------------- 128403374fdf31058c0c5b248b9f939105d6acc9 compiler/typecheck/TcHsType.hs | 290 +++++++++------------ compiler/typecheck/TcMType.hs | 122 ++++----- compiler/typecheck/TcTyClsDecls.hs | 229 ++++++++-------- compiler/typecheck/TcValidity.hs | 19 +- testsuite/tests/dependent/should_compile/T14880.hs | 1 - .../tests/dependent/should_compile/T15743e.stderr | 2 +- testsuite/tests/ghci/scripts/T15591.hs | 5 + testsuite/tests/ghci/scripts/T15743b.stdout | 2 +- testsuite/tests/ghci/scripts/T7873.stderr | 2 +- .../tests/indexed-types/should_fail/T13972.stderr | 2 +- testsuite/tests/polykinds/T11203.stderr | 2 +- testsuite/tests/polykinds/T11821a.stderr | 2 +- testsuite/tests/polykinds/T15592b.stderr | 2 +- .../tests/typecheck/should_fail/T13983.stderr | 2 +- testsuite/tests/typecheck/should_fail/T2688.stderr | 6 +- 15 files changed, 318 insertions(+), 370 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 128403374fdf31058c0c5b248b9f939105d6acc9 From git at git.haskell.org Fri Nov 16 16:54:35 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Nov 2018 16:54:35 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Combine kcImplicitTKBndrs and tcImplicitTKBndrs (b8d7bee) Message-ID: <20181116165435.4644A3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/b8d7bee6fff2222a1e28570a0513666ef71b9d12/ghc >--------------------------------------------------------------- commit b8d7bee6fff2222a1e28570a0513666ef71b9d12 Author: Simon Peyton Jones Date: Mon Nov 12 08:30:33 2018 +0000 Combine kcImplicitTKBndrs and tcImplicitTKBndrs Based on a conversation with Richard on Friday, this patch * Abolishes the distinction between kcImplicitTKBndrs and tcImplicitTKBndrs; now it is bindImplicitTKBndrs * Same for kc/tcExplicitTKBndrs * tcImplicitTKBndrs no longer does a solveLocalEqualities and sort; the caller does that Much nicer. Not quite working yet though >--------------------------------------------------------------- b8d7bee6fff2222a1e28570a0513666ef71b9d12 compiler/typecheck/TcBackpack.hs | 2 +- compiler/typecheck/TcDerivInfer.hs | 2 +- compiler/typecheck/TcHsType.hs | 238 +++++++++------------ compiler/typecheck/TcInstDcls.hs | 2 +- compiler/typecheck/TcRnMonad.hs | 4 +- compiler/typecheck/TcRules.hs | 34 ++- compiler/typecheck/TcSMonad.hs | 4 +- compiler/typecheck/TcSigs.hs | 46 ++-- compiler/typecheck/TcSimplify.hs | 18 +- compiler/typecheck/TcSplice.hs | 4 +- compiler/typecheck/TcTyClsDecls.hs | 205 +++++++++++------- compiler/typecheck/TcUnify.hs | 33 +-- testsuite/tests/dependent/should_compile/T13910.hs | 10 +- .../tests/indexed-types/should_compile/T12369.hs | 10 + testsuite/tests/indexed-types/should_fail/T7938.hs | 6 +- 15 files changed, 331 insertions(+), 287 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 b8d7bee6fff2222a1e28570a0513666ef71b9d12 From git at git.haskell.org Fri Nov 16 16:54:38 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Nov 2018 16:54:38 +0000 (UTC) Subject: [commit: ghc] wip/T15809: More progress (dfd6617) Message-ID: <20181116165438.4C2693A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/dfd66170c59a6f8dc1ba46c4187a5ccec0b4f546/ghc >--------------------------------------------------------------- commit dfd66170c59a6f8dc1ba46c4187a5ccec0b4f546 Author: Simon Peyton Jones Date: Tue Nov 6 08:55:37 2018 +0000 More progress >--------------------------------------------------------------- dfd66170c59a6f8dc1ba46c4187a5ccec0b4f546 compiler/typecheck/TcEnv.hs | 2 +- compiler/typecheck/TcHsSyn.hs | 7 ++++- compiler/typecheck/TcHsType.hs | 4 --- compiler/typecheck/TcMType.hs | 14 ++++----- compiler/typecheck/TcRnDriver.hs | 2 +- compiler/typecheck/TcSimplify.hs | 2 +- compiler/typecheck/TcTyClsDecls.hs | 61 +++++++++++++++++++++++++------------- 7 files changed, 57 insertions(+), 35 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc dfd66170c59a6f8dc1ba46c4187a5ccec0b4f546 From git at git.haskell.org Fri Nov 16 16:54:41 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Nov 2018 16:54:41 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Comments only (26c2ec3) Message-ID: <20181116165441.4097E3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/26c2ec3354546f377017623da934fb2667c1b727/ghc >--------------------------------------------------------------- commit 26c2ec3354546f377017623da934fb2667c1b727 Author: Simon Peyton Jones Date: Fri Nov 9 17:46:05 2018 +0000 Comments only >--------------------------------------------------------------- 26c2ec3354546f377017623da934fb2667c1b727 compiler/typecheck/TcMType.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/compiler/typecheck/TcMType.hs b/compiler/typecheck/TcMType.hs index 9edad0f..6d9f3ca 100644 --- a/compiler/typecheck/TcMType.hs +++ b/compiler/typecheck/TcMType.hs @@ -662,7 +662,8 @@ but this restriction was dropped, and ScopedTypeVariables can now refer to full types (GHC Proposal 29). The remaining uses of newTyVarTyVars are -* in kind signatures, see Note [Kind generalisation and TyVarTvs] +* In kind signatures, see + TcTyClsDecls Note [Inferring kinds for type declarations] and Note [Use TyVarTvs in kind-checking pass] * in partial type signatures, see Note [Quantified variables in partial type signatures] -} From git at git.haskell.org Fri Nov 16 16:54:44 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Nov 2018 16:54:44 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Wibbles (9a854cc) Message-ID: <20181116165444.364443A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/9a854cc33ceb3ad8adf7fc372d1c9053b739ead2/ghc >--------------------------------------------------------------- commit 9a854cc33ceb3ad8adf7fc372d1c9053b739ead2 Author: Simon Peyton Jones Date: Mon Nov 12 17:43:48 2018 +0000 Wibbles >--------------------------------------------------------------- 9a854cc33ceb3ad8adf7fc372d1c9053b739ead2 testsuite/tests/indexed-types/should_fail/T7536.stderr | 8 ++++---- testsuite/tests/indexed-types/should_fail/T7938.hs | 6 ++---- testsuite/tests/indexed-types/should_fail/T7938.stderr | 2 +- 3 files changed, 7 insertions(+), 9 deletions(-) diff --git a/testsuite/tests/indexed-types/should_fail/T7536.stderr b/testsuite/tests/indexed-types/should_fail/T7536.stderr index 9e7ed30..34a393e 100644 --- a/testsuite/tests/indexed-types/should_fail/T7536.stderr +++ b/testsuite/tests/indexed-types/should_fail/T7536.stderr @@ -1,5 +1,5 @@ -T7536.hs:8:15: - Family instance purports to bind type variable ‘a’ - but the real LHS (expanding synonyms) is: TF Int = ... - In the type instance declaration for ‘TF’ +T7536.hs:8:15: error: + • LHS of family instance fails to bind type variable ‘a’ + The real LHS (expanding synonyms) is: TF Int + • In the type instance declaration for ‘TF’ diff --git a/testsuite/tests/indexed-types/should_fail/T7938.hs b/testsuite/tests/indexed-types/should_fail/T7938.hs index f1e8266..246015d 100644 --- a/testsuite/tests/indexed-types/should_fail/T7938.hs +++ b/testsuite/tests/indexed-types/should_fail/T7938.hs @@ -8,7 +8,5 @@ data KProxy (a :: *) = KP class Foo (a :: k1) (b :: k2) where type Bar a --- instance Foo (a :: k1) (b :: k2) where --- type Bar a = (KP :: KProxy k2) - --- \ No newline at end of file +instance Foo (a :: k1) (b :: k2) where + type Bar a = (KP :: KProxy k2) diff --git a/testsuite/tests/indexed-types/should_fail/T7938.stderr b/testsuite/tests/indexed-types/should_fail/T7938.stderr index 890be7b..5751c4e 100644 --- a/testsuite/tests/indexed-types/should_fail/T7938.stderr +++ b/testsuite/tests/indexed-types/should_fail/T7938.stderr @@ -1,6 +1,6 @@ T7938.hs:12:17: error: - • Expected a type, but ‘KP :: KProxy k2’ has kind ‘KProxy k4’ + • Expected a type, but ‘KP :: KProxy k2’ has kind ‘KProxy k2’ • In the type ‘(KP :: KProxy k2)’ In the type instance declaration for ‘Bar’ In the instance declaration for ‘Foo (a :: k1) (b :: k2)’ From git at git.haskell.org Fri Nov 16 16:54:47 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Nov 2018 16:54:47 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Progress (3f214ea) Message-ID: <20181116165447.2D2063A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/3f214eae9a4fe6cfce7377d28bfc99634ba34c5c/ghc >--------------------------------------------------------------- commit 3f214eae9a4fe6cfce7377d28bfc99634ba34c5c Author: Simon Peyton Jones Date: Fri Nov 9 18:11:25 2018 +0000 Progress Allocate result kind outside tcImplicit in tc_hs_sig_type_and_gen Plus comments In flight.. may not build (but it's a wip/ branch) >--------------------------------------------------------------- 3f214eae9a4fe6cfce7377d28bfc99634ba34c5c compiler/typecheck/TcHsType.hs | 49 +++++++++++++++++++++--------------------- compiler/typecheck/TcMType.hs | 18 ++++------------ 2 files changed, 29 insertions(+), 38 deletions(-) diff --git a/compiler/typecheck/TcHsType.hs b/compiler/typecheck/TcHsType.hs index dd2995e..7f5d4ff 100644 --- a/compiler/typecheck/TcHsType.hs +++ b/compiler/typecheck/TcHsType.hs @@ -229,19 +229,15 @@ tc_hs_sig_type_and_gen skol_info hs_sig_type ctxt_kind | HsIB { hsib_ext = sig_vars, hsib_body = hs_ty } <- hs_sig_type = do { (_inner_lvl, wanted, (tkvs, ty)) <- pushLevelAndCaptureConstraints $ - tcImplicitTKBndrs skol_info sig_vars $ - -- tcImplicitTKBndrs does a solveLocalEqualities - do { kind <- case ctxt_kind of + do { -- See Note [Levels and generalisation] + res_kind <- case ctxt_kind of TheKind k -> return k AnyKind -> newMetaKindVar OpenKind -> newOpenTypeKind - -- The kind is checked by checkValidType, and isn't necessarily - -- of kind * in a Template Haskell quote eg [t| Maybe |] - ; tc_lhs_type typeLevelMode hs_ty kind } - -- Any remaining variables (unsolved in the solveLocalEqualities - -- in the tcImplicitTKBndrs) should be in the global tyvars, - -- and therefore won't be quantified over + ; tcImplicitTKBndrs skol_info sig_vars $ + -- tcImplicitTKBndrs does a solveLocalEqualities + tc_lhs_type typeLevelMode hs_ty res_kind } ; let ty1 = mkSpecForAllTys tkvs ty ; kvs <- kindGeneralizeLocal wanted ty1 @@ -1467,20 +1463,6 @@ To avoid the double-zonk, we do two things: 2. When we are generalizing: kindGeneralize does not require a zonked type -- it zonks as it gathers free variables. So this way effectively sidesteps step 3. - -Note [TcLevel for CUSKs] -~~~~~~~~~~~~~~~~~~~~~~~~ -In getInitialKinds we are at level 1, busy making unification -variables over which we will subsequently generalise. - -But when we find a CUSK we want to jump back to top level (0) -because that's the right starting point for a completee, -stand-alone kind signature. - -More precisely, we want to make level-1 skolems, because -the end up as the TyConBinders of the TyCon, and are brought -into scope when we type-check the body of the type declaration -(in tcTyClDecl). -} tcWildCardBinders :: [Name] @@ -2003,7 +1985,26 @@ kindGeneralizeLocal wanted kind_or_type ; quantifyTyVars mono_tvs dvs } -{- +{- Note [Levels and generalisation] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Consider + f x = e +with no type signature. We are currently at level i. +We must + * Push the level to level (i+1) + * Allocate a fresh alpha[i+1] for the result type + * Check that e :: alpha[i+1], gathering constraint WC + * Solve WC as far as possible + * Zonking the result type alpha[i+1], say to beta[i-1] -> gamma[i] + * Find the free variables with level > i, in this case gamma[i] + * Skolemise those free variables and quantify over them, giving + f :: forall g. beta[i-1] -> g + * Emit the residiual constraint wrapped in an implication for g, + thus forall g. WC + +All of this happens for types too. Consider + f :: Int -> (forall a. Proxy a -> Int) + Note [Kind generalisation] ~~~~~~~~~~~~~~~~~~~~~~~~~~ We do kind generalisation only at the outer level of a type signature. diff --git a/compiler/typecheck/TcMType.hs b/compiler/typecheck/TcMType.hs index 6d9f3ca..a1cdf24 100644 --- a/compiler/typecheck/TcMType.hs +++ b/compiler/typecheck/TcMType.hs @@ -1342,16 +1342,6 @@ to be later converted to a list in a deterministic order. For more information about deterministic sets see Note [Deterministic UniqFM] in UniqDFM. - - ---------------- Note to tidy up -------- -Can we quantify over a non-unification variable? Sadly yes (Trac #15991b) - class C2 (a :: Type) (b :: Proxy a) (c :: Proxy b) where - type T4 a c - -When we come to T4 we have in Inferred b; but it is a skolem -from the (fully settled) C2. - -} quantifyTyVars @@ -1444,10 +1434,10 @@ quantifyTyVars gbl_tvs = return Nothing -- this can happen for a covar that's associated with -- a coercion hole. Test case: typecheck/should_compile/T2494 - | not (isTcTyVar tkv) - = WARN( True, text "quantifying over a TyVar" <+> ppr tkv) - return (Just tkv) -- For associated types, we have the class variables - -- in scope, and they are TyVars not TcTyVars + | not (isTcTyVar tkv) -- I don't think this can ever happen. + -- Hence the assert + = ASSERT2( False, text "quantifying over a TyVar" <+> ppr tkv) + return (Just tkv) | otherwise = do { deflt_done <- defaultTyVar default_kind tkv From git at git.haskell.org Fri Nov 16 16:54:50 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Nov 2018 16:54:50 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Better validity checks, simplification (d027b8c) Message-ID: <20181116165450.2FD173A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/d027b8c87ec613464d4f3a3ad7088c645f8ac620/ghc >--------------------------------------------------------------- commit d027b8c87ec613464d4f3a3ad7088c645f8ac620 Author: Simon Peyton Jones Date: Thu Nov 15 23:29:34 2018 +0000 Better validity checks, simplification >--------------------------------------------------------------- d027b8c87ec613464d4f3a3ad7088c645f8ac620 compiler/typecheck/TcGenDeriv.hs | 3 +- compiler/typecheck/TcHsType.hs | 66 +++--- compiler/typecheck/TcInstDcls.hs | 43 +++- compiler/typecheck/TcTyClsDecls.hs | 223 ++++++++++++++++++- compiler/typecheck/TcValidity.hs | 238 ++------------------- .../should_fail/ExplicitForAllFams4b.stderr | 63 ++++-- .../indexed-types/should_fail/SimpleFail2a.stderr | 2 +- .../tests/indexed-types/should_fail/T14045a.stderr | 2 +- testsuite/tests/polykinds/T13985.hs | 1 + testsuite/tests/polykinds/T13985.stderr | 10 +- 10 files changed, 338 insertions(+), 313 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 d027b8c87ec613464d4f3a3ad7088c645f8ac620 From git at git.haskell.org Fri Nov 16 16:54:53 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Nov 2018 16:54:53 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Finally, validate-clean (fecafee) Message-ID: <20181116165453.34A7E3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/fecafeee5ecbed91fb397da83cc8b9e6dbffa03f/ghc >--------------------------------------------------------------- commit fecafeee5ecbed91fb397da83cc8b9e6dbffa03f Author: Simon Peyton Jones Date: Fri Nov 16 12:03:59 2018 +0000 Finally, validate-clean Except for polykinds/T14846, where there is an extra error message. I actually tnink it's correct, but have not checked yet. >--------------------------------------------------------------- fecafeee5ecbed91fb397da83cc8b9e6dbffa03f compiler/typecheck/TcBinds.hs | 24 ---- compiler/typecheck/TcClassDcl.hs | 3 - compiler/typecheck/TcDeriv.hs | 3 - compiler/typecheck/TcEnv.hs | 8 -- compiler/typecheck/TcHsType.hs | 87 +++++++++----- compiler/typecheck/TcInstDcls.hs | 81 ++++++------- compiler/typecheck/TcPat.hs | 2 +- compiler/typecheck/TcTyClsDecls.hs | 132 +++++++++++++-------- compiler/types/TyCoRep.hs | 7 +- .../indexed-types/should_fail/SimpleFail9.stderr | 2 +- .../tests/indexed-types/should_fail/T10817.stderr | 9 +- .../tests/indexed-types/should_fail/T10899.stderr | 3 +- testsuite/tests/polykinds/T8616.stderr | 9 ++ testsuite/tests/printer/Ppr040.hs | 10 +- 14 files changed, 202 insertions(+), 178 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 fecafeee5ecbed91fb397da83cc8b9e6dbffa03f From git at git.haskell.org Fri Nov 16 16:54:56 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Nov 2018 16:54:56 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Data family instances working, I think (461e8dc) Message-ID: <20181116165456.3516B3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/461e8dca1262d3751f934d05fb3ceded01d8c7b8/ghc >--------------------------------------------------------------- commit 461e8dca1262d3751f934d05fb3ceded01d8c7b8 Author: Simon Peyton Jones Date: Wed Nov 14 11:36:22 2018 +0000 Data family instances working, I think >--------------------------------------------------------------- 461e8dca1262d3751f934d05fb3ceded01d8c7b8 compiler/typecheck/TcInstDcls.hs | 154 +++++++++++++++++++++++++++++++++++++ compiler/typecheck/TcTyClsDecls.hs | 68 ++++++++-------- 2 files changed, 191 insertions(+), 31 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 461e8dca1262d3751f934d05fb3ceded01d8c7b8 From git at git.haskell.org Fri Nov 16 16:54:59 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Nov 2018 16:54:59 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Print tycon arity in -ddump-types (c724f92) Message-ID: <20181116165459.34A853A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/c724f929b67a40b0e9f1c3f012dc09e5f64d964a/ghc >--------------------------------------------------------------- commit c724f929b67a40b0e9f1c3f012dc09e5f64d964a Author: Simon Peyton Jones Date: Wed Nov 14 14:57:08 2018 +0000 Print tycon arity in -ddump-types >--------------------------------------------------------------- c724f929b67a40b0e9f1c3f012dc09e5f64d964a compiler/typecheck/TcRnDriver.hs | 2 +- testsuite/tests/dependent/should_compile/T15743.stderr | 2 +- testsuite/tests/dependent/should_compile/T15743e.stderr | 4 ++-- .../tests/indexed-types/should_compile/T15711.stderr | 4 ++-- .../tests/indexed-types/should_compile/T3017.stderr | 6 +++--- testsuite/tests/partial-sigs/should_compile/ADT.stderr | 2 +- .../should_compile/DataFamilyInstanceLHS.stderr | 4 ++-- .../tests/partial-sigs/should_compile/Meltdown.stderr | 2 +- .../NamedWildcardInDataFamilyInstanceLHS.stderr | 4 ++-- .../NamedWildcardInTypeFamilyInstanceLHS.stderr | 2 +- .../tests/partial-sigs/should_compile/SkipMany.stderr | 2 +- .../should_compile/TypeFamilyInstanceLHS.stderr | 2 +- testsuite/tests/polykinds/T15592.stderr | 2 +- testsuite/tests/polykinds/T15592b.stderr | 4 ++-- testsuite/tests/roles/should_compile/Roles1.stderr | 14 +++++++------- testsuite/tests/roles/should_compile/Roles14.stderr | 2 +- testsuite/tests/roles/should_compile/Roles2.stderr | 4 ++-- testsuite/tests/roles/should_compile/Roles3.stderr | 16 ++++++++-------- testsuite/tests/roles/should_compile/Roles4.stderr | 6 +++--- testsuite/tests/roles/should_compile/T8958.stderr | 6 +++--- testsuite/tests/th/TH_Roles2.stderr | 2 +- testsuite/tests/typecheck/should_compile/T12763.stderr | 2 +- testsuite/tests/typecheck/should_compile/tc231.stderr | 6 +++--- 23 files changed, 50 insertions(+), 50 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc c724f929b67a40b0e9f1c3f012dc09e5f64d964a From git at git.haskell.org Fri Nov 16 16:55:02 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Nov 2018 16:55:02 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Nearly there... (3a85772) Message-ID: <20181116165502.3C7163A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/3a8577202fce59cd77362486c06723b7ee5cb15a/ghc >--------------------------------------------------------------- commit 3a8577202fce59cd77362486c06723b7ee5cb15a Author: Simon Peyton Jones Date: Thu Nov 15 17:43:18 2018 +0000 Nearly there... >--------------------------------------------------------------- 3a8577202fce59cd77362486c06723b7ee5cb15a compiler/typecheck/TcGenDeriv.hs | 8 +- compiler/typecheck/TcHsType.hs | 2 - compiler/typecheck/TcInstDcls.hs | 12 +- compiler/typecheck/TcTyClsDecls.hs | 100 ++-------------- compiler/typecheck/TcValidity.hs | 132 +++++++++++++++++---- testsuite/tests/ghci/scripts/T6018ghcifail.stderr | 4 +- .../should_fail/ExplicitForAllFams4a.stderr | 10 +- .../should_fail/ExplicitForAllFams4b.stderr | 20 ++-- .../indexed-types/should_fail/SimpleFail13.stderr | 2 +- .../indexed-types/should_fail/SimpleFail2a.hs | 12 +- .../indexed-types/should_fail/SimpleFail9.stderr | 4 +- .../tests/indexed-types/should_fail/T7536.stderr | 5 +- testsuite/tests/polykinds/T13985.stderr | 10 +- .../tests/th/TH_reifyExplicitForAllFams.stderr | 6 +- .../tests/typecheck/should_fail/T6018fail.stderr | 4 +- 15 files changed, 169 insertions(+), 162 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 3a8577202fce59cd77362486c06723b7ee5cb15a From git at git.haskell.org Fri Nov 16 16:55:05 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Nov 2018 16:55:05 +0000 (UTC) Subject: [commit: ghc] wip/T15809: More progress on reporting unbound variables (862873e) Message-ID: <20181116165505.3F5AB3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/862873e184c28ec0a1437a4e88fc04e7b8c729bc/ghc >--------------------------------------------------------------- commit 862873e184c28ec0a1437a4e88fc04e7b8c729bc Author: Simon Peyton Jones Date: Thu Nov 15 01:16:12 2018 +0000 More progress on reporting unbound variables >--------------------------------------------------------------- 862873e184c28ec0a1437a4e88fc04e7b8c729bc compiler/typecheck/TcHsType.hs | 16 +- compiler/typecheck/TcInstDcls.hs | 64 ++-- compiler/typecheck/TcTyClsDecls.hs | 352 +++++---------------- compiler/typecheck/TcValidity.hs | 19 +- .../should_fail/ExplicitForAllFams4a.stderr | 6 +- .../should_fail/ExplicitForAllFams4b.stderr | 30 +- testsuite/tests/polykinds/T13985.stderr | 25 +- 7 files changed, 164 insertions(+), 348 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 862873e184c28ec0a1437a4e88fc04e7b8c729bc From git at git.haskell.org Fri Nov 16 16:55:08 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Nov 2018 16:55:08 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Much more progress on tcFamTyPats (255ae41) Message-ID: <20181116165508.427A83A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/255ae41f62927e154616dcf7e67bac160edb8aad/ghc >--------------------------------------------------------------- commit 255ae41f62927e154616dcf7e67bac160edb8aad Author: Simon Peyton Jones Date: Tue Nov 13 15:36:28 2018 +0000 Much more progress on tcFamTyPats Main thing left to do: data family instances A handful of validate failures Reporting unused binders correctly polykinds/T13985 indexed-types/should_fail/ExplicitForAllFams4a indexed-types/should_fail/ExplicitForAllFams4b extra error (ok) polykinds/T8616 polykinds/T14846 >--------------------------------------------------------------- 255ae41f62927e154616dcf7e67bac160edb8aad compiler/prelude/TysPrim.hs | 19 +- compiler/typecheck/TcHsType.hs | 4 +- compiler/typecheck/TcInstDcls.hs | 14 +- compiler/typecheck/TcTyClsDecls.hs | 257 +++++++++------------ compiler/types/Type.hs | 32 ++- testsuite/tests/ghci/scripts/T6018ghcifail.stderr | 2 +- .../tests/th/TH_reifyExplicitForAllFams.stderr | 6 +- .../typecheck/should_fail/LevPolyBounded.stderr | 5 + testsuite/tests/typecheck/should_fail/T14607.hs | 2 +- .../tests/typecheck/should_fail/T14607.stderr | 17 +- .../tests/typecheck/should_fail/T6018fail.stderr | 2 +- testsuite/tests/typecheck/should_fail/all.T | 2 +- 12 files changed, 168 insertions(+), 194 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 255ae41f62927e154616dcf7e67bac160edb8aad From git at git.haskell.org Fri Nov 16 16:55:11 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Nov 2018 16:55:11 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Wibbles (99efd58) Message-ID: <20181116165511.3F4CE3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/99efd58548e16d72da8f4bc22e2fef3308f6d3f9/ghc >--------------------------------------------------------------- commit 99efd58548e16d72da8f4bc22e2fef3308f6d3f9 Author: Simon Peyton Jones Date: Wed Nov 14 17:28:35 2018 +0000 Wibbles >--------------------------------------------------------------- 99efd58548e16d72da8f4bc22e2fef3308f6d3f9 compiler/typecheck/TcHsType.hs | 2 +- compiler/typecheck/TcInstDcls.hs | 188 ++++++++------------------------------- 2 files changed, 36 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 99efd58548e16d72da8f4bc22e2fef3308f6d3f9 From git at git.haskell.org Fri Nov 16 16:55:14 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Nov 2018 16:55:14 +0000 (UTC) Subject: [commit: ghc] wip/T15809: More progress with data instances (1b8289d) Message-ID: <20181116165514.358673A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/1b8289d29cc3967ecc3ed5667c5a0ca65127ed97/ghc >--------------------------------------------------------------- commit 1b8289d29cc3967ecc3ed5667c5a0ca65127ed97 Author: Simon Peyton Jones Date: Wed Nov 14 15:25:45 2018 +0000 More progress with data instances Slightly controversially, I adjusted T15725 to have data Sing :: k -> * rather than data Sing :: forall k. k -> * See a fc-call thread. We could revisit this if need be; it's not fundamental to the line of progress. >--------------------------------------------------------------- 1b8289d29cc3967ecc3ed5667c5a0ca65127ed97 compiler/typecheck/TcDeriv.hs | 2 +- compiler/typecheck/TcInstDcls.hs | 1 - compiler/typecheck/TcTyClsDecls.hs | 17 +++++++++++------ testsuite/tests/dependent/should_compile/T15725.hs | 6 +++--- testsuite/tests/ghci/scripts/T10059.stdout | 6 +++--- testsuite/tests/ghci/scripts/ghci059.stdout | 2 +- 6 files changed, 19 insertions(+), 15 deletions(-) diff --git a/compiler/typecheck/TcDeriv.hs b/compiler/typecheck/TcDeriv.hs index bb9c76b..147191b 100644 --- a/compiler/typecheck/TcDeriv.hs +++ b/compiler/typecheck/TcDeriv.hs @@ -786,7 +786,7 @@ deriveTyData tvs tc tc_args mb_deriv_strat deriv_pred -- we want to drop type variables from T so that (C d (T a)) is well-kinded let (arg_kinds, _) = splitFunTys cls_arg_kind n_args_to_drop = length arg_kinds - n_args_to_keep = tyConArity tc - n_args_to_drop + n_args_to_keep = length tc_args - n_args_to_drop (tc_args_to_keep, args_to_drop) = splitAt n_args_to_keep tc_args inst_ty_kind = typeKind (mkTyConApp tc tc_args_to_keep) diff --git a/compiler/typecheck/TcInstDcls.hs b/compiler/typecheck/TcInstDcls.hs index 86ed84a..d1081a2 100644 --- a/compiler/typecheck/TcInstDcls.hs +++ b/compiler/typecheck/TcInstDcls.hs @@ -738,7 +738,6 @@ tcDataFamInstDecl mb_clsinfo -- Kind check type patterns ; let exp_bndrs = mb_bndrs `orElse` [] data_ctxt = DataKindCtxt (unLoc fam_name) - ; ; (_, (_, (pats, stupid_theta, res_kind))) <- pushTcLevelM_ $ diff --git a/compiler/typecheck/TcTyClsDecls.hs b/compiler/typecheck/TcTyClsDecls.hs index c8a182a..4de2238 100644 --- a/compiler/typecheck/TcTyClsDecls.hs +++ b/compiler/typecheck/TcTyClsDecls.hs @@ -1485,17 +1485,22 @@ tcFamDecl1 parent (FamilyDecl { fdInfo = fam_info, fdLName = tc_lname@(L _ tc_na { traceTc "data family:" (ppr tc_name) ; checkFamFlag tc_name - -- Check the kind signature, if any. - -- Data families might have a variable return kind. - -- See See Note [Arity of data families] in FamInstEnv. - ; (extra_binders, final_res_kind) <- tcDataKindSig binders res_kind + -- Check that the result kind is OK + -- We allow things like + -- data family T (a :: Type) :: forall k. k -> Type + -- We treat T as having arity 1, but result kind forall k. k -> Type + -- But we want to check that the result kind finishes in + -- Type or a kind-variable + -- For the latter, consider + -- data family D a :: forall k. Type -> k + ; let (_, final_res_kind) = splitPiTys res_kind ; checkTc (tcIsLiftedTypeKind final_res_kind || isJust (tcGetCastedTyVar_maybe final_res_kind)) (badKindSig False res_kind) ; tc_rep_name <- newTyConRepName tc_name - ; let tycon = mkFamilyTyCon tc_name (binders `chkAppend` extra_binders) - final_res_kind + ; let tycon = mkFamilyTyCon tc_name binders + res_kind (resultVariableName sig) (DataFamilyTyCon tc_rep_name) parent NotInjective diff --git a/testsuite/tests/dependent/should_compile/T15725.hs b/testsuite/tests/dependent/should_compile/T15725.hs index a5f259e..1e2e171 100644 --- a/testsuite/tests/dependent/should_compile/T15725.hs +++ b/testsuite/tests/dependent/should_compile/T15725.hs @@ -23,12 +23,12 @@ instance SC Identity ------------------------------------------------------------------------------- -data family Sing :: forall k. k -> Type -data instance Sing :: forall a. Identity a -> Type where +data family Sing :: k -> Type +data instance Sing :: Identity a -> Type where SIdentity :: Sing x -> Sing ('Identity x) newtype Par1 p = Par1 p -data instance Sing :: forall p. Par1 p -> Type where +data instance Sing :: Par1 p -> Type where SPar1 :: Sing x -> Sing ('Par1 x) type family Rep1 (f :: Type -> Type) :: Type -> Type diff --git a/testsuite/tests/ghci/scripts/T10059.stdout b/testsuite/tests/ghci/scripts/T10059.stdout index 92fbb45..955c95a 100644 --- a/testsuite/tests/ghci/scripts/T10059.stdout +++ b/testsuite/tests/ghci/scripts/T10059.stdout @@ -1,4 +1,4 @@ -class (a ~ b) => (~) (a :: k0) (b :: k0) -- Defined in ‘GHC.Types’ -(~) :: k0 -> k0 -> Constraint -class (a GHC.Prim.~# b) => (~) (a :: k0) (b :: k0) +class (a ~ b) => (~) (a :: k) (b :: k) -- Defined in ‘GHC.Types’ +(~) :: k -> k -> Constraint +class (a GHC.Prim.~# b) => (~) (a :: k) (b :: k) -- Defined in ‘GHC.Types’ diff --git a/testsuite/tests/ghci/scripts/ghci059.stdout b/testsuite/tests/ghci/scripts/ghci059.stdout index 9e9adb9..7e734f1 100644 --- a/testsuite/tests/ghci/scripts/ghci059.stdout +++ b/testsuite/tests/ghci/scripts/ghci059.stdout @@ -4,6 +4,6 @@ It is not a class. Please see section 9.14.4 of the user's guide for details. -} type role Coercible representational representational -class Coercible a b => Coercible (a :: k0) (b :: k0) +class Coercible a b => Coercible (a :: k) (b :: k) -- Defined in ‘GHC.Types’ coerce :: Coercible a b => a -> b -- Defined in ‘GHC.Prim’ From git at git.haskell.org Fri Nov 16 16:55:16 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 16 Nov 2018 16:55:16 +0000 (UTC) Subject: [commit: ghc] wip/T15809's head updated: Finally, validate-clean (fecafee) Message-ID: <20181116165516.C37D83A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/T15809' now includes: 255d2e3 Fix embarrassing, egregious bug in roles of (->) 74ed9c1 Actually fail in failIfEmitsConstraints 1f72a1c Don't lint erroneous programs. a78e23b Lower precedence for {-# UNPACK #-} 614028e Data.Maybe: add callstack for fromJust (Trac #15559) fcd919f users-guide: Fix formatting of eventlog format documentation 695f1f2 hadrian: build ghc-iserv-prof in addition to ghc-iserv 1c92f19 Add built-in syntax suggestions, and refactor to allow library use f877d9c Move eta-reduced coaxiom compatibility handling quirks into FamInstEnv. efb3145 users-guide: Update link to Safe Coercions paper c3c552d Bump time submodule c088137 base: Misc haddock fixes 118fca7 base: Improve haddocks for Functor 5f81952 rts: Allow output filename of eventlog to be given by command-line 6bb8aaa rts: Add FALLTHROUGH macro 2c959a1 Add Int8# and Word8# 1a3b9bd Fix for Trac #15611: Scope errors lie about what modules are imported. 72b8234 Fix #15859 by checking, not assuming, an ArgFlag 5693ddd Actually add test for #15859. 7189469 integer-gmp: Fix TBA in changelog 648b0c2 Bump directory submodule to 1.3.3.1 406978c CircleCI: Build DWARF-enabled Linux bindists f424515 [LlvmCodeGen] Fixes for Int8#/Word8# 802ce6e Revert "Fix for T14251 on ARM" 39cd12b Revert "Multiple fixes / improvements for LLVM backend" 82a5c24 Revert "CircleCI: Build DWARF-enabled Linux bindists" 932cd41 testsuite: Save performance metrics in git notes. 63a8170 Fix #15845 by defining etaExpandFamInstLHS and using it 400f3ed GHCi does not need a main function aa88285 iserv: Fix typo in cabal file b337906 Ignore .gdb_history files 98f8e1c Respect naming conventions in module RnUnbound.hs in fix for #15611 13ff0b7 Fix #15594 (--abi-hash with Backpack sometimes fails) d30352a Remove StgBinderInfo and related computation in CoreToStg 86ee74d compareByPreference: handle the integer-gmp vs -simple case 89bf7d5 Correct link to GHC API in docs index. 0f2ac24 circleci: Disable pushing of test metrics if not validating upstream 5b98a38 Make `UniqDSet` a newtype 89fa34e hadrian: build ghc-iserv-dyn eb46345 Fix a bug in SRT generation (#15892) fe05764 Comments only, about polykinded TyConApps 0ce66be Comments adding to the fix for Trac #15859 ae2c9b4 Smarter HsType pretty-print for promoted datacons 4efd1b4 bump haddock submodule a50a59a More efficient, non-allocating unsafeLookupStaticPtr 32e7738 Add missing stderr file for Trac #15898 2683496 Tc-tracing, and order of arguments only 2fa5bf1 WIP on using level numbers for generalisation 8707f2d More progress on using level numbers for gen d0772e7 Further work on TyCon generalisation 304d65f Further progress dfd6617 More progress 1284033 More progress 6ddf2d1 More progress 9a902e8 Comemnts only a7a6672 Finally done 0cd583c Comments and alpha-renaming 26c2ec3 Comments only 3f214ea Progress b8d7bee Combine kcImplicitTKBndrs and tcImplicitTKBndrs 9f41010 Get rid of kcLHsQTyVarBndrs 4d6a157 Start to eliminate tcFamTyPats e547695 More progress on tcFamTyPats 9a854cc Wibbles 255ae41 Much more progress on tcFamTyPats 461e8dc Data family instances working, I think c724f92 Print tycon arity in -ddump-types 1b8289d More progress with data instances 99efd58 Wibbles 862873e More progress on reporting unbound variables 3a85772 Nearly there... d027b8c Better validity checks, simplification fecafee Finally, validate-clean From git at git.haskell.org Sat Nov 17 05:36:04 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Nov 2018 05:36:04 +0000 (UTC) Subject: [commit: ghc] master: Some assertions and comments in scheduler (6677235) Message-ID: <20181117053604.5F56C3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6677235181ea94311ae2133a7ef8a7decdbf0bb9/ghc >--------------------------------------------------------------- commit 6677235181ea94311ae2133a7ef8a7decdbf0bb9 Author: Ömer Sinan Ağacan Date: Sat Nov 17 07:59:15 2018 +0300 Some assertions and comments in scheduler Test Plan: I can't validate this because of existing errors with the debug runtime. I'll see if this introduces any new failures. Reviewers: simonmar, bgamari, erikd Reviewed By: simonmar Subscribers: rwbarton, carter Differential Revision: https://phabricator.haskell.org/D5337 >--------------------------------------------------------------- 6677235181ea94311ae2133a7ef8a7decdbf0bb9 rts/Capability.h | 5 ++++- rts/Schedule.c | 7 +++++-- rts/Schedule.h | 1 + 3 files changed, 10 insertions(+), 3 deletions(-) diff --git a/rts/Capability.h b/rts/Capability.h index 250ec22..05a827c 100644 --- a/rts/Capability.h +++ b/rts/Capability.h @@ -264,7 +264,10 @@ typedef enum { // typedef struct { SyncType type; // The kind of synchronisation - bool *idle; + bool *idle; // Array of size n_capabilities. idle[i] is true + // if capability i will be idle during this GC + // cycle. Only available when doing GC (when + // type is SYNC_GC_*). Task *task; // The Task performing the sync } PendingSync; diff --git a/rts/Schedule.c b/rts/Schedule.c index 0444f0c..d104cfd 100644 --- a/rts/Schedule.c +++ b/rts/Schedule.c @@ -668,8 +668,10 @@ scheduleYield (Capability **pcap, Task *task) // otherwise yield (sleep), and keep yielding if necessary. do { if (doIdleGCWork(cap, false)) { + // there's more idle GC work to do didGcLast = false; } else { + // no more idle GC work to do didGcLast = yieldCapability(&cap,task, !didGcLast); } } @@ -1876,7 +1878,7 @@ delete_threads_and_gc: releaseGCThreads(cap, idle_cap); } #endif - if (heap_overflow && sched_state < SCHED_INTERRUPTING) { + if (heap_overflow && sched_state == SCHED_RUNNING) { // GC set the heap_overflow flag. We should throw an exception if we // can, or shut down otherwise. @@ -2660,7 +2662,7 @@ exitScheduler (bool wait_foreign USED_IF_THREADS) ASSERT(task->incall->tso == NULL); releaseCapability(cap); } - sched_state = SCHED_SHUTTING_DOWN; + ASSERT(sched_state == SCHED_SHUTTING_DOWN); shutdownCapabilities(task, wait_foreign); @@ -2749,6 +2751,7 @@ performMajorGC(void) void interruptStgRts(void) { + ASSERT(sched_state != SCHED_SHUTTING_DOWN); sched_state = SCHED_INTERRUPTING; interruptAllCapabilities(); #if defined(THREADED_RTS) diff --git a/rts/Schedule.h b/rts/Schedule.h index 49e094b..66cf839 100644 --- a/rts/Schedule.h +++ b/rts/Schedule.h @@ -167,6 +167,7 @@ pushOnRunQueue (Capability *cap, StgTSO *tso) INLINE_HEADER StgTSO * popRunQueue (Capability *cap) { + ASSERT(cap->n_run_queue != 0); StgTSO *t = cap->run_queue_hd; ASSERT(t != END_TSO_QUEUE); cap->run_queue_hd = t->_link; From git at git.haskell.org Sat Nov 17 05:38:38 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Nov 2018 05:38:38 +0000 (UTC) Subject: [commit: ghc] master: user's guide: typo in ViewPatterns example (9696282) Message-ID: <20181117053838.CEAA93A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9696282911a5750178b0b890f3c0b638046b8f13/ghc >--------------------------------------------------------------- commit 9696282911a5750178b0b890f3c0b638046b8f13 Author: Ben Price Date: Sun Nov 11 17:19:57 2018 +0000 user's guide: typo in ViewPatterns example >--------------------------------------------------------------- 9696282911a5750178b0b890f3c0b638046b8f13 docs/users_guide/glasgow_exts.rst | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst index 5cf50b7..7056d04 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -743,7 +743,7 @@ follows: view pattern expression are in scope. For example: :: example :: Maybe ((String -> Integer,Integer), String) -> Bool - example Just ((f,_), f -> 4) = True + example (Just ((f,_), f -> 4)) = True Additionally, in function definitions, variables bound by matching earlier curried arguments may be used in view pattern expressions From git at git.haskell.org Sat Nov 17 05:40:36 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Nov 2018 05:40:36 +0000 (UTC) Subject: [commit: ghc] master: Fix a typo in the description of -fabstract-refinement-hole-fits (6ba9aa5) Message-ID: <20181117054036.057953A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6ba9aa5dd0a539adf02690a9c71d1589f541b3c5/ghc >--------------------------------------------------------------- commit 6ba9aa5dd0a539adf02690a9c71d1589f541b3c5 Author: Dmitry Ivanov Date: Thu Nov 15 10:36:09 2018 +0100 Fix a typo in the description of -fabstract-refinement-hole-fits >--------------------------------------------------------------- 6ba9aa5dd0a539adf02690a9c71d1589f541b3c5 docs/users_guide/glasgow_exts.rst | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst index 7056d04..a07adf3 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -11898,7 +11898,7 @@ fixing the hole, this can help users understand what options they have. .. ghc-flag:: -fabstract-refinement-hole-fits :shortdesc: *default: off.* Toggles whether refinements where one or more - or more of the holes are abstract are reported. + of the holes are abstract are reported. :type: dynamic :reverse: -fno-abstract-refinement-hole-fits :category: verbosity From git at git.haskell.org Sat Nov 17 10:28:26 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Nov 2018 10:28:26 +0000 (UTC) Subject: [commit: ghc] master: NCG: New code layout algorithm. (912fd2b) Message-ID: <20181117102826.291303A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/912fd2b6ca0bc51076835b6e3d1f469b715e2760/ghc >--------------------------------------------------------------- commit 912fd2b6ca0bc51076835b6e3d1f469b715e2760 Author: Andreas Klebinger Date: Sat Nov 17 11:20:36 2018 +0100 NCG: New code layout algorithm. Summary: This patch implements a new code layout algorithm. It has been tested for x86 and is disabled on other platforms. Performance varies slightly be CPU/Machine but in general seems to be better by around 2%. Nofib shows only small differences of about +/- ~0.5% overall depending on flags/machine performance in other benchmarks improved significantly. Other benchmarks includes at least the benchmarks of: aeson, vector, megaparsec, attoparsec, containers, text and xeno. While the magnitude of gains differed three different CPUs where tested with all getting faster although to differing degrees. I tested: Sandy Bridge(Xeon), Haswell, Skylake * Library benchmark results summarized: * containers: ~1.5% faster * aeson: ~2% faster * megaparsec: ~2-5% faster * xml library benchmarks: 0.2%-1.1% faster * vector-benchmarks: 1-4% faster * text: 5.5% faster On average GHC compile times go down, as GHC compiled with the new layout is faster than the overhead introduced by using the new layout algorithm, Things this patch does: * Move code responsilbe for block layout in it's own module. * Move the NcgImpl Class into the NCGMonad module. * Extract a control flow graph from the input cmm. * Update this cfg to keep it in sync with changes during asm codegen. This has been tested on x64 but should work on x86. Other platforms still use the old codelayout. * Assign weights to the edges in the CFG based on type and limited static analysis which are then used for block layout. * Once we have the final code layout eliminate some redundant jumps. In particular turn a sequences of: jne .foo jmp .bar foo: into je bar foo: .. Test Plan: ci Reviewers: bgamari, jmct, jrtc27, simonmar, simonpj, RyanGlScott Reviewed By: RyanGlScott Subscribers: RyanGlScott, trommler, jmct, carter, thomie, rwbarton GHC Trac Issues: #15124 Differential Revision: https://phabricator.haskell.org/D4726 >--------------------------------------------------------------- 912fd2b6ca0bc51076835b6e3d1f469b715e2760 compiler/cmm/CmmMachOp.hs | 13 +- compiler/cmm/CmmNode.hs | 23 +- compiler/cmm/CmmPipeline.hs | 1 - compiler/cmm/Hoopl/Collections.hs | 11 +- compiler/cmm/Hoopl/Label.hs | 7 +- compiler/ghc.cabal.in | 2 + compiler/main/DynFlags.hs | 105 ++- compiler/nativeGen/AsmCodeGen.hs | 334 ++++----- compiler/nativeGen/BlockLayout.hs | 819 +++++++++++++++++++++ compiler/nativeGen/CFG.hs | 635 ++++++++++++++++ compiler/nativeGen/NCGMonad.hs | 89 ++- compiler/nativeGen/PPC/CodeGen.hs | 4 +- compiler/nativeGen/PPC/Instr.hs | 10 +- compiler/nativeGen/PPC/RegInfo.hs | 5 + compiler/nativeGen/RegAlloc/Linear/Base.hs | 11 +- .../nativeGen/RegAlloc/Linear/JoinToTargets.hs | 47 +- compiler/nativeGen/RegAlloc/Linear/Main.hs | 8 +- compiler/nativeGen/RegAlloc/Linear/State.hs | 14 +- compiler/nativeGen/RegAlloc/Liveness.hs | 44 +- compiler/nativeGen/SPARC/CodeGen.hs | 2 +- compiler/nativeGen/SPARC/ShortcutJump.hs | 7 +- compiler/nativeGen/X86/CodeGen.hs | 251 ++++--- compiler/nativeGen/X86/Cond.hs | 41 +- compiler/nativeGen/X86/Instr.hs | 18 +- compiler/nativeGen/X86/Regs.hs | 1 - compiler/utils/Digraph.hs | 94 +++ compiler/utils/OrdList.hs | 10 +- compiler/utils/Util.hs | 22 +- docs/users_guide/8.8.1-notes.rst | 4 + docs/users_guide/debugging.rst | 6 + docs/users_guide/using-optimisation.rst | 52 ++ .../{annotations => cmm}/should_compile/Makefile | 0 testsuite/tests/cmm/should_compile/all.T | 2 + testsuite/tests/cmm/should_compile/selfloop.cmm | 11 + 34 files changed, 2370 insertions(+), 333 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 912fd2b6ca0bc51076835b6e3d1f469b715e2760 From git at git.haskell.org Sat Nov 17 10:35:43 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Nov 2018 10:35:43 +0000 (UTC) Subject: [commit: ghc] master: fix T15898 (fc670c4) Message-ID: <20181117103543.CA0CE3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/fc670c4df4593880e3d6a5f710c8ec549d36ed84/ghc >--------------------------------------------------------------- commit fc670c4df4593880e3d6a5f710c8ec549d36ed84 Author: Alp Mestanogullari Date: Sat Nov 17 11:34:07 2018 +0100 fix T15898 Summary: validate is currently broken [1] on master, this patches addresses the failure by removing an expected stdout file for T15898 since no output is generated there. [1]: https://circleci.com/gh/ghc/ghc/11416 Test Plan: TEST=T15898 ./validate Reviewers: bgamari Subscribers: rwbarton, carter Differential Revision: https://phabricator.haskell.org/D5345 >--------------------------------------------------------------- fc670c4df4593880e3d6a5f710c8ec549d36ed84 testsuite/tests/ghci/scripts/T15898.stdout | 1 - 1 file changed, 1 deletion(-) diff --git a/testsuite/tests/ghci/scripts/T15898.stdout b/testsuite/tests/ghci/scripts/T15898.stdout deleted file mode 100644 index 0519ecb..0000000 --- a/testsuite/tests/ghci/scripts/T15898.stdout +++ /dev/null @@ -1 +0,0 @@ - \ No newline at end of file From git at git.haskell.org Sat Nov 17 12:52:47 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Nov 2018 12:52:47 +0000 (UTC) Subject: [commit: ghc] master: Building GHC with hadrian on FreeBSD (6551797) Message-ID: <20181117125247.2B1093A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/65517979adf03a1fa5d33d34e419e7dfc9444002/ghc >--------------------------------------------------------------- commit 65517979adf03a1fa5d33d34e419e7dfc9444002 Author: Krzysztof Gogolewski Date: Sat Nov 17 12:21:51 2018 +0100 Building GHC with hadrian on FreeBSD Summary: I'm currently trying to make `hadrian` work as a build system on FreeBSD (https://ghc.haskell.org/trac/ghc/ticket/15860). I'm still having some issues with `libgmp` but one can get a working `ghc` using `--integer-simple` and this patch. Reviewers: bgamari, erikd, alpmestan Reviewed By: alpmestan Subscribers: rwbarton, carter Differential Revision: https://phabricator.haskell.org/D5335 >--------------------------------------------------------------- 65517979adf03a1fa5d33d34e419e7dfc9444002 compiler/main/SysTools/BaseDir.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/main/SysTools/BaseDir.hs b/compiler/main/SysTools/BaseDir.hs index 16f5a44..786b0e4 100644 --- a/compiler/main/SysTools/BaseDir.hs +++ b/compiler/main/SysTools/BaseDir.hs @@ -27,7 +27,7 @@ import System.FilePath import Data.List -- POSIX -#if defined(darwin_HOST_OS) || defined(linux_HOST_OS) +#if defined(darwin_HOST_OS) || defined(linux_HOST_OS) || defined(freebsd_HOST_OS) import System.Environment (getExecutablePath) #endif @@ -136,7 +136,7 @@ rootDir :: FilePath -> FilePath rootDir = takeDirectory . takeDirectory . normalise getBaseDir = Just . (\p -> p "lib") . rootDir <$> getExecutablePath -#elif defined(darwin_HOST_OS) || defined(linux_HOST_OS) +#elif defined(darwin_HOST_OS) || defined(linux_HOST_OS) || defined(freebsd_HOST_OS) -- on unix, this is a bit more confusing. -- The layout right now is something like -- From git at git.haskell.org Sat Nov 17 12:52:50 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Nov 2018 12:52:50 +0000 (UTC) Subject: [commit: ghc] master: Fix #12525: Remove derived bindings from the TyThings from getBindings (921fd89) Message-ID: <20181117125250.5CF5E3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/921fd890abe0e7267962c9439098b03c94ebdb9b/ghc >--------------------------------------------------------------- commit 921fd890abe0e7267962c9439098b03c94ebdb9b Author: Roland Senn Date: Sat Nov 17 12:22:23 2018 +0100 Fix #12525: Remove derived bindings from the TyThings from getBindings Summary: Remove derived OccNames from the list of TyThings returned by the function GHC.getBindings. Therefore the output of the `:show bindings `command will not contain names generated by GHC. Test Plan: make test TEST=T12525 Reviewers: austin, hvr, alanz, angerman, thomie, bgamari, osa1 Reviewed By: osa1 Subscribers: simonpj, osa1, rwbarton, carter GHC Trac Issues: #12525 Differential Revision: https://phabricator.haskell.org/D5326 >--------------------------------------------------------------- 921fd890abe0e7267962c9439098b03c94ebdb9b ghc/GHCi/UI.hs | 29 +++++++++++++++++++++++++-- testsuite/tests/ghci/should_run/T12525.script | 4 ++++ testsuite/tests/ghci/should_run/T12525.stdout | 3 +++ testsuite/tests/ghci/should_run/all.T | 1 + 4 files changed, 35 insertions(+), 2 deletions(-) diff --git a/ghc/GHCi/UI.hs b/ghc/GHCi/UI.hs index bfcaabf..3de49b4 100644 --- a/ghc/GHCi/UI.hs +++ b/ghc/GHCi/UI.hs @@ -2927,10 +2927,12 @@ showBindings :: GHCi () showBindings = do bindings <- GHC.getBindings (insts, finsts) <- GHC.getInsts - docs <- mapM makeDoc (reverse bindings) - -- reverse so the new ones come last let idocs = map GHC.pprInstanceHdr insts fidocs = map GHC.pprFamInst finsts + binds = filter (not . isDerivedOccName . getOccName) bindings -- #12525 + -- See Note [Filter bindings] + docs <- mapM makeDoc (reverse binds) + -- reverse so the new ones come last mapM_ printForUserPartWay (docs ++ idocs ++ fidocs) where makeDoc (AnId i) = pprTypeAndContents i @@ -2951,6 +2953,29 @@ showBindings = do printTyThing :: TyThing -> GHCi () printTyThing tyth = printForUser (pprTyThing showToHeader tyth) +{- +Note [Filter bindings] +~~~~~~~~~~~~~~~~~~~~~~ + +If we don't filter the bindings returned by the function GHC.getBindings, +then the :show bindings command will also show unwanted bound names, +internally generated by GHC, eg: + $tcFoo :: GHC.Types.TyCon = _ + $trModule :: GHC.Types.Module = _ . + +The filter was introduced as a fix for Trac #12525 [1]. Comment:1 [2] to this +ticket contains an analysis of the situation and suggests the solution +implemented above. + +The same filter was also implemented to fix Trac #11051 [3]. See the +Note [What to show to users] in compiler/main/InteractiveEval.hs + +[1] https://ghc.haskell.org/trac/ghc/ticket/12525 +[2] https://ghc.haskell.org/trac/ghc/ticket/12525#comment:1 +[3] https://ghc.haskell.org/trac/ghc/ticket/11051 +-} + + showBkptTable :: GHCi () showBkptTable = do st <- getGHCiState diff --git a/testsuite/tests/ghci/should_run/T12525.script b/testsuite/tests/ghci/should_run/T12525.script new file mode 100644 index 0000000..db0dec0 --- /dev/null +++ b/testsuite/tests/ghci/should_run/T12525.script @@ -0,0 +1,4 @@ +x = () +let y = () +class Foo a +:show bindings diff --git a/testsuite/tests/ghci/should_run/T12525.stdout b/testsuite/tests/ghci/should_run/T12525.stdout new file mode 100644 index 0000000..31049e1 --- /dev/null +++ b/testsuite/tests/ghci/should_run/T12525.stdout @@ -0,0 +1,3 @@ +x :: () = _ +y :: () = () +class Foo a diff --git a/testsuite/tests/ghci/should_run/all.T b/testsuite/tests/ghci/should_run/all.T index 855b603..3dfea76 100644 --- a/testsuite/tests/ghci/should_run/all.T +++ b/testsuite/tests/ghci/should_run/all.T @@ -27,6 +27,7 @@ test('T11328', just_ghci, ghci_script, ['T11328.script']) test('T11825', just_ghci, ghci_script, ['T11825.script']) test('T12128', just_ghci, ghci_script, ['T12128.script']) test('T12456', just_ghci, ghci_script, ['T12456.script']) +test('T12525', just_ghci, ghci_script, ['T12525.script']) test('T12549', just_ghci, ghci_script, ['T12549.script']) test('BinaryArray', normal, compile_and_run, ['']) test('T14125a', just_ghci, ghci_script, ['T14125a.script']) From git at git.haskell.org Sat Nov 17 12:52:54 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Nov 2018 12:52:54 +0000 (UTC) Subject: [commit: ghc] master: Fix #12906: GHC fails to typecheck Main module without main (92f8184) Message-ID: <20181117125254.3AB513A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/92f81841e885f081bbb079d0dca6eb50b9043d4b/ghc >--------------------------------------------------------------- commit 92f81841e885f081bbb079d0dca6eb50b9043d4b Author: Roland Senn Date: Sat Nov 17 12:24:27 2018 +0100 Fix #12906: GHC fails to typecheck Main module without main Summary: The function fail is no longer called immediately after adding the no-main error message to the TcM monad. The rest of the module will be typechecked. Test Plan: make test TEST=T12906 Reviewers: dfeuer, RyanGlScott, ezyang, mpickering, bgamari Reviewed By: RyanGlScott Subscribers: rwbarton, carter GHC Trac Issues: #12906 Differential Revision: https://phabricator.haskell.org/D5338 >--------------------------------------------------------------- 92f81841e885f081bbb079d0dca6eb50b9043d4b compiler/typecheck/TcRnDriver.hs | 10 +++++----- testsuite/tests/typecheck/should_fail/T12906.hs | 5 +++++ testsuite/tests/typecheck/should_fail/T12906.stderr | 10 ++++++++++ testsuite/tests/typecheck/should_fail/all.T | 4 +++- 4 files changed, 23 insertions(+), 6 deletions(-) diff --git a/compiler/typecheck/TcRnDriver.hs b/compiler/typecheck/TcRnDriver.hs index a3e2a2f..3e8d043 100644 --- a/compiler/typecheck/TcRnDriver.hs +++ b/compiler/typecheck/TcRnDriver.hs @@ -1732,11 +1732,11 @@ check_main dflags tcg_env explicit_mod_hdr main_fn = getMainFun dflags interactive = ghcLink dflags == LinkInMemory - complain_no_main = checkTc (interactive && not explicit_mod_hdr) noMainMsg - -- In interactive mode, without an explicit module header, don't - -- worry about the absence of 'main'. - -- In other modes, fail altogether, so that we don't go on - -- and complain a second time when processing the export list. + complain_no_main = unless (interactive && not explicit_mod_hdr) + (addErrTc noMainMsg) -- #12906 + -- Without an explicit module header... + -- in interactive mode, don't worry about the absence of 'main'. + -- in other modes, add error message and go on with typechecking. mainCtxt = text "When checking the type of the" <+> pp_main_fn noMainMsg = text "The" <+> pp_main_fn diff --git a/testsuite/tests/typecheck/should_fail/T12906.hs b/testsuite/tests/typecheck/should_fail/T12906.hs new file mode 100644 index 0000000..80a10f3 --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T12906.hs @@ -0,0 +1,5 @@ +x :: String -> String +x s = print (reverse s + 1) + +myshow :: (String -> String) -> String +myshow x = show x diff --git a/testsuite/tests/typecheck/should_fail/T12906.stderr b/testsuite/tests/typecheck/should_fail/T12906.stderr new file mode 100644 index 0000000..c74fd97 --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T12906.stderr @@ -0,0 +1,10 @@ + +T12906.hs:1:1: error: + The IO action ‘main’ is not defined in module ‘Main’ + +T12906.hs:2:7: error: + • Couldn't match type ‘IO ()’ with ‘[Char]’ + Expected type: String + Actual type: IO () + • In the expression: print (reverse s + 1) + In an equation for ‘x’: x s = print (reverse s + 1) diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T index c3a9f51..3805315 100644 --- a/testsuite/tests/typecheck/should_fail/all.T +++ b/testsuite/tests/typecheck/should_fail/all.T @@ -141,7 +141,8 @@ test('tcfail154', normal, compile_fail, ['']) test('tcfail155', normal, compile_fail, ['']) test('tcfail156', normal, compile_fail, ['']) test('tcfail157', normal, compile_fail, ['']) -test('tcfail158', normal, compile_fail, ['']) +# Skip tcfail158 until Trac ticket #15899 fixes the broken test +test('tcfail158', skip, compile_fail, ['']) test('tcfail159', normal, compile_fail, ['']) test('tcfail160', normal, compile_fail, ['']) test('tcfail161', normal, compile_fail, ['']) @@ -424,6 +425,7 @@ test('T12803', normal, compile_fail, ['']) test('T12042', [extra_files(['T12042.hs', 'T12042a.hs', 'T12042.hs-boot'])], multimod_compile_fail, ['T12042', '']) test('T12966', normal, compile_fail, ['']) test('T12837', normal, compile_fail, ['']) +test('T12906', normal, compile_fail, ['']) test('T12918a', normal, compile_fail, ['']) test('T12918b', normal, compile_fail, ['']) test('T12921', normal, compile_fail, ['']) From git at git.haskell.org Sat Nov 17 12:52:57 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Nov 2018 12:52:57 +0000 (UTC) Subject: [commit: ghc] master: Minor refactoring (798c943) Message-ID: <20181117125257.2EA893A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/798c943781e14b7111431d3c7193c93fcc5ffa3e/ghc >--------------------------------------------------------------- commit 798c943781e14b7111431d3c7193c93fcc5ffa3e Author: Gabor Greif Date: Thu Feb 8 15:54:20 2018 +0100 Minor refactoring PR: https://github.com/ghc/ghc/pull/223/ >--------------------------------------------------------------- 798c943781e14b7111431d3c7193c93fcc5ffa3e compiler/cmm/CLabel.hs | 26 +++++++++++++------------- 1 file changed, 13 insertions(+), 13 deletions(-) diff --git a/compiler/cmm/CLabel.hs b/compiler/cmm/CLabel.hs index dbb92e5..3f7c97f 100644 --- a/compiler/cmm/CLabel.hs +++ b/compiler/cmm/CLabel.hs @@ -1316,20 +1316,20 @@ pprCLbl (PicBaseLabel {}) = panic "pprCLbl PicBaseLabel" pprCLbl (DeadStripPreventer {}) = panic "pprCLbl DeadStripPreventer" ppIdFlavor :: IdLabelInfo -> SDoc -ppIdFlavor x = pp_cSEP <> +ppIdFlavor x = pp_cSEP <> text (case x of - Closure -> text "closure" - InfoTable -> text "info" - LocalInfoTable -> text "info" - Entry -> text "entry" - LocalEntry -> text "entry" - Slow -> text "slow" - RednCounts -> text "ct" - ConEntry -> text "con_entry" - ConInfoTable -> text "con_info" - ClosureTable -> text "closure_tbl" - Bytes -> text "bytes" - BlockInfoTable -> text "info" + Closure -> "closure" + InfoTable -> "info" + LocalInfoTable -> "info" + Entry -> "entry" + LocalEntry -> "entry" + Slow -> "slow" + RednCounts -> "ct" + ConEntry -> "con_entry" + ConInfoTable -> "con_info" + ClosureTable -> "closure_tbl" + Bytes -> "bytes" + BlockInfoTable -> "info" ) From git at git.haskell.org Sat Nov 17 12:53:00 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Nov 2018 12:53:00 +0000 (UTC) Subject: [commit: ghc] master: Remove -Wamp flag (#11477) (33f5725) Message-ID: <20181117125300.23EC83A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/33f572589d1c40c77d642c79f9cfdd6d84fa7477/ghc >--------------------------------------------------------------- commit 33f572589d1c40c77d642c79f9cfdd6d84fa7477 Author: roland Date: Sat Nov 17 12:33:00 2018 +0100 Remove -Wamp flag (#11477) Summary: Add line "The deprecated ghc-flag -Wamp has been removed." to the release notes for 8.8.1 Reviewers: bgamari, monoidal Reviewed By: monoidal Subscribers: rwbarton, carter GHC Trac Issues: #11477 Differential Revision: https://phabricator.haskell.org/D5296 >--------------------------------------------------------------- 33f572589d1c40c77d642c79f9cfdd6d84fa7477 docs/users_guide/8.8.1-notes.rst | 2 ++ 1 file changed, 2 insertions(+) diff --git a/docs/users_guide/8.8.1-notes.rst b/docs/users_guide/8.8.1-notes.rst index 66ecdf0..69b9c5d 100644 --- a/docs/users_guide/8.8.1-notes.rst +++ b/docs/users_guide/8.8.1-notes.rst @@ -77,6 +77,8 @@ Compiler - The :ghc-flag:`-fblock-layout-cfg` flag enables a new code layout algorithm on x86. This is enabled by default at :ghc-flag:`-O` and :ghc-flag:`-O2`. +- The deprecated ghc-flag ``-Wamp`` has been removed. + Runtime system ~~~~~~~~~~~~~~ From git at git.haskell.org Sat Nov 17 12:53:03 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Nov 2018 12:53:03 +0000 (UTC) Subject: [commit: ghc] master: Fix trac #15702, as a followon to fix for #13704. (0e7790a) Message-ID: <20181117125303.AAC153A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0e7790abf7d19d19f84c86dc95e50beb65462d12/ghc >--------------------------------------------------------------- commit 0e7790abf7d19d19f84c86dc95e50beb65462d12 Author: Chris Smith Date: Sat Nov 17 12:40:23 2018 +0100 Fix trac #15702, as a followon to fix for #13704. Summary: The effect of this change is that -main-is changes the default export list for the main module, but does not apply the same change to non-main modules. This fixes some cases where -main-is was used to wrap a module that expected that default behavior (exporting `main`, even when that wasn't the main entry point name). Reviewers: mpickering, monoidal, bgamari Subscribers: rwbarton, carter GHC Trac Issues: #13704, #15702 Differential Revision: https://phabricator.haskell.org/D5322 >--------------------------------------------------------------- 0e7790abf7d19d19f84c86dc95e50beb65462d12 compiler/typecheck/TcRnExports.hs | 6 ++-- docs/users_guide/bugs.rst | 38 +++++++++++++++------- testsuite/tests/module/{T13704.hs => T13704a.hs} | 0 .../{dynlibs/T5373B.hs => module/T13704b1.hs} | 2 +- testsuite/tests/module/T13704b2.hs | 7 ++++ testsuite/tests/module/all.T | 3 +- 6 files changed, 41 insertions(+), 15 deletions(-) diff --git a/compiler/typecheck/TcRnExports.hs b/compiler/typecheck/TcRnExports.hs index 1b57608..a2f892b 100644 --- a/compiler/typecheck/TcRnExports.hs +++ b/compiler/typecheck/TcRnExports.hs @@ -127,9 +127,11 @@ tcRnExports explicit_mod exports -- In interactive mode, we behave as if he had -- written "module Main where ..." ; dflags <- getDynFlags + ; let is_main_mod = mainModIs dflags == this_mod ; let default_main = case mainFunIs dflags of - Just main_fun -> mkUnqual varName (fsLit main_fun) - Nothing -> main_RDR_Unqual + Just main_fun + | is_main_mod -> mkUnqual varName (fsLit main_fun) + _ -> main_RDR_Unqual ; let real_exports | explicit_mod = exports | ghcLink dflags == LinkInMemory = Nothing diff --git a/docs/users_guide/bugs.rst b/docs/users_guide/bugs.rst index 0290622..96cdd25 100644 --- a/docs/users_guide/bugs.rst +++ b/docs/users_guide/bugs.rst @@ -171,35 +171,51 @@ same context. For example, this is fine: :: g :: Ord a => a -> Bool g y = (y <= y) || f True -.. _infelicities-Modules: +.. _infelicities-default-exports: Default Module headers with -main-is ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ -The Haskell2010 report specifies in that +The Haskell2010 Report specifies in that "An abbreviated form of module, consisting only of the module body, is permitted. If this is used, the header is assumed to be `module Main(main) where`." +GHC's ``-main-is`` option can be used to change the name of the top-level entry +point from ``main`` to any other variable. When compiling the main module and +``-main-is`` has been used to rename the default entry point, GHC will also use +the alternate name in the default export list. + Consider the following program: :: -- file: Main.hs program :: IO () program = return () -Under the report, this would fail with ``ghc -main-is Main.program Main.hs`` -with the following errors: :: +GHC will successfully compile this module with +``ghc -main-is Main.program Main.hs``, because the default export list +will include ``program`` rather than ``main``, as the Haskell Report +typically requires. + +This change only applies to the main module. Other modules will still export +``main`` from a default export list, regardless of the ``-main-is`` flag. +This allows use of ``-main-is`` with existing modules that export ``main`` via +a default export list, even when ``-main-is`` points to a different entry +point, as in this example (compiled with ``-main-is MainWrapper.program``). :: - Main.hs:1:1: error: - Not in scope: 'main' - Perhaps you meant 'min' (imported from Prelude) + -- file MainWrapper.hs + module MainWrapper where + import Main - Main.hs:1:1: error: - The main IO action 'program' is not exported by module 'Main' + program :: IO () + program = putStrLn "Redirecting..." >> main + + -- file Main.hs + main :: IO () + main = putStrLn "I am main." -GHC's flag '-main-is' allows one to change the entry point name so that -the above example would succeed. +.. _infelicities-Modules: Module system and interface files ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ diff --git a/testsuite/tests/module/T13704.hs b/testsuite/tests/module/T13704a.hs similarity index 100% rename from testsuite/tests/module/T13704.hs rename to testsuite/tests/module/T13704a.hs diff --git a/testsuite/tests/dynlibs/T5373B.hs b/testsuite/tests/module/T13704b1.hs similarity index 55% copy from testsuite/tests/dynlibs/T5373B.hs copy to testsuite/tests/module/T13704b1.hs index 0570fb1..28b8800 100644 --- a/testsuite/tests/dynlibs/T5373B.hs +++ b/testsuite/tests/module/T13704b1.hs @@ -1,4 +1,4 @@ - main :: IO () main = return () +-- wrapped by T13704b2.hs diff --git a/testsuite/tests/module/T13704b2.hs b/testsuite/tests/module/T13704b2.hs new file mode 100644 index 0000000..d76206f --- /dev/null +++ b/testsuite/tests/module/T13704b2.hs @@ -0,0 +1,7 @@ +module T13704b2 where +import Main (main) + +program :: IO () +program = main + +-- meant to be compiled with '-main-is T13704b2.program' diff --git a/testsuite/tests/module/all.T b/testsuite/tests/module/all.T index dbba44f..33ce3ae 100644 --- a/testsuite/tests/module/all.T +++ b/testsuite/tests/module/all.T @@ -284,4 +284,5 @@ test('T11970B', normal, compile_fail, ['']) test('MultiExport', normal, compile, ['']) test('T13528', normal, compile, ['']) test('T13622', normal, compile, ['']) -test('T13704', normal, compile, ['-main-is Main.program']) +test('T13704a', normal, compile, ['-main-is Main.program']) +test('T13704b', [], multimod_compile, ['T13704b1.hs T13704b2.hs', '-main-is T13704b2.program -v0']) From git at git.haskell.org Sat Nov 17 12:53:06 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Nov 2018 12:53:06 +0000 (UTC) Subject: [commit: ghc] master: More compact Outputable instance for `Uniq(D)Set` (17e771e) Message-ID: <20181117125306.A150D3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/17e771e17e2374f50f39948955e583760f28351f/ghc >--------------------------------------------------------------- commit 17e771e17e2374f50f39948955e583760f28351f Author: Sebastian Graf Date: Sat Nov 17 12:31:29 2018 +0100 More compact Outputable instance for `Uniq(D)Set` Summary: Until now, `UniqSet` and `UniqDSet` inherited their `Outputable` instances from `UniqFM` and `UniqDFM`. That made for verbose and redundant output. This patch rectifies that by pretty-printing these sets in common math notation. E.g., previously, we would render `UniqSet`s like this: [s2fE :-> x_s2fE, s2fF :-> y_s2fF, s2fG :-> z_s2fG, s2fH :-> g_s2fH] Now, they're are printed like this: {x_s2fE, y_s2fF, z_s2fG, g_s2fH} Reviewers: simonpj, bgamari, AndreasK, dfeuer, osa1 Reviewed By: osa1 Subscribers: osa1, rwbarton, carter GHC Trac Issues: #15879 Differential Revision: https://phabricator.haskell.org/D5315 >--------------------------------------------------------------- 17e771e17e2374f50f39948955e583760f28351f compiler/utils/UniqDSet.hs | 2 +- compiler/utils/UniqSet.hs | 4 +++- 2 files changed, 4 insertions(+), 2 deletions(-) diff --git a/compiler/utils/UniqDSet.hs b/compiler/utils/UniqDSet.hs index 4be437c..92d924e 100644 --- a/compiler/utils/UniqDSet.hs +++ b/compiler/utils/UniqDSet.hs @@ -133,4 +133,4 @@ instance Outputable a => Outputable (UniqDSet a) where ppr = pprUniqDSet ppr pprUniqDSet :: (a -> SDoc) -> UniqDSet a -> SDoc -pprUniqDSet f (UniqDSet s) = pprUniqDFM f s +pprUniqDSet f = braces . pprWithCommas f . uniqDSetToList diff --git a/compiler/utils/UniqSet.hs b/compiler/utils/UniqSet.hs index be600a0..82b5e9f 100644 --- a/compiler/utils/UniqSet.hs +++ b/compiler/utils/UniqSet.hs @@ -191,4 +191,6 @@ instance Outputable a => Outputable (UniqSet a) where ppr = pprUniqSet ppr pprUniqSet :: (a -> SDoc) -> UniqSet a -> SDoc -pprUniqSet f (UniqSet s) = pprUniqFM f s +-- It's OK to use nonDetUFMToList here because we only use it for +-- pretty-printing. +pprUniqSet f = braces . pprWithCommas f . nonDetEltsUniqSet From git at git.haskell.org Sat Nov 17 12:53:09 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Nov 2018 12:53:09 +0000 (UTC) Subject: [commit: ghc] master: Speed up MonadUtils.mapMaybeM (5bf0786) Message-ID: <20181117125309.9A1593A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5bf07866fe34a5b7eb27870ec73a9f44e1c9c37e/ghc >--------------------------------------------------------------- commit 5bf07866fe34a5b7eb27870ec73a9f44e1c9c37e Author: Simon Jakobi Date: Sat Nov 17 12:30:12 2018 +0100 Speed up MonadUtils.mapMaybeM Summary: This version is nearly 2x faster according to a few small benchmarks. Reviewers: bgamari, monoidal Reviewed By: monoidal Subscribers: rwbarton, carter Differential Revision: https://phabricator.haskell.org/D5344 >--------------------------------------------------------------- 5bf07866fe34a5b7eb27870ec73a9f44e1c9c37e compiler/utils/MonadUtils.hs | 9 ++++----- 1 file changed, 4 insertions(+), 5 deletions(-) diff --git a/compiler/utils/MonadUtils.hs b/compiler/utils/MonadUtils.hs index e86bc49..8f40f88 100644 --- a/compiler/utils/MonadUtils.hs +++ b/compiler/utils/MonadUtils.hs @@ -30,8 +30,6 @@ module MonadUtils import GhcPrelude -import Maybes - import Control.Applicative import Control.Monad import Control.Monad.Fix @@ -144,9 +142,10 @@ mapSndM f ((a,b):xs) = do { c <- f b; rs <- mapSndM f xs; return ((a,c):rs) } concatMapM :: Monad m => (a -> m [b]) -> [a] -> m [b] concatMapM f xs = liftM concat (mapM f xs) --- | Monadic version of mapMaybe -mapMaybeM :: (Monad m) => (a -> m (Maybe b)) -> [a] -> m [b] -mapMaybeM f = liftM catMaybes . mapM f +-- | Applicative version of mapMaybe +mapMaybeM :: Applicative m => (a -> m (Maybe b)) -> [a] -> m [b] +mapMaybeM f = foldr g (pure []) + where g a = liftA2 (maybe id (:)) (f a) -- | Monadic version of fmap fmapMaybeM :: (Monad m) => (a -> m b) -> Maybe a -> m (Maybe b) From git at git.haskell.org Sat Nov 17 13:17:49 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Nov 2018 13:17:49 +0000 (UTC) Subject: [commit: packages/binary] master: Add support for Int16#, Word16# (aa9fd16) Message-ID: <20181117131749.53F603A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/aa9fd16beef8c0025e2964d26d4b54bf04e071c9 >--------------------------------------------------------------- commit aa9fd16beef8c0025e2964d26d4b54bf04e071c9 Author: Ben Gamari Date: Mon Nov 5 12:44:06 2018 -0500 Add support for Int16#, Word16# >--------------------------------------------------------------- aa9fd16beef8c0025e2964d26d4b54bf04e071c9 src/Data/Binary/Class.hs | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/src/Data/Binary/Class.hs b/src/Data/Binary/Class.hs index b44001d..690f3da 100644 --- a/src/Data/Binary/Class.hs +++ b/src/Data/Binary/Class.hs @@ -885,6 +885,8 @@ instance Binary RuntimeRep where #if __GLASGOW_HASKELL__ >= 807 put Int8Rep = putWord8 12 put Word8Rep = putWord8 13 + put Int16Rep = putWord8 14 + put Word16Rep = putWord8 15 #endif get = do @@ -905,6 +907,8 @@ instance Binary RuntimeRep where #if __GLASGOW_HASKELL__ >= 807 12 -> pure Int8Rep 13 -> pure Word8Rep + 14 -> pure Int16Rep + 15 -> pure Word16Rep #endif _ -> fail "GHCi.TH.Binary.putRuntimeRep: invalid tag" From git at git.haskell.org Sat Nov 17 13:17:51 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Nov 2018 13:17:51 +0000 (UTC) Subject: [commit: packages/binary] master: Remove unused imports. (e30a2c6) Message-ID: <20181117131751.5A3373A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/e30a2c64a68199e645fb1d7b4cf1987b083dc20c >--------------------------------------------------------------- commit e30a2c64a68199e645fb1d7b4cf1987b083dc20c Author: David Eichmann Date: Tue Nov 6 17:54:23 2018 +0000 Remove unused imports. Due to a bug in ghc, some unused imports do not yield warnings. This commit will remove such unused imports in preparation for the ghc bug fix (see https://ghc.haskell.org/trac/ghc/ticket/13064). >--------------------------------------------------------------- e30a2c64a68199e645fb1d7b4cf1987b083dc20c src/Data/Binary/Class.hs | 2 ++ src/Data/Binary/Generic.hs | 2 ++ 2 files changed, 4 insertions(+) diff --git a/src/Data/Binary/Class.hs b/src/Data/Binary/Class.hs index b44001d..d9c157d 100644 --- a/src/Data/Binary/Class.hs +++ b/src/Data/Binary/Class.hs @@ -59,7 +59,9 @@ import Control.Applicative import Data.Monoid (mempty) #endif import qualified Data.Monoid as Monoid +#if !MIN_VERSION_base(4,11,0) import Data.Monoid ((<>)) +#endif #if MIN_VERSION_base(4,8,0) import Data.Functor.Identity (Identity (..)) #endif diff --git a/src/Data/Binary/Generic.hs b/src/Data/Binary/Generic.hs index feb85d7..89f67f2 100644 --- a/src/Data/Binary/Generic.hs +++ b/src/Data/Binary/Generic.hs @@ -30,7 +30,9 @@ import Data.Binary.Get import Data.Binary.Put import Data.Bits import Data.Word +#if !MIN_VERSION_base(4,11,0) import Data.Monoid ((<>)) +#endif #ifdef HAS_DATA_KIND import Data.Kind #endif From git at git.haskell.org Sat Nov 17 13:17:53 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Nov 2018 13:17:53 +0000 (UTC) Subject: [commit: packages/binary] master: Merge pull request #157 from bgamari/master (ced6f4a) Message-ID: <20181117131753.611EE3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/ced6f4a481c3c02941d4389ca095102b264bbf06 >--------------------------------------------------------------- commit ced6f4a481c3c02941d4389ca095102b264bbf06 Merge: 0318374 aa9fd16 Author: Lennart Kolmodin Date: Tue Nov 13 10:34:25 2018 +0100 Merge pull request #157 from bgamari/master Add support for Int16#, Word16# >--------------------------------------------------------------- ced6f4a481c3c02941d4389ca095102b264bbf06 src/Data/Binary/Class.hs | 4 ++++ 1 file changed, 4 insertions(+) From git at git.haskell.org Sat Nov 17 13:17:55 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Nov 2018 13:17:55 +0000 (UTC) Subject: [commit: packages/binary] master: Merge pull request #159 from DavidEichmann/T-13064 (fb461cf) Message-ID: <20181117131755.688853A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/binary On branch : master Link : http://git.haskell.org/packages/binary.git/commitdiff/fb461cf048460813a7fac8e040c1004a0d123e42 >--------------------------------------------------------------- commit fb461cf048460813a7fac8e040c1004a0d123e42 Merge: ced6f4a e30a2c6 Author: Lennart Kolmodin Date: Thu Nov 15 16:06:14 2018 +0100 Merge pull request #159 from DavidEichmann/T-13064 Remove unused imports. >--------------------------------------------------------------- fb461cf048460813a7fac8e040c1004a0d123e42 src/Data/Binary/Class.hs | 2 ++ src/Data/Binary/Generic.hs | 2 ++ 2 files changed, 4 insertions(+) From git at git.haskell.org Sat Nov 17 15:03:45 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 17 Nov 2018 15:03:45 +0000 (UTC) Subject: [commit: ghc] master: Introduce Int16# and Word16# (36fcf9e) Message-ID: <20181117150345.08F463A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/36fcf9edee31513db2ddbf716ee0aa79766cbe69/ghc >--------------------------------------------------------------- commit 36fcf9edee31513db2ddbf716ee0aa79766cbe69 Author: Abhiroop Sarkar Date: Mon Nov 5 12:06:58 2018 -0500 Introduce Int16# and Word16# This builds off of D4475. Bumps binary submodule. Reviewers: carter, AndreasK, hvr, goldfire, bgamari, simonmar Subscribers: rwbarton, thomie Differential Revision: https://phabricator.haskell.org/D5006 >--------------------------------------------------------------- 36fcf9edee31513db2ddbf716ee0aa79766cbe69 compiler/cmm/CmmUtils.hs | 4 + compiler/codeGen/StgCmmArgRep.hs | 2 + compiler/codeGen/StgCmmPrim.hs | 45 +++++ compiler/prelude/PrelNames.hs | 115 ++++++------ compiler/prelude/TysPrim.hs | 22 ++- compiler/prelude/TysWiredIn.hs | 15 +- compiler/prelude/TysWiredIn.hs-boot | 1 + compiler/prelude/primops.txt.pp | 82 +++++++++ compiler/simplStg/RepType.hs | 2 + compiler/typecheck/TcGenDeriv.hs | 42 ++++- compiler/types/TyCon.hs | 4 + compiler/utils/Binary.hs | 4 + libraries/base/Data/Typeable/Internal.hs | 2 + libraries/binary | 2 +- libraries/ghc-prim/GHC/Types.hs | 6 +- testsuite/tests/ffi/should_run/PrimFFIInt16.hs | 28 +++ .../{PrimFFIInt8.stdout => PrimFFIInt16.stdout} | 0 testsuite/tests/ffi/should_run/PrimFFIInt16_c.c | 7 + testsuite/tests/ffi/should_run/PrimFFIWord16.hs | 28 +++ .../{PrimFFIInt8.stdout => PrimFFIWord16.stdout} | 0 testsuite/tests/ffi/should_run/PrimFFIWord16_c.c | 7 + testsuite/tests/ffi/should_run/all.T | 4 + testsuite/tests/primops/should_run/ArithInt16.hs | 197 +++++++++++++++++++++ .../tests/primops/should_run/ArithInt16.stdout | 8 + testsuite/tests/primops/should_run/ArithWord16.hs | 194 ++++++++++++++++++++ .../tests/primops/should_run/ArithWord16.stdout | 8 + .../primops/should_run/{CmpInt8.hs => CmpInt16.hs} | 34 ++-- .../should_run/{CmpInt8.stdout => CmpInt16.stdout} | 0 .../should_run/{CmpWord8.hs => CmpWord16.hs} | 34 ++-- .../{CmpInt8.stdout => CmpWord16.stdout} | 0 testsuite/tests/primops/should_run/ShowPrim.hs | 16 +- testsuite/tests/primops/should_run/ShowPrim.stdout | 3 +- testsuite/tests/primops/should_run/all.T | 5 + utils/genprimopcode/Main.hs | 4 +- 34 files changed, 809 insertions(+), 116 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 36fcf9edee31513db2ddbf716ee0aa79766cbe69 From git at git.haskell.org Sun Nov 18 12:00:20 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 18 Nov 2018 12:00:20 +0000 (UTC) Subject: [commit: ghc] master: Fix typo in docs (ecfc7b4) Message-ID: <20181118120020.1C3703A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ecfc7b4665676cb668bfeee7fd5c83ff58b4f485/ghc >--------------------------------------------------------------- commit ecfc7b4665676cb668bfeee7fd5c83ff58b4f485 Author: Chris Done Date: Sun Nov 18 11:44:53 2018 +0000 Fix typo in docs I've been reading this line of docs for years and it ruffles my feathers. >--------------------------------------------------------------- ecfc7b4665676cb668bfeee7fd5c83ff58b4f485 compiler/basicTypes/Var.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/basicTypes/Var.hs b/compiler/basicTypes/Var.hs index a23132e..5d84187 100644 --- a/compiler/basicTypes/Var.hs +++ b/compiler/basicTypes/Var.hs @@ -216,7 +216,7 @@ in its @VarDetails at . -- | Variable -- -- Essentially a typed 'Name', that may also contain some additional information --- about the 'Var' and it's use sites. +-- about the 'Var' and its use sites. data Var = TyVar { -- Type and kind variables -- see Note [Kind and type variables] From git at git.haskell.org Mon Nov 19 07:29:21 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Nov 2018 07:29:21 +0000 (UTC) Subject: [commit: ghc] master: Tiny refactor in exitScheduler (348ea16) Message-ID: <20181119072921.1E63D3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/348ea161a9a5957f30eb3dc61726850ecf00134d/ghc >--------------------------------------------------------------- commit 348ea161a9a5957f30eb3dc61726850ecf00134d Author: Ömer Sinan Ağacan Date: Mon Nov 19 10:28:57 2018 +0300 Tiny refactor in exitScheduler >--------------------------------------------------------------- 348ea161a9a5957f30eb3dc61726850ecf00134d rts/Schedule.c | 4 +--- 1 file changed, 1 insertion(+), 3 deletions(-) diff --git a/rts/Schedule.c b/rts/Schedule.c index d104cfd..54ebb43 100644 --- a/rts/Schedule.c +++ b/rts/Schedule.c @@ -2649,9 +2649,7 @@ void exitScheduler (bool wait_foreign USED_IF_THREADS) /* see Capability.c, shutdownCapability() */ { - Task *task = NULL; - - task = newBoundTask(); + Task *task = newBoundTask(); // If we haven't killed all the threads yet, do it now. if (sched_state < SCHED_SHUTTING_DOWN) { From git at git.haskell.org Mon Nov 19 08:22:25 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Nov 2018 08:22:25 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Simplify typing of associated family instances (2104d6c) Message-ID: <20181119082225.2215B3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/2104d6ca43f1ca5c5bf71015afb9039b00a7b256/ghc >--------------------------------------------------------------- commit 2104d6ca43f1ca5c5bf71015afb9039b00a7b256 Author: Simon Peyton Jones Date: Mon Nov 19 08:19:14 2018 +0000 Simplify typing of associated family instances This experimental patch simplifies the treatment of assocaited family instances, by - Treating them entirely independently from their enclosing class-instance declaration - Making a separate check (checkConsistentFamInst) that the instance(s) match the class-instance decl This makes two or three testsuite cases fail -- but I think that's a feature not bug! This is on my wip/T15809 branch >--------------------------------------------------------------- 2104d6ca43f1ca5c5bf71015afb9039b00a7b256 compiler/typecheck/TcTyClsDecls.hs | 136 +++++++++++++++++-------------------- 1 file changed, 64 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 2104d6ca43f1ca5c5bf71015afb9039b00a7b256 From git at git.haskell.org Mon Nov 19 11:35:05 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Nov 2018 11:35:05 +0000 (UTC) Subject: [commit: ghc] master: eventlog: Log the current stack size when stack overflows (7e57067) Message-ID: <20181119113505.E390F3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7e570676bd0a57f8a77e5577d9f27e2d3159193e/ghc >--------------------------------------------------------------- commit 7e570676bd0a57f8a77e5577d9f27e2d3159193e Author: Matthew Pickering Date: Mon Nov 19 11:34:13 2018 +0000 eventlog: Log the current stack size when stack overflows Reviewers: maoe, bgamari, erikd, simonmar Reviewed By: simonmar Subscribers: rwbarton, carter, sjorn3 Differential Revision: https://phabricator.haskell.org/D5287 >--------------------------------------------------------------- 7e570676bd0a57f8a77e5577d9f27e2d3159193e rts/Schedule.c | 6 +++++- rts/Trace.c | 5 +++++ 2 files changed, 10 insertions(+), 1 deletion(-) diff --git a/rts/Schedule.c b/rts/Schedule.c index 54ebb43..eb9203f 100644 --- a/rts/Schedule.c +++ b/rts/Schedule.c @@ -492,7 +492,11 @@ run_thread: traceEventStopThread(cap, t, t->why_blocked + 6, 0); } } else { - traceEventStopThread(cap, t, ret, 0); + if (ret == StackOverflow) { + traceEventStopThread(cap, t, ret, t->tot_stack_size); + } else { + traceEventStopThread(cap, t, ret, 0); + } } ASSERT_FULL_CAPABILITY_INVARIANTS(cap,task); diff --git a/rts/Trace.c b/rts/Trace.c index 5abd1d9..4475054 100644 --- a/rts/Trace.c +++ b/rts/Trace.c @@ -218,6 +218,11 @@ static void traceSchedEvent_stderr (Capability *cap, EventTypeNum tag, if (info1 == 6 + BlockedOnBlackHole) { debugBelch("cap %d: thread %" FMT_Word " stopped (blocked on black hole owned by thread %lu)\n", cap->no, (W_)tso->id, (long)info2); + } else if (info1 == StackOverflow) { + debugBelch("cap %d: thead %" FMT_Word + " stopped (stack overflow, size %lu)\n", + cap->no, (W_)tso->id, (long)info2); + } else { debugBelch("cap %d: thread %" FMT_Word " stopped (%s)\n", cap->no, (W_)tso->id, thread_stop_reasons[info1]); From git at git.haskell.org Mon Nov 19 15:15:28 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Nov 2018 15:15:28 +0000 (UTC) Subject: [commit: ghc] master: hadrian: make it possible to run the testsuite with quickest and quick (cc615c6) Message-ID: <20181119151528.BECF73A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/cc615c697b54e3141e7b30b975de0b07dc9b8b29/ghc >--------------------------------------------------------------- commit cc615c697b54e3141e7b30b975de0b07dc9b8b29 Author: Alp Mestanogullari Date: Mon Nov 19 16:12:56 2018 +0100 hadrian: make it possible to run the testsuite with quickest and quick More generally, we so far assumed that the testsuite would be executed with a flavour that's as comprehensive as perf in terms of available RTS and library flavours (at least vanilla + dynamic + prof). This would manifest itself concretely by needing 3 "ways" of the iserv program, unconditionally. We now only require the ways among vanilla, dynamic and prof that we can find in our current Flavour's rtsWays. Test Plan: hadrian/build.sh --flavour={quick, quickest} test now goes through (with a few failing tests, of course). Reviewers: bgamari, tdammers Reviewed By: tdammers Subscribers: mpickering, RyanGlScott, rwbarton, carter Differential Revision: https://phabricator.haskell.org/D5355 >--------------------------------------------------------------- cc615c697b54e3141e7b30b975de0b07dc9b8b29 hadrian/src/Rules/Test.hs | 8 ++++++-- 1 file changed, 6 insertions(+), 2 deletions(-) diff --git a/hadrian/src/Rules/Test.hs b/hadrian/src/Rules/Test.hs index de73390..bbce4db 100644 --- a/hadrian/src/Rules/Test.hs +++ b/hadrian/src/Rules/Test.hs @@ -104,9 +104,13 @@ timeoutProgBuilder = do makeExecutable (root -/- timeoutPath) needIservBins :: Action () -needIservBins = +needIservBins = do + rtsways <- interpretInContext (vanillaContext Stage1 ghc) getRtsWays need =<< traverse programPath - [ Context Stage1 iserv w | w <- [vanilla, profiling, dynamic] ] + [ Context Stage1 iserv w + | w <- [vanilla, profiling, dynamic] + , w `elem` rtsways + ] needTestBuilders :: Action () needTestBuilders = do From git at git.haskell.org Mon Nov 19 16:49:47 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Nov 2018 16:49:47 +0000 (UTC) Subject: [commit: ghc] master: Don't track free variables in STG syntax by default (47bbc70) Message-ID: <20181119164947.D38B93A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/47bbc709cb221e32310c6e28eb2f33acf78488c7/ghc >--------------------------------------------------------------- commit 47bbc709cb221e32310c6e28eb2f33acf78488c7 Author: Sebastian Graf Date: Mon Nov 19 17:48:44 2018 +0100 Don't track free variables in STG syntax by default Summary: Currently, `CoreToStg` annotates `StgRhsClosure`s with their set of non-global free variables. This free variable information is only needed in the final code generation step (i.e. `StgCmm.codeGen`), which leads to transformations such as `StgCse` and `StgUnarise` having to maintain this information. This is tiresome and unnecessary, so this patch introduces a trees-to-grow-like approach that only introduces the free variable set into the syntax tree in the code gen pass, along with a free variable analysis on STG terms to generate that information. Fixes #15754. Reviewers: simonpj, osa1, bgamari, simonmar Reviewed By: osa1 Subscribers: rwbarton, carter GHC Trac Issues: #15754 Differential Revision: https://phabricator.haskell.org/D5324 >--------------------------------------------------------------- 47bbc709cb221e32310c6e28eb2f33acf78488c7 compiler/basicTypes/VarSet.hs | 5 +- compiler/codeGen/StgCmm.hs | 14 +- compiler/codeGen/StgCmmBind.hs | 20 +- compiler/codeGen/StgCmmBind.hs-boot | 4 +- compiler/codeGen/StgCmmExpr.hs | 26 +- compiler/ghc.cabal.in | 1 + compiler/main/DynFlags.hs | 8 +- compiler/main/HscMain.hs | 4 +- compiler/simplStg/StgCse.hs | 12 +- compiler/simplStg/StgStats.hs | 8 +- compiler/simplStg/UnariseStg.hs | 23 +- compiler/stgSyn/CoreToStg.hs | 295 ++++++--------------- compiler/stgSyn/StgFVs.hs | 125 +++++++++ compiler/stgSyn/StgSyn.hs | 224 +++++++++------- compiler/utils/UniqDSet.hs | 7 +- .../simplCore/should_compile/noinline01.stderr | 8 +- 16 files changed, 408 insertions(+), 376 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 47bbc709cb221e32310c6e28eb2f33acf78488c7 From git at git.haskell.org Mon Nov 19 20:47:35 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Nov 2018 20:47:35 +0000 (UTC) Subject: [commit: ghc] wip/T15809: More progress on reporting unbound variables (4a17ead) Message-ID: <20181119204735.F36123A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/4a17ead225c5a3b6965a0c8de27e588921509d8c/ghc >--------------------------------------------------------------- commit 4a17ead225c5a3b6965a0c8de27e588921509d8c Author: Simon Peyton Jones Date: Thu Nov 15 01:16:12 2018 +0000 More progress on reporting unbound variables >--------------------------------------------------------------- 4a17ead225c5a3b6965a0c8de27e588921509d8c compiler/typecheck/TcHsType.hs | 16 +- compiler/typecheck/TcInstDcls.hs | 64 ++-- compiler/typecheck/TcTyClsDecls.hs | 352 +++++---------------- compiler/typecheck/TcValidity.hs | 19 +- .../should_fail/ExplicitForAllFams4a.stderr | 6 +- .../should_fail/ExplicitForAllFams4b.stderr | 30 +- testsuite/tests/polykinds/T13985.stderr | 25 +- 7 files changed, 164 insertions(+), 348 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 4a17ead225c5a3b6965a0c8de27e588921509d8c From git at git.haskell.org Mon Nov 19 20:47:39 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Nov 2018 20:47:39 +0000 (UTC) Subject: [commit: ghc] wip/T15809: More progress (e646676) Message-ID: <20181119204739.03D993A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/e6466767496b65fca070201a6b1c67a017853ccb/ghc >--------------------------------------------------------------- commit e6466767496b65fca070201a6b1c67a017853ccb Author: Simon Peyton Jones Date: Wed Nov 7 07:52:16 2018 +0000 More progress A fixup in TcPatSyn >--------------------------------------------------------------- e6466767496b65fca070201a6b1c67a017853ccb compiler/typecheck/TcMType.hs | 48 ++++++++++++++++---------------- compiler/typecheck/TcPatSyn.hs | 56 +++++++++++++++++++++++++++++++------- compiler/typecheck/TcSimplify.hs | 7 +++-- compiler/typecheck/TcTyClsDecls.hs | 1 + 4 files changed, 75 insertions(+), 37 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc e6466767496b65fca070201a6b1c67a017853ccb From git at git.haskell.org Mon Nov 19 20:47:42 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Nov 2018 20:47:42 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Combine kcImplicitTKBndrs and tcImplicitTKBndrs (b1a93a1) Message-ID: <20181119204742.138CE3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/b1a93a1a975a2c811139f36154d7f11f33c1e0ef/ghc >--------------------------------------------------------------- commit b1a93a1a975a2c811139f36154d7f11f33c1e0ef Author: Simon Peyton Jones Date: Mon Nov 12 08:30:33 2018 +0000 Combine kcImplicitTKBndrs and tcImplicitTKBndrs Based on a conversation with Richard on Friday, this patch * Abolishes the distinction between kcImplicitTKBndrs and tcImplicitTKBndrs; now it is bindImplicitTKBndrs * Same for kc/tcExplicitTKBndrs * tcImplicitTKBndrs no longer does a solveLocalEqualities and sort; the caller does that Much nicer. Not quite working yet though >--------------------------------------------------------------- b1a93a1a975a2c811139f36154d7f11f33c1e0ef compiler/typecheck/TcBackpack.hs | 2 +- compiler/typecheck/TcDerivInfer.hs | 2 +- compiler/typecheck/TcHsType.hs | 238 +++++++++------------ compiler/typecheck/TcInstDcls.hs | 2 +- compiler/typecheck/TcRnMonad.hs | 4 +- compiler/typecheck/TcRules.hs | 34 ++- compiler/typecheck/TcSMonad.hs | 4 +- compiler/typecheck/TcSigs.hs | 46 ++-- compiler/typecheck/TcSimplify.hs | 18 +- compiler/typecheck/TcSplice.hs | 4 +- compiler/typecheck/TcTyClsDecls.hs | 205 +++++++++++------- compiler/typecheck/TcUnify.hs | 33 +-- testsuite/tests/dependent/should_compile/T13910.hs | 10 +- .../tests/indexed-types/should_compile/T12369.hs | 10 + testsuite/tests/indexed-types/should_fail/T7938.hs | 6 +- 15 files changed, 331 insertions(+), 287 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 b1a93a1a975a2c811139f36154d7f11f33c1e0ef From git at git.haskell.org Mon Nov 19 20:47:45 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Nov 2018 20:47:45 +0000 (UTC) Subject: [commit: ghc] wip/T15809: More progress on using level numbers for gen (f96148e) Message-ID: <20181119204745.185A43A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/f96148e82e26bafcc46af613ce81ab4664ebd037/ghc >--------------------------------------------------------------- commit f96148e82e26bafcc46af613ce81ab4664ebd037 Author: Simon Peyton Jones Date: Wed Oct 31 15:00:16 2018 +0000 More progress on using level numbers for gen >--------------------------------------------------------------- f96148e82e26bafcc46af613ce81ab4664ebd037 compiler/typecheck/TcHsType.hs | 196 ++++++++++++++++++------------------- compiler/typecheck/TcInstDcls.hs | 11 +-- compiler/typecheck/TcMType.hs | 5 +- compiler/typecheck/TcSimplify.hs | 11 ++- compiler/typecheck/TcTyClsDecls.hs | 8 +- 5 files changed, 112 insertions(+), 119 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 f96148e82e26bafcc46af613ce81ab4664ebd037 From git at git.haskell.org Mon Nov 19 20:47:48 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Nov 2018 20:47:48 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Simplify typing of associated family instances (ae72e3e) Message-ID: <20181119204748.1BBCD3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/ae72e3e35c1b13a33cac1ea6f5e997d76c338b7b/ghc >--------------------------------------------------------------- commit ae72e3e35c1b13a33cac1ea6f5e997d76c338b7b Author: Simon Peyton Jones Date: Mon Nov 19 08:19:14 2018 +0000 Simplify typing of associated family instances This experimental patch simplifies the treatment of assocaited family instances, by - Treating them entirely independently from their enclosing class-instance declaration - Making a separate check (checkConsistentFamInst) that the instance(s) match the class-instance decl This makes two or three testsuite cases fail -- but I think that's a feature not bug! This is on my wip/T15809 branch >--------------------------------------------------------------- ae72e3e35c1b13a33cac1ea6f5e997d76c338b7b compiler/typecheck/TcTyClsDecls.hs | 136 +++++++++++++++++-------------------- 1 file changed, 64 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 ae72e3e35c1b13a33cac1ea6f5e997d76c338b7b From git at git.haskell.org Mon Nov 19 20:47:51 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Nov 2018 20:47:51 +0000 (UTC) Subject: [commit: ghc] wip/T15809: More progress with data instances (398119c) Message-ID: <20181119204751.1430F3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/398119cbad5c590b7b5def025e647bfb50350195/ghc >--------------------------------------------------------------- commit 398119cbad5c590b7b5def025e647bfb50350195 Author: Simon Peyton Jones Date: Wed Nov 14 15:25:45 2018 +0000 More progress with data instances Slightly controversially, I adjusted T15725 to have data Sing :: k -> * rather than data Sing :: forall k. k -> * See a fc-call thread. We could revisit this if need be; it's not fundamental to the line of progress. >--------------------------------------------------------------- 398119cbad5c590b7b5def025e647bfb50350195 compiler/typecheck/TcDeriv.hs | 2 +- compiler/typecheck/TcInstDcls.hs | 1 - compiler/typecheck/TcTyClsDecls.hs | 17 +++++++++++------ testsuite/tests/dependent/should_compile/T15725.hs | 6 +++--- testsuite/tests/ghci/scripts/T10059.stdout | 6 +++--- testsuite/tests/ghci/scripts/ghci059.stdout | 2 +- 6 files changed, 19 insertions(+), 15 deletions(-) diff --git a/compiler/typecheck/TcDeriv.hs b/compiler/typecheck/TcDeriv.hs index bb9c76b..147191b 100644 --- a/compiler/typecheck/TcDeriv.hs +++ b/compiler/typecheck/TcDeriv.hs @@ -786,7 +786,7 @@ deriveTyData tvs tc tc_args mb_deriv_strat deriv_pred -- we want to drop type variables from T so that (C d (T a)) is well-kinded let (arg_kinds, _) = splitFunTys cls_arg_kind n_args_to_drop = length arg_kinds - n_args_to_keep = tyConArity tc - n_args_to_drop + n_args_to_keep = length tc_args - n_args_to_drop (tc_args_to_keep, args_to_drop) = splitAt n_args_to_keep tc_args inst_ty_kind = typeKind (mkTyConApp tc tc_args_to_keep) diff --git a/compiler/typecheck/TcInstDcls.hs b/compiler/typecheck/TcInstDcls.hs index 86ed84a..d1081a2 100644 --- a/compiler/typecheck/TcInstDcls.hs +++ b/compiler/typecheck/TcInstDcls.hs @@ -738,7 +738,6 @@ tcDataFamInstDecl mb_clsinfo -- Kind check type patterns ; let exp_bndrs = mb_bndrs `orElse` [] data_ctxt = DataKindCtxt (unLoc fam_name) - ; ; (_, (_, (pats, stupid_theta, res_kind))) <- pushTcLevelM_ $ diff --git a/compiler/typecheck/TcTyClsDecls.hs b/compiler/typecheck/TcTyClsDecls.hs index c8a182a..4de2238 100644 --- a/compiler/typecheck/TcTyClsDecls.hs +++ b/compiler/typecheck/TcTyClsDecls.hs @@ -1485,17 +1485,22 @@ tcFamDecl1 parent (FamilyDecl { fdInfo = fam_info, fdLName = tc_lname@(L _ tc_na { traceTc "data family:" (ppr tc_name) ; checkFamFlag tc_name - -- Check the kind signature, if any. - -- Data families might have a variable return kind. - -- See See Note [Arity of data families] in FamInstEnv. - ; (extra_binders, final_res_kind) <- tcDataKindSig binders res_kind + -- Check that the result kind is OK + -- We allow things like + -- data family T (a :: Type) :: forall k. k -> Type + -- We treat T as having arity 1, but result kind forall k. k -> Type + -- But we want to check that the result kind finishes in + -- Type or a kind-variable + -- For the latter, consider + -- data family D a :: forall k. Type -> k + ; let (_, final_res_kind) = splitPiTys res_kind ; checkTc (tcIsLiftedTypeKind final_res_kind || isJust (tcGetCastedTyVar_maybe final_res_kind)) (badKindSig False res_kind) ; tc_rep_name <- newTyConRepName tc_name - ; let tycon = mkFamilyTyCon tc_name (binders `chkAppend` extra_binders) - final_res_kind + ; let tycon = mkFamilyTyCon tc_name binders + res_kind (resultVariableName sig) (DataFamilyTyCon tc_rep_name) parent NotInjective diff --git a/testsuite/tests/dependent/should_compile/T15725.hs b/testsuite/tests/dependent/should_compile/T15725.hs index a5f259e..1e2e171 100644 --- a/testsuite/tests/dependent/should_compile/T15725.hs +++ b/testsuite/tests/dependent/should_compile/T15725.hs @@ -23,12 +23,12 @@ instance SC Identity ------------------------------------------------------------------------------- -data family Sing :: forall k. k -> Type -data instance Sing :: forall a. Identity a -> Type where +data family Sing :: k -> Type +data instance Sing :: Identity a -> Type where SIdentity :: Sing x -> Sing ('Identity x) newtype Par1 p = Par1 p -data instance Sing :: forall p. Par1 p -> Type where +data instance Sing :: Par1 p -> Type where SPar1 :: Sing x -> Sing ('Par1 x) type family Rep1 (f :: Type -> Type) :: Type -> Type diff --git a/testsuite/tests/ghci/scripts/T10059.stdout b/testsuite/tests/ghci/scripts/T10059.stdout index 92fbb45..955c95a 100644 --- a/testsuite/tests/ghci/scripts/T10059.stdout +++ b/testsuite/tests/ghci/scripts/T10059.stdout @@ -1,4 +1,4 @@ -class (a ~ b) => (~) (a :: k0) (b :: k0) -- Defined in ‘GHC.Types’ -(~) :: k0 -> k0 -> Constraint -class (a GHC.Prim.~# b) => (~) (a :: k0) (b :: k0) +class (a ~ b) => (~) (a :: k) (b :: k) -- Defined in ‘GHC.Types’ +(~) :: k -> k -> Constraint +class (a GHC.Prim.~# b) => (~) (a :: k) (b :: k) -- Defined in ‘GHC.Types’ diff --git a/testsuite/tests/ghci/scripts/ghci059.stdout b/testsuite/tests/ghci/scripts/ghci059.stdout index 9e9adb9..7e734f1 100644 --- a/testsuite/tests/ghci/scripts/ghci059.stdout +++ b/testsuite/tests/ghci/scripts/ghci059.stdout @@ -4,6 +4,6 @@ It is not a class. Please see section 9.14.4 of the user's guide for details. -} type role Coercible representational representational -class Coercible a b => Coercible (a :: k0) (b :: k0) +class Coercible a b => Coercible (a :: k) (b :: k) -- Defined in ‘GHC.Types’ coerce :: Coercible a b => a -> b -- Defined in ‘GHC.Prim’ From git at git.haskell.org Mon Nov 19 20:47:54 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Nov 2018 20:47:54 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Further work on TyCon generalisation (4eadda8) Message-ID: <20181119204754.1B9A83A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/4eadda866e288f8f108a35a190b5f16478840e2b/ghc >--------------------------------------------------------------- commit 4eadda866e288f8f108a35a190b5f16478840e2b Author: Simon Peyton Jones Date: Fri Nov 2 18:06:16 2018 +0000 Further work on TyCon generalisation >--------------------------------------------------------------- 4eadda866e288f8f108a35a190b5f16478840e2b compiler/typecheck/TcHsType.hs | 109 +++++++++++---------- compiler/typecheck/TcMType.hs | 54 +++++++--- compiler/typecheck/TcRnTypes.hs | 8 +- compiler/typecheck/TcTyClsDecls.hs | 93 +++++------------- compiler/types/TyCoRep.hs | 16 ++- compiler/types/Type.hs | 2 +- testsuite/tests/dependent/should_compile/T14880.hs | 1 + .../tests/dependent/should_compile/T15743e.stderr | 6 +- .../tests/indexed-types/should_fail/T13972.stderr | 2 +- testsuite/tests/polykinds/T12593.stderr | 8 +- 10 files changed, 147 insertions(+), 152 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 4eadda866e288f8f108a35a190b5f16478840e2b From git at git.haskell.org Mon Nov 19 20:47:58 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Nov 2018 20:47:58 +0000 (UTC) Subject: [commit: ghc] wip/T15809: More progress on tcFamTyPats (b3bab72) Message-ID: <20181119204758.1E0BB3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/b3bab721249d4b5c66819a54d25075bfc1f76130/ghc >--------------------------------------------------------------- commit b3bab721249d4b5c66819a54d25075bfc1f76130 Author: Simon Peyton Jones Date: Mon Nov 12 17:21:55 2018 +0000 More progress on tcFamTyPats This fixes Trac #15740 >--------------------------------------------------------------- b3bab721249d4b5c66819a54d25075bfc1f76130 compiler/typecheck/TcHsType.hs | 26 ++++++++++------- compiler/typecheck/TcMType.hs | 4 +-- compiler/typecheck/TcTyClsDecls.hs | 51 +++++++++++++++++++++++++++------ compiler/typecheck/TcValidity.hs | 23 ++++++++------- testsuite/tests/polykinds/T13985.stderr | 10 ++----- testsuite/tests/polykinds/T15740.hs | 15 ++++++++++ testsuite/tests/polykinds/T15740.stderr | 6 ++++ testsuite/tests/polykinds/T15740a.hs | 12 ++++++++ testsuite/tests/polykinds/all.T | 2 ++ 9 files changed, 109 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 b3bab721249d4b5c66819a54d25075bfc1f76130 From git at git.haskell.org Mon Nov 19 20:48:01 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Nov 2018 20:48:01 +0000 (UTC) Subject: [commit: ghc] wip/T15809: More progress (5318307) Message-ID: <20181119204801.2D07B3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/531830780f10ef90d913641a0de7211dae18b4c0/ghc >--------------------------------------------------------------- commit 531830780f10ef90d913641a0de7211dae18b4c0 Author: Simon Peyton Jones Date: Tue Nov 6 17:44:25 2018 +0000 More progress >--------------------------------------------------------------- 531830780f10ef90d913641a0de7211dae18b4c0 compiler/typecheck/TcHsType.hs | 290 +++++++++------------ compiler/typecheck/TcMType.hs | 122 ++++----- compiler/typecheck/TcTyClsDecls.hs | 229 ++++++++-------- compiler/typecheck/TcValidity.hs | 19 +- testsuite/tests/dependent/should_compile/T14880.hs | 1 - .../tests/dependent/should_compile/T15743e.stderr | 2 +- testsuite/tests/ghci/scripts/T15591.hs | 5 + testsuite/tests/ghci/scripts/T15743b.stdout | 2 +- testsuite/tests/ghci/scripts/T7873.stderr | 2 +- .../tests/indexed-types/should_fail/T13972.stderr | 2 +- testsuite/tests/polykinds/T11203.stderr | 2 +- testsuite/tests/polykinds/T11821a.stderr | 2 +- testsuite/tests/polykinds/T15592b.stderr | 2 +- .../tests/typecheck/should_fail/T13983.stderr | 2 +- testsuite/tests/typecheck/should_fail/T2688.stderr | 6 +- 15 files changed, 318 insertions(+), 370 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 531830780f10ef90d913641a0de7211dae18b4c0 From git at git.haskell.org Mon Nov 19 20:48:04 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Nov 2018 20:48:04 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Finally, validate-clean (5e062be) Message-ID: <20181119204804.346DE3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/5e062be19cae5292311758148482c3be0b0ecf70/ghc >--------------------------------------------------------------- commit 5e062be19cae5292311758148482c3be0b0ecf70 Author: Simon Peyton Jones Date: Fri Nov 16 12:03:59 2018 +0000 Finally, validate-clean Except for polykinds/T14846, where there is an extra error message. I actually tnink it's correct, but have not checked yet. >--------------------------------------------------------------- 5e062be19cae5292311758148482c3be0b0ecf70 compiler/typecheck/TcBinds.hs | 24 ---- compiler/typecheck/TcClassDcl.hs | 3 - compiler/typecheck/TcDeriv.hs | 3 - compiler/typecheck/TcEnv.hs | 8 -- compiler/typecheck/TcHsType.hs | 87 +++++++++----- compiler/typecheck/TcInstDcls.hs | 81 ++++++------- compiler/typecheck/TcPat.hs | 2 +- compiler/typecheck/TcTyClsDecls.hs | 132 +++++++++++++-------- compiler/types/TyCoRep.hs | 7 +- .../indexed-types/should_fail/SimpleFail9.stderr | 2 +- .../tests/indexed-types/should_fail/T10817.stderr | 9 +- .../tests/indexed-types/should_fail/T10899.stderr | 3 +- testsuite/tests/polykinds/T8616.stderr | 9 ++ testsuite/tests/printer/Ppr040.hs | 10 +- 14 files changed, 202 insertions(+), 178 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 5e062be19cae5292311758148482c3be0b0ecf70 From git at git.haskell.org Mon Nov 19 20:48:07 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Nov 2018 20:48:07 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Print tycon arity in -ddump-types (aa8409f) Message-ID: <20181119204807.33D403A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/aa8409f4b16674c030465f2262933a5837fd1b29/ghc >--------------------------------------------------------------- commit aa8409f4b16674c030465f2262933a5837fd1b29 Author: Simon Peyton Jones Date: Wed Nov 14 14:57:08 2018 +0000 Print tycon arity in -ddump-types >--------------------------------------------------------------- aa8409f4b16674c030465f2262933a5837fd1b29 compiler/typecheck/TcRnDriver.hs | 2 +- testsuite/tests/dependent/should_compile/T15743.stderr | 2 +- testsuite/tests/dependent/should_compile/T15743e.stderr | 4 ++-- .../tests/indexed-types/should_compile/T15711.stderr | 4 ++-- .../tests/indexed-types/should_compile/T3017.stderr | 6 +++--- testsuite/tests/partial-sigs/should_compile/ADT.stderr | 2 +- .../should_compile/DataFamilyInstanceLHS.stderr | 4 ++-- .../tests/partial-sigs/should_compile/Meltdown.stderr | 2 +- .../NamedWildcardInDataFamilyInstanceLHS.stderr | 4 ++-- .../NamedWildcardInTypeFamilyInstanceLHS.stderr | 2 +- .../tests/partial-sigs/should_compile/SkipMany.stderr | 2 +- .../should_compile/TypeFamilyInstanceLHS.stderr | 2 +- testsuite/tests/polykinds/T15592.stderr | 2 +- testsuite/tests/polykinds/T15592b.stderr | 4 ++-- testsuite/tests/roles/should_compile/Roles1.stderr | 14 +++++++------- testsuite/tests/roles/should_compile/Roles14.stderr | 2 +- testsuite/tests/roles/should_compile/Roles2.stderr | 4 ++-- testsuite/tests/roles/should_compile/Roles3.stderr | 16 ++++++++-------- testsuite/tests/roles/should_compile/Roles4.stderr | 6 +++--- testsuite/tests/roles/should_compile/T8958.stderr | 6 +++--- testsuite/tests/th/TH_Roles2.stderr | 2 +- testsuite/tests/typecheck/should_compile/T12763.stderr | 2 +- testsuite/tests/typecheck/should_compile/tc231.stderr | 6 +++--- 23 files changed, 50 insertions(+), 50 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc aa8409f4b16674c030465f2262933a5837fd1b29 From git at git.haskell.org Mon Nov 19 20:48:10 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Nov 2018 20:48:10 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Tc-tracing, and order of arguments only (39fa4ee) Message-ID: <20181119204810.2AF543A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/39fa4ee3e2fca5fe229e99ced4b33b884b1361c7/ghc >--------------------------------------------------------------- commit 39fa4ee3e2fca5fe229e99ced4b33b884b1361c7 Author: Simon Peyton Jones Date: Wed Oct 31 08:31:38 2018 +0000 Tc-tracing, and order of arguments only I changed the order of arguments to reportAllUnsolved, and the tc-tracing that surrounds it. No change in behaviour >--------------------------------------------------------------- 39fa4ee3e2fca5fe229e99ced4b33b884b1361c7 compiler/typecheck/TcErrors.hs | 29 ++++++++++++++++------------- compiler/typecheck/TcRnMonad.hs | 2 ++ compiler/typecheck/TcSimplify.hs | 4 ---- 3 files changed, 18 insertions(+), 17 deletions(-) diff --git a/compiler/typecheck/TcErrors.hs b/compiler/typecheck/TcErrors.hs index c692b7b..9bca25f 100644 --- a/compiler/typecheck/TcErrors.hs +++ b/compiler/typecheck/TcErrors.hs @@ -146,8 +146,9 @@ reportUnsolved wanted | warn_out_of_scope = HoleWarn | otherwise = HoleDefer - ; report_unsolved binds_var type_errors expr_holes - type_holes out_of_scope_holes wanted + ; report_unsolved type_errors expr_holes + type_holes out_of_scope_holes + binds_var wanted ; ev_binds <- getTcEvBindsMap binds_var ; return (evBindMapBinds ev_binds)} @@ -162,8 +163,8 @@ reportUnsolved wanted reportAllUnsolved :: WantedConstraints -> TcM () reportAllUnsolved wanted = do { ev_binds <- newNoTcEvBinds - ; report_unsolved ev_binds TypeError - HoleError HoleError HoleError wanted } + ; report_unsolved TypeError HoleError HoleError HoleError + ev_binds wanted } -- | Report all unsolved goals as warnings (but without deferring any errors to -- run-time). See Note [Safe Haskell Overlapping Instances Implementation] in @@ -171,22 +172,23 @@ reportAllUnsolved wanted warnAllUnsolved :: WantedConstraints -> TcM () warnAllUnsolved wanted = do { ev_binds <- newTcEvBinds - ; report_unsolved ev_binds (TypeWarn NoReason) - HoleWarn HoleWarn HoleWarn wanted } + ; report_unsolved (TypeWarn NoReason) HoleWarn HoleWarn HoleWarn + ev_binds wanted } -- | Report unsolved goals as errors or warnings. -report_unsolved :: EvBindsVar -- cec_binds - -> TypeErrorChoice -- Deferred type errors +report_unsolved :: TypeErrorChoice -- Deferred type errors -> HoleChoice -- Expression holes -> HoleChoice -- Type holes -> HoleChoice -- Out of scope holes + -> EvBindsVar -- cec_binds -> WantedConstraints -> TcM () -report_unsolved mb_binds_var type_errors expr_holes - type_holes out_of_scope_holes wanted +report_unsolved type_errors expr_holes + type_holes out_of_scope_holes binds_var wanted | isEmptyWC wanted = return () | otherwise - = do { traceTc "reportUnsolved warning/error settings:" $ + = do { traceTc "reportUnsolved {" empty + ; traceTc "reportUnsolved warning/error settings:" $ vcat [ text "type errors:" <+> ppr type_errors , text "expr holes:" <+> ppr expr_holes , text "type holes:" <+> ppr type_holes @@ -219,10 +221,11 @@ report_unsolved mb_binds_var type_errors expr_holes -- See Trac #15539 and c.f. setting ic_status -- in TcSimplify.setImplicationStatus , cec_warn_redundant = warn_redundant - , cec_binds = mb_binds_var } + , cec_binds = binds_var } ; tc_lvl <- getTcLevel - ; reportWanteds err_ctxt tc_lvl wanted } + ; reportWanteds err_ctxt tc_lvl wanted + ; traceTc "reportUnsolved }" empty } -------------------------------------------- -- Internal functions diff --git a/compiler/typecheck/TcRnMonad.hs b/compiler/typecheck/TcRnMonad.hs index bef1044..5e6cb8f 100644 --- a/compiler/typecheck/TcRnMonad.hs +++ b/compiler/typecheck/TcRnMonad.hs @@ -1532,8 +1532,10 @@ pushLevelAndCaptureConstraints :: TcM a -> TcM (TcLevel, WantedConstraints, a) pushLevelAndCaptureConstraints thing_inside = do { env <- getLclEnv ; let tclvl' = pushTcLevel (tcl_tclvl env) + ; traceTc "pushLevelAndCaptureConstraints {" (ppr tclvl') ; (res, lie) <- setLclEnv (env { tcl_tclvl = tclvl' }) $ captureConstraints thing_inside + ; traceTc "pushLevelAndCaptureConstraints }" (ppr tclvl') ; return (tclvl', lie, res) } pushTcLevelM_ :: TcM a -> TcM a diff --git a/compiler/typecheck/TcSimplify.hs b/compiler/typecheck/TcSimplify.hs index 6ef62c8..c424a02 100644 --- a/compiler/typecheck/TcSimplify.hs +++ b/compiler/typecheck/TcSimplify.hs @@ -178,9 +178,7 @@ solveEqualities thing_inside -- vars to LiftedRep. This is needed to avoid #14991. ; traceTc "End solveEqualities }" empty - ; traceTc "reportAllUnsolved {" empty ; reportAllUnsolved final_wc - ; traceTc "reportAllUnsolved }" empty ; return result } -- | Simplify top-level constraints, but without reporting any unsolved @@ -514,9 +512,7 @@ simplifyDefault theta = do { traceTc "simplifyDefault" empty ; wanteds <- newWanteds DefaultOrigin theta ; unsolved <- runTcSDeriveds (solveWantedsAndDrop (mkSimpleWC wanteds)) - ; traceTc "reportUnsolved {" empty ; reportAllUnsolved unsolved - ; traceTc "reportUnsolved }" empty ; return () } ------------------ From git at git.haskell.org Mon Nov 19 20:48:13 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Nov 2018 20:48:13 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Progress (df731cb) Message-ID: <20181119204813.28ACD3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/df731cb546b7a17178c84b698feb30a25407a662/ghc >--------------------------------------------------------------- commit df731cb546b7a17178c84b698feb30a25407a662 Author: Simon Peyton Jones Date: Fri Nov 9 18:11:25 2018 +0000 Progress Allocate result kind outside tcImplicit in tc_hs_sig_type_and_gen Plus comments In flight.. may not build (but it's a wip/ branch) >--------------------------------------------------------------- df731cb546b7a17178c84b698feb30a25407a662 compiler/typecheck/TcHsType.hs | 49 +++++++++++++++++++++--------------------- compiler/typecheck/TcMType.hs | 18 ++++------------ 2 files changed, 29 insertions(+), 38 deletions(-) diff --git a/compiler/typecheck/TcHsType.hs b/compiler/typecheck/TcHsType.hs index dd2995e..7f5d4ff 100644 --- a/compiler/typecheck/TcHsType.hs +++ b/compiler/typecheck/TcHsType.hs @@ -229,19 +229,15 @@ tc_hs_sig_type_and_gen skol_info hs_sig_type ctxt_kind | HsIB { hsib_ext = sig_vars, hsib_body = hs_ty } <- hs_sig_type = do { (_inner_lvl, wanted, (tkvs, ty)) <- pushLevelAndCaptureConstraints $ - tcImplicitTKBndrs skol_info sig_vars $ - -- tcImplicitTKBndrs does a solveLocalEqualities - do { kind <- case ctxt_kind of + do { -- See Note [Levels and generalisation] + res_kind <- case ctxt_kind of TheKind k -> return k AnyKind -> newMetaKindVar OpenKind -> newOpenTypeKind - -- The kind is checked by checkValidType, and isn't necessarily - -- of kind * in a Template Haskell quote eg [t| Maybe |] - ; tc_lhs_type typeLevelMode hs_ty kind } - -- Any remaining variables (unsolved in the solveLocalEqualities - -- in the tcImplicitTKBndrs) should be in the global tyvars, - -- and therefore won't be quantified over + ; tcImplicitTKBndrs skol_info sig_vars $ + -- tcImplicitTKBndrs does a solveLocalEqualities + tc_lhs_type typeLevelMode hs_ty res_kind } ; let ty1 = mkSpecForAllTys tkvs ty ; kvs <- kindGeneralizeLocal wanted ty1 @@ -1467,20 +1463,6 @@ To avoid the double-zonk, we do two things: 2. When we are generalizing: kindGeneralize does not require a zonked type -- it zonks as it gathers free variables. So this way effectively sidesteps step 3. - -Note [TcLevel for CUSKs] -~~~~~~~~~~~~~~~~~~~~~~~~ -In getInitialKinds we are at level 1, busy making unification -variables over which we will subsequently generalise. - -But when we find a CUSK we want to jump back to top level (0) -because that's the right starting point for a completee, -stand-alone kind signature. - -More precisely, we want to make level-1 skolems, because -the end up as the TyConBinders of the TyCon, and are brought -into scope when we type-check the body of the type declaration -(in tcTyClDecl). -} tcWildCardBinders :: [Name] @@ -2003,7 +1985,26 @@ kindGeneralizeLocal wanted kind_or_type ; quantifyTyVars mono_tvs dvs } -{- +{- Note [Levels and generalisation] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Consider + f x = e +with no type signature. We are currently at level i. +We must + * Push the level to level (i+1) + * Allocate a fresh alpha[i+1] for the result type + * Check that e :: alpha[i+1], gathering constraint WC + * Solve WC as far as possible + * Zonking the result type alpha[i+1], say to beta[i-1] -> gamma[i] + * Find the free variables with level > i, in this case gamma[i] + * Skolemise those free variables and quantify over them, giving + f :: forall g. beta[i-1] -> g + * Emit the residiual constraint wrapped in an implication for g, + thus forall g. WC + +All of this happens for types too. Consider + f :: Int -> (forall a. Proxy a -> Int) + Note [Kind generalisation] ~~~~~~~~~~~~~~~~~~~~~~~~~~ We do kind generalisation only at the outer level of a type signature. diff --git a/compiler/typecheck/TcMType.hs b/compiler/typecheck/TcMType.hs index 6d9f3ca..a1cdf24 100644 --- a/compiler/typecheck/TcMType.hs +++ b/compiler/typecheck/TcMType.hs @@ -1342,16 +1342,6 @@ to be later converted to a list in a deterministic order. For more information about deterministic sets see Note [Deterministic UniqFM] in UniqDFM. - - ---------------- Note to tidy up -------- -Can we quantify over a non-unification variable? Sadly yes (Trac #15991b) - class C2 (a :: Type) (b :: Proxy a) (c :: Proxy b) where - type T4 a c - -When we come to T4 we have in Inferred b; but it is a skolem -from the (fully settled) C2. - -} quantifyTyVars @@ -1444,10 +1434,10 @@ quantifyTyVars gbl_tvs = return Nothing -- this can happen for a covar that's associated with -- a coercion hole. Test case: typecheck/should_compile/T2494 - | not (isTcTyVar tkv) - = WARN( True, text "quantifying over a TyVar" <+> ppr tkv) - return (Just tkv) -- For associated types, we have the class variables - -- in scope, and they are TyVars not TcTyVars + | not (isTcTyVar tkv) -- I don't think this can ever happen. + -- Hence the assert + = ASSERT2( False, text "quantifying over a TyVar" <+> ppr tkv) + return (Just tkv) | otherwise = do { deflt_done <- defaultTyVar default_kind tkv From git at git.haskell.org Mon Nov 19 20:48:16 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Nov 2018 20:48:16 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Much more progress on tcFamTyPats (a4e43a8) Message-ID: <20181119204816.3339B3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/a4e43a8613f388d3c57e9ae138bfbb5082ceefae/ghc >--------------------------------------------------------------- commit a4e43a8613f388d3c57e9ae138bfbb5082ceefae Author: Simon Peyton Jones Date: Tue Nov 13 15:36:28 2018 +0000 Much more progress on tcFamTyPats Main thing left to do: data family instances A handful of validate failures Reporting unused binders correctly polykinds/T13985 indexed-types/should_fail/ExplicitForAllFams4a indexed-types/should_fail/ExplicitForAllFams4b extra error (ok) polykinds/T8616 polykinds/T14846 >--------------------------------------------------------------- a4e43a8613f388d3c57e9ae138bfbb5082ceefae compiler/prelude/TysPrim.hs | 19 +- compiler/typecheck/TcHsType.hs | 4 +- compiler/typecheck/TcInstDcls.hs | 14 +- compiler/typecheck/TcTyClsDecls.hs | 257 +++++++++------------ compiler/types/Type.hs | 32 ++- testsuite/tests/ghci/scripts/T6018ghcifail.stderr | 2 +- .../tests/th/TH_reifyExplicitForAllFams.stderr | 6 +- .../typecheck/should_fail/LevPolyBounded.stderr | 5 + testsuite/tests/typecheck/should_fail/T14607.hs | 2 +- .../tests/typecheck/should_fail/T14607.stderr | 17 +- .../tests/typecheck/should_fail/T6018fail.stderr | 2 +- testsuite/tests/typecheck/should_fail/all.T | 2 +- 12 files changed, 168 insertions(+), 194 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 a4e43a8613f388d3c57e9ae138bfbb5082ceefae From git at git.haskell.org Mon Nov 19 20:48:19 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Nov 2018 20:48:19 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Comemnts only (92ec580) Message-ID: <20181119204819.36A443A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/92ec58087b438bdf81f8cf3f330fc3401020c720/ghc >--------------------------------------------------------------- commit 92ec58087b438bdf81f8cf3f330fc3401020c720 Author: Simon Peyton Jones Date: Wed Nov 7 11:40:50 2018 +0000 Comemnts only >--------------------------------------------------------------- 92ec58087b438bdf81f8cf3f330fc3401020c720 compiler/typecheck/TcTyClsDecls.hs | 74 +++++++++++++++++++++++--------------- 1 file changed, 46 insertions(+), 28 deletions(-) diff --git a/compiler/typecheck/TcTyClsDecls.hs b/compiler/typecheck/TcTyClsDecls.hs index 3f90c42..cefc9ca 100644 --- a/compiler/typecheck/TcTyClsDecls.hs +++ b/compiler/typecheck/TcTyClsDecls.hs @@ -637,37 +637,55 @@ generaliseTcTyCon tc {- Note [Required, Specified, and Inferred for types] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -We have some design choices in how we classify the tyvars bound -in a type declaration. (Here, I use "type" to refer to any TyClDecl.) -Much of the debate is memorialized in #15743. This Note documents -the final conclusion. - -First, a reminder: - * a Required argument is one that must be provided at every call site - * a Specified argument is one that can be inferred at call sites, but - may be instantiated with visible type application - * an Inferred argument is one that must be inferred at call sites; it - is unavailable for use with visible type application. - -Why have Inferred at all? Because we just can't make user-facing promises -about the ordering of some variables. These might swizzle around even between -minor released. By forbidding visible type application, we ensure users -aren't caught unawares. See also -Note [VarBndrs, TyCoVarBinders, TyConBinders, and visibility] in TyCoRep. - -When inferring the ordering of variables (that is, for those -variables that he user has not specified the order with an explicit `forall`) -we use the following order: - - 1. Inferred variables from an enclosing class (associated types only) - 2. Specified variables from an enclosing class (associated types only) - 3. Inferred variables not from an enclosing class - 4. Specified variables not from an enclosing class - 5. Required variables before a top-level :: - 6. All variables after a top-level :: +Each forall'd type variable in a type or kind is one of + + * Required: an argument must be provided at every call site + + * Specified: the argument can be inferred at call sites, but + may be instantiated with visible type/kind application + + * Inferred: the must be inferred at call sites; it + is unavailable for use with visible type/kind application. + +Why have Inferred at all? Because we just can't make user-facing +promises about the ordering of some variables. These might swizzle +around even between minor released. By forbidding visible type +application, we ensure users aren't caught unawares. + +Go read Note [VarBndrs, TyCoVarBinders, TyConBinders, and visibility] in TyCoRep. + +The question for this Note is this: + given a TyClDecl, how are its quantified type variables classified? +Much of the debate is memorialized in #15743. + +Here is our design choice. When inferring the ordering of variables +for a TyCl declaration (that is, for those variables that he user +has not specified the order with an explicit `forall`), we use the +following order: + + 1. Inferred variables + 2. Specified variables; in the left-to-right order in which + the user wrote them, modified by scopedSort (see below) + to put them in depdendency order. + 3. Required variables before a top-level :: + 4. All variables after a top-level :: If this ordering does not make a valid telescope, we reject the definition. +Example: + data SameKind :: k -> k -> * + data X a (b :: SameKind a b) (c :: k) d + +For X: + - a, b, c, d are Required; they are explicitly listed by the user + as the positional arguments of X + - k is Specified; it appears explicitly in a kind signature + - k2, the kind of d, is Inferred; it is not mentioned explicitly at all + +Putting variables in the order Inferred, Specified, Required gives us + Inferred: k2 + Specified: k (a ::kb + This idea is implemented in the generalise function within kcTyClGroup (for declarations without CUSKs), and in kcLHsQTyVars (for declarations with CUSKs). Note that neither definition worries about point (6) above, as this From git at git.haskell.org Mon Nov 19 20:48:22 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Nov 2018 20:48:22 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Finally done (19fb060) Message-ID: <20181119204822.2AB9F3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/19fb0607174a5dd5200a6f16b09e963c6d549ceb/ghc >--------------------------------------------------------------- commit 19fb0607174a5dd5200a6f16b09e963c6d549ceb Author: Simon Peyton Jones Date: Wed Nov 7 12:51:32 2018 +0000 Finally done >--------------------------------------------------------------- 19fb0607174a5dd5200a6f16b09e963c6d549ceb compiler/typecheck/TcHsType.hs | 128 +++----------- compiler/typecheck/TcMType.hs | 63 +++---- compiler/typecheck/TcTyClsDecls.hs | 188 ++++++++++++++++----- compiler/typecheck/TcValidity.hs | 77 ++++++--- .../dependent/should_fail/BadTelescope.stderr | 7 +- .../dependent/should_fail/BadTelescope3.stderr | 6 +- .../dependent/should_fail/BadTelescope4.stderr | 13 +- .../tests/dependent/should_fail/T13895.stderr | 37 +--- .../tests/dependent/should_fail/T14066f.stderr | 6 +- .../tests/dependent/should_fail/T14066g.stderr | 8 +- .../tests/dependent/should_fail/T15591b.stderr | 9 +- .../tests/dependent/should_fail/T15591c.stderr | 9 +- .../tests/dependent/should_fail/T15743c.stderr | 13 +- .../tests/dependent/should_fail/T15743d.stderr | 13 +- testsuite/tests/ghci/scripts/T15591.hs | 9 +- testsuite/tests/ghci/scripts/T15591.stdout | 6 +- 16 files changed, 312 insertions(+), 280 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 19fb0607174a5dd5200a6f16b09e963c6d549ceb From git at git.haskell.org Mon Nov 19 20:48:25 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Nov 2018 20:48:25 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Wibbles (3fd542e) Message-ID: <20181119204825.28AC73A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/3fd542e4aa25344d13d36570f4bc8a262f286e3c/ghc >--------------------------------------------------------------- commit 3fd542e4aa25344d13d36570f4bc8a262f286e3c Author: Simon Peyton Jones Date: Mon Nov 19 11:32:56 2018 +0000 Wibbles >--------------------------------------------------------------- 3fd542e4aa25344d13d36570f4bc8a262f286e3c compiler/typecheck/TcTyClsDecls.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/typecheck/TcTyClsDecls.hs b/compiler/typecheck/TcTyClsDecls.hs index 0f8057d..e1c570d 100644 --- a/compiler/typecheck/TcTyClsDecls.hs +++ b/compiler/typecheck/TcTyClsDecls.hs @@ -1879,7 +1879,7 @@ tcFamTyPatsAndGen fam_tc mb_clsinfo imp_vars exp_bndrs hs_pats thing_inside tcFamTyPats :: TyCon -> Maybe ClsInstInfo -> HsTyPats GhcRn -- Patterns -> TcM ([TcType], TcKind) -- (pats, rhs_kind) -tcFamTyPats fam_tc mb_clsinfo hs_pats +tcFamTyPats fam_tc _mb_clsinfo hs_pats = do { traceTc "tcFamTyPats {" $ vcat [ ppr fam_tc <+> dcolon <+> ppr fun_kind , text "arity:" <+> ppr fam_arity @@ -1911,7 +1911,7 @@ tcFamTyPats fam_tc mb_clsinfo hs_pats fun_kind = tyConKind fam_tc lhs_fun = noLoc (HsTyVar noExt NotPromoted (noLoc fam_name)) (invis_bndrs, body_kind) = splitPiTysInvisibleN fam_arity fun_kind - mb_kind_env = thdOf3 <$> mb_clsinfo +-- mb_kind_env = thdOf3 <$> mb_clsinfo bad_lhs fam_app = hang (text "Ill-typed LHS of family instance") From git at git.haskell.org Mon Nov 19 20:48:28 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Nov 2018 20:48:28 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Start to eliminate tcFamTyPats (f22df63) Message-ID: <20181119204828.242643A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/f22df63ae8f31a8ede62a7415a0b16dfd20cc7b3/ghc >--------------------------------------------------------------- commit f22df63ae8f31a8ede62a7415a0b16dfd20cc7b3 Author: Simon Peyton Jones Date: Mon Nov 12 13:41:33 2018 +0000 Start to eliminate tcFamTyPats >--------------------------------------------------------------- f22df63ae8f31a8ede62a7415a0b16dfd20cc7b3 compiler/typecheck/TcHsType.hs | 1 + compiler/typecheck/TcTyClsDecls.hs | 20 ++++++++------------ 2 files changed, 9 insertions(+), 12 deletions(-) diff --git a/compiler/typecheck/TcHsType.hs b/compiler/typecheck/TcHsType.hs index 7f637b7..fe8c1a0 100644 --- a/compiler/typecheck/TcHsType.hs +++ b/compiler/typecheck/TcHsType.hs @@ -21,6 +21,7 @@ module TcHsType ( UserTypeCtxt(..), bindImplicitTKBndrs_Skol, bindImplicitTKBndrs_Q_Skol, bindExplicitTKBndrs_Skol, bindExplicitTKBndrs_Q_Skol, + ContextKind(..), -- Type checking type and class decls kcLookupTcTyCon, kcTyClTyVars, tcTyClTyVars, diff --git a/compiler/typecheck/TcTyClsDecls.hs b/compiler/typecheck/TcTyClsDecls.hs index 5b5d858..b9227de 100644 --- a/compiler/typecheck/TcTyClsDecls.hs +++ b/compiler/typecheck/TcTyClsDecls.hs @@ -1760,6 +1760,7 @@ tcTyFamInstEqn :: TcTyCon -> Maybe ClsInstInfo -> LTyFamInstEqn GhcRn -- (typechecked here) have TyFamInstEqns +{- tcTyFamInstEqn fam_tc mb_clsinfo (L loc (HsIB { hsib_ext = imp_vars , hsib_body = FamEqn { feqn_tycon = L _ eqn_tc_name @@ -1780,8 +1781,8 @@ tcTyFamInstEqn fam_tc mb_clsinfo ; return (mkCoAxBranch tvs' [] pats' rhs_ty' (map (const Nominal) tvs') loc) } +-} -{- tcTyFamInstEqn fam_tc mb_clsinfo eqn@(L loc (HsIB { hsib_ext = imp_vars , hsib_body = FamEqn { feqn_tycon = L _ eqn_tc_name @@ -1790,12 +1791,12 @@ tcTyFamInstEqn fam_tc mb_clsinfo , feqn_rhs = hs_ty }})) = ASSERT( getName fam_tc == eqn_tc_name ) setSrcSpan loc $ - do { traceTc "tcTyFamInstEqn {" (ppr eqn) - ; (imp_tvs, (exp_tvs, ((pats, rhs_ty)))) + do { traceTc "tcTyFamInstEqn {" (ppr eqn_tc_name <+> ppr hs_pats) + ; (_imp_tvs, (_exp_tvs, ((pats, rhs_ty)))) <- pushTcLevelM_ $ solveEqualities $ bindImplicitTKBndrs_Q_Skol imp_vars $ - bindExplicitTKBndrs_Q_Skol (mb_expl_bndrs `orElse` []) $ + bindExplicitTKBndrs_Q_Skol AnyKind (mb_expl_bndrs `orElse` []) $ do { let fam_name = tyConName fam_tc lhs_fun = L loc (HsTyVar noExt NotPromoted (L loc fam_name)) @@ -1808,21 +1809,16 @@ tcTyFamInstEqn fam_tc mb_clsinfo ; rhs_ty <- tcCheckLHsType hs_ty res_kind ; return (pats, rhs_ty) } - ; imp_tvs <- zonkAndScopedSort imp_tvs - ; let spec_req_tkvs = imp_tvs ++ exp_tvs - ; dvs <- candidateQTyVarsOfKinds $ - typeKind rhs_ty : map tyVarKind (spec_req_tkvs) - ; let final_dvs = dvs `delCandidates` spec_req_tkvs - ; inferred_kvs <- quantifyTyVars emptyVarSet final_dvs + ; dvs <- candidateQTyVarsOfTypes (rhs_ty : pats) + ; qtkvs <- quantifyTyVars emptyVarSet dvs - ; (ze, tvs') <- zonkTyBndrs (inferred_kvs ++ spec_req_tkvs) + ; (ze, tvs') <- zonkTyBndrs qtkvs ; pats' <- zonkTcTypesToTypesX ze pats ; rhs_ty' <- zonkTcTypeToTypeX ze rhs_ty ; traceTc "tcTyFamInstEqn }" (ppr fam_tc <+> pprTyVars tvs') ; return (mkCoAxBranch tvs' [] pats' rhs_ty' (map (const Nominal) tvs') loc) } --} tcTyFamInstEqn _ _ (L _ (XHsImplicitBndrs _)) = panic "tcTyFamInstEqn" From git at git.haskell.org Mon Nov 19 20:48:31 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Nov 2018 20:48:31 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Better validity checks, simplification (04aa622) Message-ID: <20181119204831.2952A3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/04aa622b96554205e84f2f5aac49b8ff7f4cfe90/ghc >--------------------------------------------------------------- commit 04aa622b96554205e84f2f5aac49b8ff7f4cfe90 Author: Simon Peyton Jones Date: Thu Nov 15 23:29:34 2018 +0000 Better validity checks, simplification >--------------------------------------------------------------- 04aa622b96554205e84f2f5aac49b8ff7f4cfe90 compiler/typecheck/TcGenDeriv.hs | 3 +- compiler/typecheck/TcHsType.hs | 66 +++--- compiler/typecheck/TcInstDcls.hs | 43 +++- compiler/typecheck/TcTyClsDecls.hs | 223 ++++++++++++++++++- compiler/typecheck/TcValidity.hs | 238 ++------------------- .../should_fail/ExplicitForAllFams4b.stderr | 63 ++++-- .../indexed-types/should_fail/SimpleFail2a.stderr | 2 +- .../tests/indexed-types/should_fail/T14045a.stderr | 2 +- testsuite/tests/polykinds/T13985.hs | 1 + testsuite/tests/polykinds/T13985.stderr | 10 +- 10 files changed, 338 insertions(+), 313 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 04aa622b96554205e84f2f5aac49b8ff7f4cfe90 From git at git.haskell.org Mon Nov 19 20:48:34 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Nov 2018 20:48:34 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Nearly there... (6ab2bae) Message-ID: <20181119204834.326EE3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/6ab2baeef6b6abc775398b927a28d00b983a2a67/ghc >--------------------------------------------------------------- commit 6ab2baeef6b6abc775398b927a28d00b983a2a67 Author: Simon Peyton Jones Date: Thu Nov 15 17:43:18 2018 +0000 Nearly there... >--------------------------------------------------------------- 6ab2baeef6b6abc775398b927a28d00b983a2a67 compiler/typecheck/TcGenDeriv.hs | 8 +- compiler/typecheck/TcHsType.hs | 2 - compiler/typecheck/TcInstDcls.hs | 12 +- compiler/typecheck/TcTyClsDecls.hs | 100 ++-------------- compiler/typecheck/TcValidity.hs | 132 +++++++++++++++++---- testsuite/tests/ghci/scripts/T6018ghcifail.stderr | 4 +- .../should_fail/ExplicitForAllFams4a.stderr | 10 +- .../should_fail/ExplicitForAllFams4b.stderr | 20 ++-- .../indexed-types/should_fail/SimpleFail13.stderr | 2 +- .../indexed-types/should_fail/SimpleFail2a.hs | 12 +- .../indexed-types/should_fail/SimpleFail9.stderr | 4 +- .../tests/indexed-types/should_fail/T7536.stderr | 5 +- testsuite/tests/polykinds/T13985.stderr | 10 +- .../tests/th/TH_reifyExplicitForAllFams.stderr | 6 +- .../tests/typecheck/should_fail/T6018fail.stderr | 4 +- 15 files changed, 169 insertions(+), 162 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 6ab2baeef6b6abc775398b927a28d00b983a2a67 From git at git.haskell.org Mon Nov 19 20:48:37 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Nov 2018 20:48:37 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Get rid of kcLHsQTyVarBndrs (ce50177) Message-ID: <20181119204837.4409C3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/ce50177c151dc8e7c5a6b9a762f7c9e18f4618e2/ghc >--------------------------------------------------------------- commit ce50177c151dc8e7c5a6b9a762f7c9e18f4618e2 Author: Simon Peyton Jones Date: Mon Nov 12 12:08:33 2018 +0000 Get rid of kcLHsQTyVarBndrs >--------------------------------------------------------------- ce50177c151dc8e7c5a6b9a762f7c9e18f4618e2 compiler/typecheck/TcHsType.hs | 289 +++++++++++++++++++-------------------- compiler/typecheck/TcMType.hs | 2 +- compiler/typecheck/TcValidity.hs | 21 --- 3 files changed, 138 insertions(+), 174 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 ce50177c151dc8e7c5a6b9a762f7c9e18f4618e2 From git at git.haskell.org Mon Nov 19 20:48:40 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Nov 2018 20:48:40 +0000 (UTC) Subject: [commit: ghc] wip/T15809: More progress (6e0aab6) Message-ID: <20181119204840.4F61E3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/6e0aab673ad997bbebb876cf65abea4d22cd8d63/ghc >--------------------------------------------------------------- commit 6e0aab673ad997bbebb876cf65abea4d22cd8d63 Author: Simon Peyton Jones Date: Tue Nov 6 08:55:37 2018 +0000 More progress >--------------------------------------------------------------- 6e0aab673ad997bbebb876cf65abea4d22cd8d63 compiler/typecheck/TcEnv.hs | 2 +- compiler/typecheck/TcHsSyn.hs | 7 ++++- compiler/typecheck/TcHsType.hs | 4 --- compiler/typecheck/TcMType.hs | 14 ++++----- compiler/typecheck/TcRnDriver.hs | 2 +- compiler/typecheck/TcSimplify.hs | 2 +- compiler/typecheck/TcTyClsDecls.hs | 61 +++++++++++++++++++++++++------------- 7 files changed, 57 insertions(+), 35 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 6e0aab673ad997bbebb876cf65abea4d22cd8d63 From git at git.haskell.org Mon Nov 19 20:48:43 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Nov 2018 20:48:43 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Comments only (3dcc2c6) Message-ID: <20181119204843.54EE83A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/3dcc2c63066159442b407d6b6c8efac0ecc73bf9/ghc >--------------------------------------------------------------- commit 3dcc2c63066159442b407d6b6c8efac0ecc73bf9 Author: Simon Peyton Jones Date: Fri Nov 9 17:46:05 2018 +0000 Comments only >--------------------------------------------------------------- 3dcc2c63066159442b407d6b6c8efac0ecc73bf9 compiler/typecheck/TcMType.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/compiler/typecheck/TcMType.hs b/compiler/typecheck/TcMType.hs index 9edad0f..6d9f3ca 100644 --- a/compiler/typecheck/TcMType.hs +++ b/compiler/typecheck/TcMType.hs @@ -662,7 +662,8 @@ but this restriction was dropped, and ScopedTypeVariables can now refer to full types (GHC Proposal 29). The remaining uses of newTyVarTyVars are -* in kind signatures, see Note [Kind generalisation and TyVarTvs] +* In kind signatures, see + TcTyClsDecls Note [Inferring kinds for type declarations] and Note [Use TyVarTvs in kind-checking pass] * in partial type signatures, see Note [Quantified variables in partial type signatures] -} From git at git.haskell.org Mon Nov 19 20:48:46 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Nov 2018 20:48:46 +0000 (UTC) Subject: [commit: ghc] wip/T15809: WIP on using level numbers for generalisation (9ecec6f) Message-ID: <20181119204846.630CC3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/9ecec6f15172e47e81095d0893b13e6d8fc400a8/ghc >--------------------------------------------------------------- commit 9ecec6f15172e47e81095d0893b13e6d8fc400a8 Author: Simon Peyton Jones Date: Wed Oct 31 08:40:40 2018 +0000 WIP on using level numbers for generalisation This mostly works. So far I simply have a WARNING in quantifyTyVars which fires if the two methods (old "global-tyvars" and new "level-numbers") give different answers. Some modest but important refactoring along the way. Main thing that is still wrong: in instance declarations we are not skoelmising. Here's a partial patch to TcInstDcls, that /doesn't/ yet work -- Next, process any associated types. ; traceTc "tcLocalInstDecl" (ppr poly_ty) - ; tyfam_insts0 <- scopeTyVars InstSkol tyvars $ - mapAndRecoverM (tcTyFamInstDecl mb_info) ats - ; datafam_stuff <- scopeTyVars InstSkol tyvars $ - mapAndRecoverM (tcDataFamInstDecl mb_info) adts + ; (_subst, skol_tvs) <- tcInstSkolTyVars tyvars + ; (tyfam_insts0, datafam_stuff) + <- tcExtendNameTyVarEnv (map tyVarName tyvars `zip` skol_tvs) $ + do { tfs <- mapAndRecoverM (tcTyFamInstDecl mb_info) ats + ; dfs <- mapAndRecoverM (tcDataFamInstDecl mb_info) adts + ; return (tfs, dfs) } ; let (datafam_insts, m_deriv_infos) = unzip datafam_stuff >--------------------------------------------------------------- 9ecec6f15172e47e81095d0893b13e6d8fc400a8 compiler/typecheck/TcHsType.hs | 95 ++++++++++++++++++++++++------------ compiler/typecheck/TcMType.hs | 99 ++++++++++++++++++++++++++------------ compiler/typecheck/TcSimplify.hs | 19 +++++--- compiler/typecheck/TcTyClsDecls.hs | 86 ++++++++++++++++----------------- compiler/typecheck/TcValidity.hs | 12 ++--- 5 files changed, 192 insertions(+), 119 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 9ecec6f15172e47e81095d0893b13e6d8fc400a8 From git at git.haskell.org Mon Nov 19 20:48:49 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Nov 2018 20:48:49 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Wibbles (65954ac) Message-ID: <20181119204849.632F93A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/65954acf496d6bd7e8a62a7b5d68b4c2383efaa3/ghc >--------------------------------------------------------------- commit 65954acf496d6bd7e8a62a7b5d68b4c2383efaa3 Author: Simon Peyton Jones Date: Wed Nov 14 17:28:35 2018 +0000 Wibbles >--------------------------------------------------------------- 65954acf496d6bd7e8a62a7b5d68b4c2383efaa3 compiler/typecheck/TcHsType.hs | 2 +- compiler/typecheck/TcInstDcls.hs | 188 ++++++++------------------------------- 2 files changed, 36 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 65954acf496d6bd7e8a62a7b5d68b4c2383efaa3 From git at git.haskell.org Mon Nov 19 20:48:52 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Nov 2018 20:48:52 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Data family instances working, I think (f60929b) Message-ID: <20181119204852.6D47A3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/f60929b4270c3a7f225d4c0dfb0ccbfc6cbc0ed7/ghc >--------------------------------------------------------------- commit f60929b4270c3a7f225d4c0dfb0ccbfc6cbc0ed7 Author: Simon Peyton Jones Date: Wed Nov 14 11:36:22 2018 +0000 Data family instances working, I think >--------------------------------------------------------------- f60929b4270c3a7f225d4c0dfb0ccbfc6cbc0ed7 compiler/typecheck/TcInstDcls.hs | 154 +++++++++++++++++++++++++++++++++++++ compiler/typecheck/TcTyClsDecls.hs | 68 ++++++++-------- 2 files changed, 191 insertions(+), 31 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc f60929b4270c3a7f225d4c0dfb0ccbfc6cbc0ed7 From git at git.haskell.org Mon Nov 19 20:48:55 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Nov 2018 20:48:55 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Comments and alpha-renaming (b2ac6e7) Message-ID: <20181119204855.66EB63A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/b2ac6e77e189145f6f40c35e71b06fef318b9887/ghc >--------------------------------------------------------------- commit b2ac6e77e189145f6f40c35e71b06fef318b9887 Author: Simon Peyton Jones Date: Wed Nov 7 23:26:05 2018 +0000 Comments and alpha-renaming >--------------------------------------------------------------- b2ac6e77e189145f6f40c35e71b06fef318b9887 compiler/typecheck/TcHsType.hs | 2 -- compiler/typecheck/TcInstDcls.hs | 10 +++++----- compiler/typecheck/TcMType.hs | 2 +- compiler/typecheck/TcSimplify.hs | 7 ++++--- 4 files changed, 10 insertions(+), 11 deletions(-) diff --git a/compiler/typecheck/TcHsType.hs b/compiler/typecheck/TcHsType.hs index 2ce23e7..dd2995e 100644 --- a/compiler/typecheck/TcHsType.hs +++ b/compiler/typecheck/TcHsType.hs @@ -1744,7 +1744,6 @@ kcImplicitTKBndrs = kcImplicitTKBndrsX newFlexiKindedTyVarTyVar -- | Bring implicitly quantified type/kind variables into scope during -- kind checking. The returned TcTyVars are in 1-1 correspondence --- with the names passed in. --- Note [Use TyVarTvs in kind-checking pass] in TcTyClsDecls. kcImplicitTKBndrsX :: (Name -> TcM TcTyVar) -- new_tv function -> [Name] -- of the vars -> TcM a @@ -2065,7 +2064,6 @@ kcLookupTcTyCon nm -- Never emits constraints, though the thing_inside might. kcTyClTyVars :: Name -> TcM a -> TcM a kcTyClTyVars tycon_name thing_inside - -- See Note [Use TyVarTvs in kind-checking pass] in TcTyClsDecls = do { tycon <- kcLookupTcTyCon tycon_name ; tcExtendNameTyVarEnv (tcTyConScopedTyVars tycon) $ thing_inside } diff --git a/compiler/typecheck/TcInstDcls.hs b/compiler/typecheck/TcInstDcls.hs index 84f43e9..63c565d 100644 --- a/compiler/typecheck/TcInstDcls.hs +++ b/compiler/typecheck/TcInstDcls.hs @@ -465,14 +465,14 @@ tcLocalInstDecl (L _ (XInstDecl _)) = panic "tcLocalInstDecl" tcClsInstDecl :: LClsInstDecl GhcRn -> TcM ([InstInfo GhcRn], [FamInst], [DerivInfo]) -- The returned DerivInfos are for any associated data families -tcClsInstDecl (L loc (ClsInstDecl { cid_poly_ty = poly_ty, cid_binds = binds +tcClsInstDecl (L loc (ClsInstDecl { cid_poly_ty = hs_ty, cid_binds = binds , cid_sigs = uprags, cid_tyfam_insts = ats , cid_overlap_mode = overlap_mode , cid_datafam_insts = adts })) = setSrcSpan loc $ - addErrCtxt (instDeclCtxt1 poly_ty) $ + addErrCtxt (instDeclCtxt1 hs_ty) $ do { (tyvars, theta, clas, inst_tys) - <- tcHsClsInstType (InstDeclCtxt False) poly_ty + <- tcHsClsInstType (InstDeclCtxt False) hs_ty -- NB: tcHsClsInstType does checkValidInstance ; tcExtendTyVarEnv tyvars $ @@ -481,7 +481,7 @@ tcClsInstDecl (L loc (ClsInstDecl { cid_poly_ty = poly_ty, cid_binds = binds mb_info = Just (clas, tyvars, mini_env) -- Next, process any associated types. - ; traceTc "tcLocalInstDecl" (ppr poly_ty) + ; traceTc "tcLocalInstDecl" (ppr hs_ty) ; tyfam_insts0 <- mapAndRecoverM (tcTyFamInstDecl mb_info) ats ; datafam_stuff <- mapAndRecoverM (tcDataFamInstDecl mb_info) adts ; let (datafam_insts, m_deriv_infos) = unzip datafam_stuff @@ -500,7 +500,7 @@ tcClsInstDecl (L loc (ClsInstDecl { cid_poly_ty = poly_ty, cid_binds = binds -- Finally, construct the Core representation of the instance. -- (This no longer includes the associated types.) - ; dfun_name <- newDFunName clas inst_tys (getLoc (hsSigType poly_ty)) + ; dfun_name <- newDFunName clas inst_tys (getLoc (hsSigType hs_ty)) -- Dfun location is that of instance *header* ; ispec <- newClsInst (fmap unLoc overlap_mode) dfun_name tyvars theta diff --git a/compiler/typecheck/TcMType.hs b/compiler/typecheck/TcMType.hs index 8192f75..9edad0f 100644 --- a/compiler/typecheck/TcMType.hs +++ b/compiler/typecheck/TcMType.hs @@ -1499,7 +1499,7 @@ defaultTyVar default_kind tv -- Do not default TyVarTvs. Doing so would violate the invariants -- on TyVarTvs; see Note [Signature skolems] in TcType. -- Trac #13343 is an example; #14555 is another - -- See Note [Kind generalisation and TyVarTvs] + -- See Note [Inferring kinds for type declarations] in TcTyClsDecls = return False diff --git a/compiler/typecheck/TcSimplify.hs b/compiler/typecheck/TcSimplify.hs index 750b621..e1a3532 100644 --- a/compiler/typecheck/TcSimplify.hs +++ b/compiler/typecheck/TcSimplify.hs @@ -2008,9 +2008,10 @@ promoteTyVarTcS tv defaultTyVarTcS :: TcTyVar -> TcS Bool defaultTyVarTcS the_tv | isRuntimeRepVar the_tv - , not (isTyVarTyVar the_tv) -- TyVarTvs should only be unified with a tyvar - -- never with a type; c.f. TcMType.defaultTyVar - -- See Note [Kind generalisation and TyVarTvs] + , not (isTyVarTyVar the_tv) + -- TyVarTvs should only be unified with a tyvar + -- never with a type; c.f. TcMType.defaultTyVar + -- and Note [Inferring kinds for type declarations] in TcTyClsDecls = do { traceTcS "defaultTyVarTcS RuntimeRep" (ppr the_tv) ; unifyTyVar the_tv liftedRepTy ; return True } From git at git.haskell.org Mon Nov 19 20:48:58 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Nov 2018 20:48:58 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Further progress (7b706d4) Message-ID: <20181119204858.6D00D3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/7b706d46636555b358f157fbe8f3d41e0155146f/ghc >--------------------------------------------------------------- commit 7b706d46636555b358f157fbe8f3d41e0155146f Author: Simon Peyton Jones Date: Mon Nov 5 17:43:08 2018 +0000 Further progress >--------------------------------------------------------------- 7b706d46636555b358f157fbe8f3d41e0155146f compiler/typecheck/TcHsSyn.hs | 28 ++++++----- compiler/typecheck/TcHsType.hs | 7 ++- compiler/typecheck/TcMType.hs | 95 ++++++++++++++++++++++++-------------- compiler/typecheck/TcRules.hs | 2 +- compiler/typecheck/TcSimplify.hs | 6 +-- compiler/typecheck/TcTyClsDecls.hs | 43 +++++++++-------- 6 files changed, 111 insertions(+), 70 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 7b706d46636555b358f157fbe8f3d41e0155146f From git at git.haskell.org Mon Nov 19 20:49:01 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Nov 2018 20:49:01 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Wibbles (11de61f) Message-ID: <20181119204901.6B60A3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/11de61f98c1c09e46f87ddce9cf0320d55a3097c/ghc >--------------------------------------------------------------- commit 11de61f98c1c09e46f87ddce9cf0320d55a3097c Author: Simon Peyton Jones Date: Mon Nov 12 17:43:48 2018 +0000 Wibbles >--------------------------------------------------------------- 11de61f98c1c09e46f87ddce9cf0320d55a3097c testsuite/tests/indexed-types/should_fail/T7536.stderr | 8 ++++---- testsuite/tests/indexed-types/should_fail/T7938.hs | 6 ++---- testsuite/tests/indexed-types/should_fail/T7938.stderr | 2 +- 3 files changed, 7 insertions(+), 9 deletions(-) diff --git a/testsuite/tests/indexed-types/should_fail/T7536.stderr b/testsuite/tests/indexed-types/should_fail/T7536.stderr index 9e7ed30..34a393e 100644 --- a/testsuite/tests/indexed-types/should_fail/T7536.stderr +++ b/testsuite/tests/indexed-types/should_fail/T7536.stderr @@ -1,5 +1,5 @@ -T7536.hs:8:15: - Family instance purports to bind type variable ‘a’ - but the real LHS (expanding synonyms) is: TF Int = ... - In the type instance declaration for ‘TF’ +T7536.hs:8:15: error: + • LHS of family instance fails to bind type variable ‘a’ + The real LHS (expanding synonyms) is: TF Int + • In the type instance declaration for ‘TF’ diff --git a/testsuite/tests/indexed-types/should_fail/T7938.hs b/testsuite/tests/indexed-types/should_fail/T7938.hs index f1e8266..246015d 100644 --- a/testsuite/tests/indexed-types/should_fail/T7938.hs +++ b/testsuite/tests/indexed-types/should_fail/T7938.hs @@ -8,7 +8,5 @@ data KProxy (a :: *) = KP class Foo (a :: k1) (b :: k2) where type Bar a --- instance Foo (a :: k1) (b :: k2) where --- type Bar a = (KP :: KProxy k2) - --- \ No newline at end of file +instance Foo (a :: k1) (b :: k2) where + type Bar a = (KP :: KProxy k2) diff --git a/testsuite/tests/indexed-types/should_fail/T7938.stderr b/testsuite/tests/indexed-types/should_fail/T7938.stderr index 890be7b..5751c4e 100644 --- a/testsuite/tests/indexed-types/should_fail/T7938.stderr +++ b/testsuite/tests/indexed-types/should_fail/T7938.stderr @@ -1,6 +1,6 @@ T7938.hs:12:17: error: - • Expected a type, but ‘KP :: KProxy k2’ has kind ‘KProxy k4’ + • Expected a type, but ‘KP :: KProxy k2’ has kind ‘KProxy k2’ • In the type ‘(KP :: KProxy k2)’ In the type instance declaration for ‘Bar’ In the instance declaration for ‘Foo (a :: k1) (b :: k2)’ From git at git.haskell.org Mon Nov 19 20:49:04 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Nov 2018 20:49:04 +0000 (UTC) Subject: [commit: ghc] wip/T15809: More wibbles (f575c3c) Message-ID: <20181119204904.649393A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/f575c3ce1cef9d024584e9c0b931c035d3380a31/ghc >--------------------------------------------------------------- commit f575c3ce1cef9d024584e9c0b931c035d3380a31 Author: Simon Peyton Jones Date: Mon Nov 19 20:45:09 2018 +0000 More wibbles >--------------------------------------------------------------- f575c3ce1cef9d024584e9c0b931c035d3380a31 compiler/typecheck/TcTyClsDecls.hs | 62 +++++++++++++++----------------------- 1 file changed, 24 insertions(+), 38 deletions(-) diff --git a/compiler/typecheck/TcTyClsDecls.hs b/compiler/typecheck/TcTyClsDecls.hs index e1c570d..7427035 100644 --- a/compiler/typecheck/TcTyClsDecls.hs +++ b/compiler/typecheck/TcTyClsDecls.hs @@ -67,7 +67,6 @@ import SrcLoc import ListSetOps import DynFlags import Unique -import UniqFM( nonDetEltsUFM ) import ConLike( ConLike(..) ) import BasicTypes import qualified GHC.LanguageExtensions as LangExt @@ -3222,8 +3221,7 @@ checkConsistentFamInst :: Maybe ClsInstInfo checkConsistentFamInst Nothing _ _ = return () checkConsistentFamInst (Just (clas, inst_tvs, mini_env)) fam_tc at_arg_tys = do { traceTc "checkConsistentFamInst" (vcat [ ppr inst_tvs - , ppr kind_prs - , ppr type_prs + , ppr arg_triples , ppr mini_env ]) -- Check that the associated type indeed comes from this class -- See [Mismatched class methods and associated type families] @@ -3231,28 +3229,16 @@ checkConsistentFamInst (Just (clas, inst_tvs, mini_env)) fam_tc at_arg_tys ; checkTc (Just (classTyCon clas) == tyConAssoc_maybe fam_tc) (badATErr (className clas) (tyConName fam_tc)) - -- Check kind args first, suggesting -fprint-explicit-kiinds - -- if there is a mis-match here. - ; checkTc (isJust mb_kinds_match) (pp_wrong_at_arg $$ ppSuggestExplicitKinds) - - -- Then type args. If we do these first, then we'll fail to - -- suggest -fprint-explicit-kinds for (T @k vs T @Type) - ; checkTc (isJust mb_types_match) pp_wrong_at_arg + ; check_match arg_triples } where - kind_prs, type_prs :: [(Type,Type)] - (kind_prs, type_prs) = partitionInvisibles $ - [ ((cls_arg_ty, at_arg_ty), vis) - | (fam_tc_tv, vis, at_arg_ty) - <- zip3 (tyConTyVars fam_tc) - (tyConArgFlags fam_tc at_arg_tys) - at_arg_tys - , Just cls_arg_ty <- [lookupVarEnv mini_env fam_tc_tv] ] - - - mb_types_match = alphaMatchTysX emptyTCvSubst type_prs - Just subst1 = mb_types_match - mb_kinds_match = alphaMatchTysX subst1 kind_prs + arg_triples :: [(Type,Type, ArgFlag)] + arg_triples = [ (cls_arg_ty, at_arg_ty, vis) + | (fam_tc_tv, vis, at_arg_ty) + <- zip3 (tyConTyVars fam_tc) + (tyConArgFlags fam_tc at_arg_tys) + at_arg_tys + , Just cls_arg_ty <- [lookupVarEnv mini_env fam_tc_tv] ] pp_wrong_at_arg = vcat [ text "Type indexes must match class instance head" , text "Expected:" <+> ppr (mkTyConApp fam_tc expected_args) @@ -3263,22 +3249,22 @@ checkConsistentFamInst (Just (clas, inst_tvs, mini_env)) fam_tc at_arg_tys underscore at_tv = mkTyVarTy (mkTyVar tv_name (tyVarKind at_tv)) tv_name = mkInternalName (mkAlphaTyVarUnique 1) (mkTyVarOcc "_") noSrcSpan -alphaMatchTysX :: TCvSubst -> [(Type,Type)] -> Maybe TCvSubst -alphaMatchTysX subst pairs - | null pairs = Just subst - | otherwise = go subst pairs - where - go :: TCvSubst -> [(Type,Type)] -> Maybe TCvSubst - go subst [] - | allDistinctTyVars emptyVarSet $ - nonDetEltsUFM (getTvSubstEnv subst) - = Just subst + check_match :: [(Type,Type, ArgFlag)] -> TcM () + check_match triples = go emptyTCvSubst emptyTCvSubst triples + + go _ _ [] = return () + go lr_subst rl_subst ((ty1,ty2,vis):triples) + | Just lr_subst1 <- tcMatchTyX lr_subst ty1 ty2 + , Just rl_subst1 <- tcMatchTyX rl_subst ty2 ty1 + = go lr_subst1 rl_subst1 triples | otherwise - = Nothing - go subst ((ty1,ty2):prs) - = case tcMatchTyX subst ty1 ty2 of - Just subst' -> go subst' prs - Nothing -> Nothing + = addErrTc (pp_wrong_at_arg $$ + ppWhen (isInvisibleArgFlag vis) ppSuggestExplicitKinds) + -- NB: checks left-to-right, kinds first. + -- If we types first, we'll fail to + -- suggest -fprint-explicit-kinds for a mis-match with + -- T @k vs T @Type + -- somewhere deep inside the type badATErr :: Name -> Name -> SDoc badATErr clas op From git at git.haskell.org Mon Nov 19 20:49:06 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 19 Nov 2018 20:49:06 +0000 (UTC) Subject: [commit: ghc] wip/T15809's head updated: More wibbles (f575c3c) Message-ID: <20181119204906.C93B63A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/T15809' now includes: 6677235 Some assertions and comments in scheduler 9696282 user's guide: typo in ViewPatterns example 6ba9aa5 Fix a typo in the description of -fabstract-refinement-hole-fits 912fd2b NCG: New code layout algorithm. fc670c4 fix T15898 6551797 Building GHC with hadrian on FreeBSD 921fd89 Fix #12525: Remove derived bindings from the TyThings from getBindings 92f8184 Fix #12906: GHC fails to typecheck Main module without main 5bf0786 Speed up MonadUtils.mapMaybeM 17e771e More compact Outputable instance for `Uniq(D)Set` 33f5725 Remove -Wamp flag (#11477) 798c943 Minor refactoring 0e7790a Fix trac #15702, as a followon to fix for #13704. 36fcf9e Introduce Int16# and Word16# ecfc7b4 Fix typo in docs 348ea16 Tiny refactor in exitScheduler 39fa4ee Tc-tracing, and order of arguments only 9ecec6f WIP on using level numbers for generalisation f96148e More progress on using level numbers for gen 4eadda8 Further work on TyCon generalisation 7b706d4 Further progress 6e0aab6 More progress 5318307 More progress e646676 More progress 92ec580 Comemnts only 19fb060 Finally done b2ac6e7 Comments and alpha-renaming 3dcc2c6 Comments only df731cb Progress b1a93a1 Combine kcImplicitTKBndrs and tcImplicitTKBndrs ce50177 Get rid of kcLHsQTyVarBndrs f22df63 Start to eliminate tcFamTyPats b3bab72 More progress on tcFamTyPats 11de61f Wibbles a4e43a8 Much more progress on tcFamTyPats f60929b Data family instances working, I think aa8409f Print tycon arity in -ddump-types 398119c More progress with data instances 65954ac Wibbles 4a17ead More progress on reporting unbound variables 6ab2bae Nearly there... 04aa622 Better validity checks, simplification 5e062be Finally, validate-clean ae72e3e Simplify typing of associated family instances 3fd542e Wibbles f575c3c More wibbles From git at git.haskell.org Tue Nov 20 13:32:58 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 20 Nov 2018 13:32:58 +0000 (UTC) Subject: [commit: ghc] master: Remove redundant check in cgCase (d13b7d6) Message-ID: <20181120133258.D78263A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d13b7d60650cb84af11ee15b3f51c3511548cfdb/ghc >--------------------------------------------------------------- commit d13b7d60650cb84af11ee15b3f51c3511548cfdb Author: Ömer Sinan Ağacan Date: Tue Nov 20 16:30:15 2018 +0300 Remove redundant check in cgCase D5339 (part of D5324) removed the dead case binder analysis done during CoreToStg so this condition always holds now. Test Plan: Validated locally. Reviewers: sgraf, bgamari, simonmar Subscribers: rwbarton, carter Differential Revision: https://phabricator.haskell.org/D5358 >--------------------------------------------------------------- d13b7d60650cb84af11ee15b3f51c3511548cfdb compiler/codeGen/StgCmmExpr.hs | 11 ++++------- 1 file changed, 4 insertions(+), 7 deletions(-) diff --git a/compiler/codeGen/StgCmmExpr.hs b/compiler/codeGen/StgCmmExpr.hs index e8d111f..2430a0d 100644 --- a/compiler/codeGen/StgCmmExpr.hs +++ b/compiler/codeGen/StgCmmExpr.hs @@ -304,13 +304,10 @@ cgCase (StgOpApp (StgPrimOp op) args _) bndr (AlgAlt tycon) alts | isEnumerationTyCon tycon -- Note [case on bool] = do { tag_expr <- do_enum_primop op args - -- If the binder is not dead, convert the tag to a constructor - -- and assign it. - ; unless (isDeadBinder bndr) $ do - { dflags <- getDynFlags - ; tmp_reg <- bindArgToReg (NonVoid bndr) - ; emitAssign (CmmLocal tmp_reg) - (tagToClosure dflags tycon tag_expr) } + ; dflags <- getDynFlags + ; tmp_reg <- bindArgToReg (NonVoid bndr) + ; emitAssign (CmmLocal tmp_reg) + (tagToClosure dflags tycon tag_expr) ; (mb_deflt, branches) <- cgAlgAltRhss (NoGcInAlts,AssignedDirectly) (NonVoid bndr) alts From git at git.haskell.org Tue Nov 20 15:29:21 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 20 Nov 2018 15:29:21 +0000 (UTC) Subject: [commit: nofib] master: Fix `make clean` for `real/compress` (7e5619a) Message-ID: <20181120152921.BBDA23A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/nofib On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7e5619a6abe7ce89eb55b411736025b31410f478/nofib >--------------------------------------------------------------- commit 7e5619a6abe7ce89eb55b411736025b31410f478 Author: Sebastian Graf Date: Tue Nov 20 12:47:34 2018 +0100 Fix `make clean` for `real/compress` Summary: The `make boot` phase of `real/compress` generates files that are cleaned up by `make clean` with `rm`. Doing `make clean` without a prior `make boot` leads to a failure. This just supplies `-f` to `rm` so that plain `make clean` no longer fails. Reviewers: O26 nofib Differential Revision: https://phabricator.haskell.org/D5359 >--------------------------------------------------------------- 7e5619a6abe7ce89eb55b411736025b31410f478 real/compress/Makefile | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/real/compress/Makefile b/real/compress/Makefile index 275ba77..2f87ccb 100644 --- a/real/compress/Makefile +++ b/real/compress/Makefile @@ -19,4 +19,4 @@ compress.stdout : compress.stdin compress clean :: - rm compress.stdin compress.stdout + rm -f compress.stdin compress.stdout From git at git.haskell.org Tue Nov 20 16:39:16 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 20 Nov 2018 16:39:16 +0000 (UTC) Subject: [commit: ghc] wip/T15809: More progress in tcFamTyPats (8f77e9e) Message-ID: <20181120163916.2B17F3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/8f77e9e48ed41fe94261c9e092920a80b3e2ece1/ghc >--------------------------------------------------------------- commit 8f77e9e48ed41fe94261c9e092920a80b3e2ece1 Author: Simon Peyton Jones Date: Tue Nov 20 16:36:06 2018 +0000 More progress in tcFamTyPats In particular, revert to taking account of the class instance types in tcFamTyPats, but by unification rather than by messing with tcInferApps >--------------------------------------------------------------- 8f77e9e48ed41fe94261c9e092920a80b3e2ece1 compiler/typecheck/Inst.hs | 31 ++++++++++++------ compiler/typecheck/TcHsType.hs | 54 +++++++------------------------- compiler/typecheck/TcTyClsDecls.hs | 64 +++++++++++++++++++++++++++----------- compiler/types/Type.hs | 15 ++++++++- 4 files changed, 92 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 8f77e9e48ed41fe94261c9e092920a80b3e2ece1 From git at git.haskell.org Wed Nov 21 00:29:36 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 21 Nov 2018 00:29:36 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Wibbles (8babe69) Message-ID: <20181121002936.550ED3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/8babe691794a69bc21b52950c5e515b3ada6266c/ghc >--------------------------------------------------------------- commit 8babe691794a69bc21b52950c5e515b3ada6266c Author: Simon Peyton Jones Date: Wed Nov 21 00:00:53 2018 +0000 Wibbles >--------------------------------------------------------------- 8babe691794a69bc21b52950c5e515b3ada6266c compiler/typecheck/TcMType.hs | 15 +++++++++++++ compiler/typecheck/TcRnTypes.hs | 8 ++++++- compiler/typecheck/TcTyClsDecls.hs | 25 +++++++++++----------- .../tests/indexed-types/should_fail/SimpleFail9.hs | 4 +++- 4 files changed, 37 insertions(+), 15 deletions(-) diff --git a/compiler/typecheck/TcMType.hs b/compiler/typecheck/TcMType.hs index 886a894..769a312 100644 --- a/compiler/typecheck/TcMType.hs +++ b/compiler/typecheck/TcMType.hs @@ -41,6 +41,7 @@ module TcMType ( newEvVar, newEvVars, newDict, newWanted, newWanteds, newHoleCt, cloneWanted, cloneWC, emitWanted, emitWantedEq, emitWantedEvVar, emitWantedEvVars, + emitDerivedEqs, newTcEvBinds, newNoTcEvBinds, addTcEvBind, newCoercionHole, fillCoercionHole, isFilledCoercionHole, @@ -232,6 +233,20 @@ emitWanted origin pty ; emitSimple $ mkNonCanonical ev ; return $ ctEvTerm ev } +emitDerivedEqs :: CtOrigin -> [(TcType,TcType)] -> TcM () +-- Emit some new derived nominal equalities +emitDerivedEqs origin pairs + | null pairs + = return () + | otherwise + = do { loc <- getCtLocM origin Nothing + ; emitSimples (listToBag (map (mk_one loc) pairs)) } + where + mk_one loc (ty1, ty2) + = mkNonCanonical $ + CtDerived { ctev_pred = mkPrimEqPred ty1 ty2 + , ctev_loc = loc } + -- | Emits a new equality constraint emitWantedEq :: CtOrigin -> TypeOrKind -> Role -> TcType -> TcType -> TcM Coercion emitWantedEq origin t_or_k role ty1 ty2 diff --git a/compiler/typecheck/TcRnTypes.hs b/compiler/typecheck/TcRnTypes.hs index a0a2c1e..8d2370d 100644 --- a/compiler/typecheck/TcRnTypes.hs +++ b/compiler/typecheck/TcRnTypes.hs @@ -3510,8 +3510,10 @@ data CtOrigin | NegateOrigin -- Occurrence of syntactic negation | ArithSeqOrigin (ArithSeqInfo GhcRn) -- [x..], [x..y] etc + | AssocFamPatOrigin -- When matching the patterns of an associated + -- family instance with that of its parent class | SectionOrigin - | TupleOrigin -- (..,..) + | TupleOrigin -- (..,..) | ExprSigOrigin -- e :: ty | PatSigOrigin -- p :: ty | PatOrigin -- Instantiating a polytyped pattern at a constructor @@ -3729,6 +3731,9 @@ pprCtOrigin (KindEqOrigin t1 (Just t2) _ _) = hang (ctoHerald <+> text "a kind equality arising from") 2 (sep [ppr t1, char '~', ppr t2]) +pprCtOrigin AssocFamPatOrigin + = text "when matching a family LHS with its class instance head" + pprCtOrigin (KindEqOrigin t1 Nothing _ _) = hang (ctoHerald <+> text "a kind equality when matching") 2 (ppr t1) @@ -3800,6 +3805,7 @@ pprCtO IfOrigin = text "an if expression" pprCtO (LiteralOrigin lit) = hsep [text "the literal", quotes (ppr lit)] pprCtO (ArithSeqOrigin seq) = hsep [text "the arithmetic sequence", quotes (ppr seq)] pprCtO SectionOrigin = text "an operator section" +pprCtO AssocFamPatOrigin = text "the LHS of a famly instance" pprCtO TupleOrigin = text "a tuple" pprCtO NegateOrigin = text "a use of syntactic negation" pprCtO (ScOrigin n) = text "the superclasses of an instance declaration" diff --git a/compiler/typecheck/TcTyClsDecls.hs b/compiler/typecheck/TcTyClsDecls.hs index 92977fb..7a8bc9e 100644 --- a/compiler/typecheck/TcTyClsDecls.hs +++ b/compiler/typecheck/TcTyClsDecls.hs @@ -39,7 +39,6 @@ import TcDeriv (DerivInfo) import TcHsType import Inst( tcInstTyBinders ) import TcMType -import TcUnify( unifyType ) import TysWiredIn ( unitTy ) import TcType import RnEnv( lookupConstructorFields ) @@ -1770,9 +1769,7 @@ tcTyFamInstEqn fam_tc mb_clsinfo ; (qtvs, pats, rhs_ty) <- tcFamTyPatsAndGen fam_tc mb_clsinfo imp_vars (mb_expl_bndrs `orElse` []) hs_pats - (\ res_kind -> - do { traceTc "tcTyFasmInstEqn" (ppr fam_tc $$ ppr hs_pats $$ ppr res_kind) - ; tcCheckLHsType rhs_hs_ty res_kind }) + (tcCheckLHsType rhs_hs_ty res_kind) ; (ze, qtvs') <- zonkTyBndrs qtvs ; pats' <- zonkTcTypesToTypesX ze pats @@ -1932,16 +1929,19 @@ addConsistencyConstraints :: Maybe ClsInstInfo -> TyCon -> [Type] -> TcM () -- F c x y a :: Type -- Here the first arg of F should be the same as the third of C -- and the fourth arg of F should be the same as the first of C - +-- +-- We emit /Derived/ constraints (a bit like fundeps) to encourage +-- unification to happen, but without actually reporting errors. +-- If, despite the efforts, corresponding positions do not match, +-- checkConsistentFamInst will complain addConsistencyConstraints Nothing _ _ = return () addConsistencyConstraints (Just (_, _, inst_ty_env)) fam_tc pats - = mapM_ do_one (tyConTyVars fam_tc `zip` pats) - where - do_one (fam_tc_tv, pat) - | Just cls_arg_ty <- lookupVarEnv inst_ty_env fam_tc_tv - = discardResult (unifyType Nothing cls_arg_ty pat) - | otherwise - = return () + = emitDerivedEqs AssocFamPatOrigin + [ (cls_ty, pat) + | (fam_tc_tv, pat) <- tyConTyVars fam_tc `zip` pats + , Just cls_ty <- [lookupVarEnv inst_ty_env fam_tc_tv] ] + -- Improve inference + -- Any mis-match is reports by checkConsistentFamInst {- Note [Constraints in patterns] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -3237,7 +3237,6 @@ checkFamFlag tc_name -- types. type ClsInstInfo = (Class, [TyVar], VarEnv Type) - checkConsistentFamInst :: Maybe ClsInstInfo -> TyCon -- ^ Family tycon -> [Type] -- ^ Type patterns from instance diff --git a/testsuite/tests/indexed-types/should_fail/SimpleFail9.hs b/testsuite/tests/indexed-types/should_fail/SimpleFail9.hs index 9c1c4a8..0f20f78 100644 --- a/testsuite/tests/indexed-types/should_fail/SimpleFail9.hs +++ b/testsuite/tests/indexed-types/should_fail/SimpleFail9.hs @@ -2,8 +2,10 @@ module ShouldFail where +import Data.Kind + class C7 a b where - data S7 b :: * + data S7 b :: Type instance C7 Char (a, Bool) where data S7 (a, Bool) = S7_1 From git at git.haskell.org Wed Nov 21 13:56:19 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 21 Nov 2018 13:56:19 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Wibble, to fix build (4e11d6c) Message-ID: <20181121135620.0316E3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/4e11d6c217226370681cd97bf04217271c63f21c/ghc >--------------------------------------------------------------- commit 4e11d6c217226370681cd97bf04217271c63f21c Author: Simon Peyton Jones Date: Wed Nov 21 13:55:54 2018 +0000 Wibble, to fix build >--------------------------------------------------------------- 4e11d6c217226370681cd97bf04217271c63f21c compiler/typecheck/TcTyClsDecls.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/typecheck/TcTyClsDecls.hs b/compiler/typecheck/TcTyClsDecls.hs index 7a8bc9e..1fc675c 100644 --- a/compiler/typecheck/TcTyClsDecls.hs +++ b/compiler/typecheck/TcTyClsDecls.hs @@ -1769,7 +1769,7 @@ tcTyFamInstEqn fam_tc mb_clsinfo ; (qtvs, pats, rhs_ty) <- tcFamTyPatsAndGen fam_tc mb_clsinfo imp_vars (mb_expl_bndrs `orElse` []) hs_pats - (tcCheckLHsType rhs_hs_ty res_kind) + (tcCheckLHsType rhs_hs_ty) ; (ze, qtvs') <- zonkTyBndrs qtvs ; pats' <- zonkTcTypesToTypesX ze pats From git at git.haskell.org Wed Nov 21 17:30:31 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 21 Nov 2018 17:30:31 +0000 (UTC) Subject: [commit: ghc] master: Fix heap corruption during stable name allocation (691aa71) Message-ID: <20181121173031.095EF3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/691aa715cf43bf9d88ee32bca37e471bae35adfb/ghc >--------------------------------------------------------------- commit 691aa715cf43bf9d88ee32bca37e471bae35adfb Author: Ömer Sinan Ağacan Date: Wed Nov 21 20:03:38 2018 +0300 Fix heap corruption during stable name allocation See #15906 for the problem. To fix we simply call `allocate()` instead of `ALLOC_PRIM()`. `allocate()` does not trigger GC when the nursery is full, instead it extends it. Test Plan: This validates. memo001 now passes with `-debug` compile parameter. I'll add another test that runs memo001 with `-debug` once I figure out how to use stdout files for multiple tests. Reviewers: simonmar, bgamari, erikd Reviewed By: simonmar Subscribers: rwbarton, carter GHC Trac Issues: #15906 Differential Revision: https://phabricator.haskell.org/D5342 >--------------------------------------------------------------- 691aa715cf43bf9d88ee32bca37e471bae35adfb rts/PrimOps.cmm | 15 +++++++++++++-- 1 file changed, 13 insertions(+), 2 deletions(-) diff --git a/rts/PrimOps.cmm b/rts/PrimOps.cmm index a5d8553..625f5f5 100644 --- a/rts/PrimOps.cmm +++ b/rts/PrimOps.cmm @@ -1893,14 +1893,25 @@ stg_makeStableNamezh ( P_ obj ) { W_ index, sn_obj; + MAYBE_GC_P(stg_makeStableNamezh, obj); + (index) = ccall lookupStableName(obj "ptr"); /* Is there already a StableName for this heap object? * stable_name_table is a pointer to an array of snEntry structs. */ if ( snEntry_sn_obj(W_[stable_name_table] + index*SIZEOF_snEntry) == NULL ) { - ALLOC_PRIM (SIZEOF_StgStableName); - sn_obj = Hp - SIZEOF_StgStableName + WDS(1); + // At this point we have a snEntry, but it doesn't look as used to the + // GC yet because we don't have a StableName object for the sn_obj field + // (remember that sn_obj == NULL means the entry is free). So if we call + // GC here we end up skipping the snEntry in gcStableNameTable(). This + // caused #15906. Solution: use allocate(), which does not call GC. + // + // (Alternatively we could use a special value for the sn_obj field to + // indicate that the entry is being allocated and not free, but that's + // too complicated and doesn't buy us much. See D5342?id=18700.) + ("ptr" sn_obj) = ccall allocate(MyCapability() "ptr", + BYTES_TO_WDS(SIZEOF_StgStableName)); SET_HDR(sn_obj, stg_STABLE_NAME_info, CCCS); StgStableName_sn(sn_obj) = index; snEntry_sn_obj(W_[stable_name_table] + index*SIZEOF_snEntry) = sn_obj; From git at git.haskell.org Thu Nov 22 09:57:21 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Nov 2018 09:57:21 +0000 (UTC) Subject: [commit: ghc] master: another minor refactoring (4343d5a) Message-ID: <20181122095721.8EDCD3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4343d5af30d4b4fffb8be05616736e5920b6999a/ghc >--------------------------------------------------------------- commit 4343d5af30d4b4fffb8be05616736e5920b6999a Author: Gabor Greif Date: Tue Nov 20 16:35:08 2018 +0100 another minor refactoring >--------------------------------------------------------------- 4343d5af30d4b4fffb8be05616736e5920b6999a compiler/llvmGen/Llvm/PpLlvm.hs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/compiler/llvmGen/Llvm/PpLlvm.hs b/compiler/llvmGen/Llvm/PpLlvm.hs index b350ab4..b534276 100644 --- a/compiler/llvmGen/Llvm/PpLlvm.hs +++ b/compiler/llvmGen/Llvm/PpLlvm.hs @@ -80,11 +80,11 @@ ppLlvmGlobal (LMGlobal var@(LMGlobalVar _ _ link x a c) dat) = -- Position of linkage is different for aliases. const = case c of - Global -> text "global" - Constant -> text "constant" - Alias -> text "alias" + Global -> "global" + Constant -> "constant" + Alias -> "alias" - in ppAssignment var $ ppr link <+> const <+> rhs <> sect <> align + in ppAssignment var $ ppr link <+> text const <+> rhs <> sect <> align $+$ newLine ppLlvmGlobal (LMGlobal var val) = sdocWithDynFlags $ \dflags -> From git at git.haskell.org Thu Nov 22 09:57:24 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Nov 2018 09:57:24 +0000 (UTC) Subject: [commit: ghc] master: Minor performance optimisation (8707911) Message-ID: <20181122095724.933B53A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8707911a8ba42619e77315f7c0443546991a6668/ghc >--------------------------------------------------------------- commit 8707911a8ba42619e77315f7c0443546991a6668 Author: Gabor Greif Date: Wed Nov 21 18:30:49 2018 +0100 Minor performance optimisation only concat once >--------------------------------------------------------------- 8707911a8ba42619e77315f7c0443546991a6668 compiler/llvmGen/LlvmCodeGen.hs | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/compiler/llvmGen/LlvmCodeGen.hs b/compiler/llvmGen/LlvmCodeGen.hs index 3fcf83a..b003cbc 100644 --- a/compiler/llvmGen/LlvmCodeGen.hs +++ b/compiler/llvmGen/LlvmCodeGen.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE CPP, TypeFamilies #-} +{-# LANGUAGE CPP, TypeFamilies, ViewPatterns #-} -- ----------------------------------------------------------------------------- -- | This is the top-level module in the LLVM code generator. @@ -125,13 +125,13 @@ cmmDataLlvmGens :: [(Section,CmmStatics)] -> LlvmM () cmmDataLlvmGens statics = do lmdatas <- mapM genLlvmData statics - let (gss, tss) = unzip lmdatas + let (concat -> gs, tss) = unzip lmdatas let regGlobal (LMGlobal (LMGlobalVar l ty _ _ _ _) _) = funInsert l ty - regGlobal _ = return () - mapM_ regGlobal (concat gss) - gss' <- mapM aliasify $ concat gss + regGlobal _ = pure () + mapM_ regGlobal gs + gss' <- mapM aliasify $ gs renderLlvm $ pprLlvmData (concat gss', concat tss) From git at git.haskell.org Thu Nov 22 10:16:12 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Nov 2018 10:16:12 +0000 (UTC) Subject: [commit: ghc] branch 'wip/safer-haskell' created Message-ID: <20181122101612.6AE693A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/safer-haskell Referencing: a8adb5519bd3807a05d813eccb48eb5a1910e165 From git at git.haskell.org Thu Nov 22 10:16:15 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Nov 2018 10:16:15 +0000 (UTC) Subject: [commit: ghc] wip/safer-haskell: Add -fno-safe-haskell flag (371696d) Message-ID: <20181122101616.004D13A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/safer-haskell Link : http://ghc.haskell.org/trac/ghc/changeset/371696dee9e180ab0794021bd57659503430bcbd/ghc >--------------------------------------------------------------- commit 371696dee9e180ab0794021bd57659503430bcbd Author: Matthew Pickering Date: Tue Nov 20 11:58:55 2018 +0000 Add -fno-safe-haskell flag Summary: This flag can be set to turn off the Safe Haskell checks. Whether a module is marked Safe/Unsafe/Trustworthy is ignored when this flag to set. Reviewers: bgamari Subscribers: rwbarton, carter GHC Trac Issues: #15920 Differential Revision: https://phabricator.haskell.org/D5360 >--------------------------------------------------------------- 371696dee9e180ab0794021bd57659503430bcbd compiler/main/DynFlags.hs | 16 +++++++++++++--- compiler/main/HscMain.hs | 5 +++-- compiler/main/HscTypes.hs | 2 ++ docs/users_guide/safe_haskell.rst | 17 +++++++++++++++++ testsuite/tests/safeHaskell/flags/SafeIgnore.hs | 6 ++++++ testsuite/tests/safeHaskell/flags/SafeIgnoreA.hs | 4 ++++ testsuite/tests/safeHaskell/flags/all.T | 2 ++ 7 files changed, 47 insertions(+), 5 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 371696dee9e180ab0794021bd57659503430bcbd From git at git.haskell.org Thu Nov 22 10:16:18 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Nov 2018 10:16:18 +0000 (UTC) Subject: [commit: ghc] wip/safer-haskell: fix test (a8adb55) Message-ID: <20181122101618.E81723A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/safer-haskell Link : http://ghc.haskell.org/trac/ghc/changeset/a8adb5519bd3807a05d813eccb48eb5a1910e165/ghc >--------------------------------------------------------------- commit a8adb5519bd3807a05d813eccb48eb5a1910e165 Author: Matthew Pickering Date: Tue Nov 20 16:24:38 2018 +0000 fix test >--------------------------------------------------------------- a8adb5519bd3807a05d813eccb48eb5a1910e165 testsuite/tests/safeHaskell/flags/all.T | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/testsuite/tests/safeHaskell/flags/all.T b/testsuite/tests/safeHaskell/flags/all.T index 3a22a21..8b1ea97 100644 --- a/testsuite/tests/safeHaskell/flags/all.T +++ b/testsuite/tests/safeHaskell/flags/all.T @@ -64,4 +64,4 @@ test('Flags02', normal, compile, ['-XSafe']) test('SafeFlags30', normal, compile_fail, ['']) -test('SafeIgnore', normal, multimod_compile, ['SafeIgnore', '-v0', '-fno-safe-haskell']) +test('SafeIgnore', [], multimod_compile, ['SafeIgnore', '-v0 -fno-safe-haskell']) From git at git.haskell.org Thu Nov 22 11:40:49 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Nov 2018 11:40:49 +0000 (UTC) Subject: [commit: nofib] master: Add binary artifacts to .gitignore (605bbb7) Message-ID: <20181122114049.365D53A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/nofib On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/605bbb7adee3643d84fd58dc81fedb5da5ccac3a/nofib >--------------------------------------------------------------- commit 605bbb7adee3643d84fd58dc81fedb5da5ccac3a Author: Sebastian Graf Date: Thu Nov 22 12:40:36 2018 +0100 Add binary artifacts to .gitignore Summary: I'm not sure why, but after D4989 (maybe also before) some binary artifacts crept into the working tree. Reviewers: AndreasK, mpickering, osa1, alpmestan, O26 nofib Reviewed By: alpmestan Differential Revision: https://phabricator.haskell.org/D5366 >--------------------------------------------------------------- 605bbb7adee3643d84fd58dc81fedb5da5ccac3a .gitignore | 14 ++++++++++++++ 1 file changed, 14 insertions(+) diff --git a/.gitignore b/.gitignore index 21a7ce7..c69af58 100644 --- a/.gitignore +++ b/.gitignore @@ -14,6 +14,8 @@ nofib-analyse/nofib-analyse runstdtest/runstdtest imaginary/bernouilli/bernouilli +imaginary/digits-of-e1/digits-of-e1 +imaginary/digits-of-e2/digits-of-e2 imaginary/exp3_8/exp3_8 imaginary/gen_regexps/gen_regexps imaginary/integrate/integrate @@ -36,6 +38,13 @@ real/compress/compress.stdout real/compress2/compress2 real/compress2/compress2.stdin real/compress2/compress2.stdout +real/eff/CS/CS +real/eff/CSD/CSD +real/eff/FS/FS +real/eff/S/S +real/eff/VS/VS +real/eff/VSD/VSD +real/eff/VSM/VSM real/fem/fem real/fluid/fluid real/fulsom/fulsom @@ -46,6 +55,7 @@ real/hidden/hidden real/hpg/hpg real/infer/infer real/lift/lift +real/linear/linear real/maillist/runtime_files/addresses.tex real/maillist/maillist real/mkhprog/mkhprog @@ -98,6 +108,7 @@ spectral/cryptarithm1/cryptarithm1 spectral/cryptarithm2/cryptarithm2 spectral/cse/cse spectral/eliza/eliza +spectral/exact-reals/exact-reals spectral/expert/expert spectral/fft2/fft2 spectral/fibheaps/fibheaps @@ -120,10 +131,13 @@ spectral/hartel/wang/wang spectral/hartel/wave4main/wave4main spectral/integer/integer spectral/knights/knights +spectral/lambda/lambda +spectral/last-piece/last-piece spectral/lcss/lcss spectral/life/life spectral/mandel/mandel spectral/mandel2/mandel2 +spectral/mate/mate spectral/minimax/minimax spectral/multiplier/multiplier spectral/para/para From git at git.haskell.org Thu Nov 22 11:41:14 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Nov 2018 11:41:14 +0000 (UTC) Subject: [commit: nofib] master: Clean more generated files (f87d446) Message-ID: <20181122114114.218B13A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/nofib On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f87d446b4e361cc82f219cf78917db9681af69b3/nofib >--------------------------------------------------------------- commit f87d446b4e361cc82f219cf78917db9681af69b3 Author: Sebastian Graf Date: Thu Nov 22 12:41:01 2018 +0100 Clean more generated files Summary: When we don't remove the generated files, `make boot` won't regenerate them. That in turn leads to expected output failures after bumping `{FAST,NORM,SLOW}_OPTS`. Test Plan: make clean && make boot && make Reviewers: AndreasK, mpickering, osa1, alpmestan, O26 nofib Reviewed By: alpmestan Differential Revision: https://phabricator.haskell.org/D5365 >--------------------------------------------------------------- f87d446b4e361cc82f219cf78917db9681af69b3 real/compress/Makefile | 6 ++---- shootout/k-nucleotide/Makefile | 2 ++ 2 files changed, 4 insertions(+), 4 deletions(-) diff --git a/real/compress/Makefile b/real/compress/Makefile index 2f87ccb..f366d2c 100644 --- a/real/compress/Makefile +++ b/real/compress/Makefile @@ -5,6 +5,8 @@ SRC_RUNTEST_OPTS += -stdout-binary SRCS = BinConv.hs BinTest.hs Decode.hs Defaults.hs Encode.hs Main.hs PTTrees.hs Uncompress.hs +CLEAN_FILES += compress.stdin compress.stdout + Lzw_HC_OPTS = -cpp include $(TOP)/mk/target.mk @@ -16,7 +18,3 @@ compress.stdin : compress.faststdin compress.stdout : compress.stdin compress ./compress < compress.stdin > compress.stdout - - -clean :: - rm -f compress.stdin compress.stdout diff --git a/shootout/k-nucleotide/Makefile b/shootout/k-nucleotide/Makefile index dad274a..56870ff 100644 --- a/shootout/k-nucleotide/Makefile +++ b/shootout/k-nucleotide/Makefile @@ -7,6 +7,8 @@ FAST_OPTS = 250000 NORM_OPTS = 500000 SLOW_OPTS = 25000000 # official shootout setting +CLEAN_FILES += fasta-c k-nucleotide.*stdin + # The benchmark game also uses -fllvm, which we can't since it might # not be available on the developer's machine. HC_OPTS += -XBangPatterns -package bytestring From git at git.haskell.org Thu Nov 22 14:29:32 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Nov 2018 14:29:32 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Yet more on family-instance checking (c003b03) Message-ID: <20181122142932.CF99D3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/c003b03fcdd0a0beb61f127ac080260d05266379/ghc >--------------------------------------------------------------- commit c003b03fcdd0a0beb61f127ac080260d05266379 Author: Simon Peyton Jones Date: Thu Nov 22 14:24:28 2018 +0000 Yet more on family-instance checking Following conversation with Richard yesterday. Very close now. Comments to be written. >--------------------------------------------------------------- c003b03fcdd0a0beb61f127ac080260d05266379 compiler/hsSyn/HsDecls.hs | 57 +++---- compiler/hsSyn/HsTypes.hs | 68 ++++---- compiler/nativeGen/CFG.hs | 6 +- compiler/parser/RdrHsSyn.hs | 8 +- compiler/typecheck/Inst.hs | 2 +- compiler/typecheck/TcHsType.hs | 5 +- compiler/typecheck/TcInstDcls.hs | 125 ++++++++------- compiler/typecheck/TcMType.hs | 155 +++++++++--------- compiler/typecheck/TcSigs.hs | 21 +-- compiler/typecheck/TcTyClsDecls.hs | 173 +++++++++++++-------- compiler/types/Unify.hs | 43 +++-- .../should_fail/ExplicitForAllFams4b.hs | 1 + .../should_fail/ExplicitForAllFams4b.stderr | 54 +++++-- .../indexed-types/should_fail/SimpleFail9.stderr | 2 +- .../tests/indexed-types/should_fail/T12041.stderr | 11 +- .../tests/indexed-types/should_fail/T13972.hs | 6 + .../tests/indexed-types/should_fail/T13972.stderr | 7 - .../tests/indexed-types/should_fail/T14045a.hs | 5 + .../tests/indexed-types/should_fail/T14045a.stderr | 7 - testsuite/tests/indexed-types/should_fail/T9160.hs | 1 + .../tests/indexed-types/should_fail/T9160.stderr | 13 +- testsuite/tests/indexed-types/should_fail/all.T | 4 +- .../tests/partial-sigs/should_fail/T14040a.stderr | 8 +- testsuite/tests/polykinds/T14450.stderr | 12 +- testsuite/tests/polykinds/T14846.stderr | 36 +++-- 25 files changed, 450 insertions(+), 380 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 c003b03fcdd0a0beb61f127ac080260d05266379 From git at git.haskell.org Thu Nov 22 18:42:16 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Nov 2018 18:42:16 +0000 (UTC) Subject: [commit: ghc] master: users guide: We no longer build libraries with -split-objs (f5fbecc) Message-ID: <20181122184216.52C6B3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f5fbecc85967218fd8ba6512f10eea2daf2812ac/ghc >--------------------------------------------------------------- commit f5fbecc85967218fd8ba6512f10eea2daf2812ac Author: Ben Gamari Date: Wed Nov 21 19:17:41 2018 -0500 users guide: We no longer build libraries with -split-objs We now generally use split-sections instead. >--------------------------------------------------------------- f5fbecc85967218fd8ba6512f10eea2daf2812ac docs/users_guide/phases.rst | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/docs/users_guide/phases.rst b/docs/users_guide/phases.rst index 788b9be..f5f735b 100644 --- a/docs/users_guide/phases.rst +++ b/docs/users_guide/phases.rst @@ -745,7 +745,7 @@ for example). However, assembling all the sections separately is expensive, so this is slower than compiling normally. Additionally, the size of the library itself (the ``.a`` file) can be a factor of 2 to 2.5 - larger. We use this feature for building GHC's libraries. + larger. .. ghc-flag:: -split-sections :shortdesc: Split sections for link-time dead-code stripping From git at git.haskell.org Thu Nov 22 18:42:32 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Nov 2018 18:42:32 +0000 (UTC) Subject: [commit: ghc] master: Rename literal constructors (13bb4bf) Message-ID: <20181122184232.5E0603A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/13bb4bf44e6e690133be334bbf0c63fcae5db34a/ghc >--------------------------------------------------------------- commit 13bb4bf44e6e690133be334bbf0c63fcae5db34a Author: Sylvain Henry Date: Thu Nov 22 11:31:16 2018 -0500 Rename literal constructors In a previous patch we replaced some built-in literal constructors (MachInt, MachWord, etc.) with a single LitNumber constructor. In this patch we replace the `Mach` prefix of the remaining constructors with `Lit` for consistency (e.g., LitChar, LitLabel, etc.). Sadly the name `LitString` was already taken for a kind of FastString and it would become misleading to have both `LitStr` (literal constructor renamed after `MachStr`) and `LitString` (FastString variant). Hence this patch renames the FastString variant `PtrString` (which is more accurate) and the literal string constructor now uses the least surprising `LitString` name. Both `Literal` and `LitString/PtrString` have recently seen breaking changes so doing this kind of renaming now shouldn't harm much. Reviewers: hvr, goldfire, bgamari, simonmar, jrtc27, tdammers Subscribers: tdammers, rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4881 >--------------------------------------------------------------- 13bb4bf44e6e690133be334bbf0c63fcae5db34a compiler/basicTypes/Literal.hs | 380 +++++++++++---------- compiler/cmm/CLabel.hs | 4 +- compiler/cmm/CmmType.hs | 2 +- compiler/codeGen/StgCmmCon.hs | 2 +- compiler/codeGen/StgCmmUtils.hs | 28 +- compiler/coreSyn/CoreOpt.hs | 8 +- compiler/coreSyn/CorePrep.hs | 8 +- compiler/coreSyn/CoreSyn.hs | 24 +- compiler/coreSyn/CoreUnfold.hs | 2 +- compiler/coreSyn/CoreUtils.hs | 8 +- compiler/coreSyn/MkCore.hs | 6 +- compiler/deSugar/DsCCall.hs | 4 +- compiler/deSugar/DsForeign.hs | 6 +- compiler/deSugar/DsMonad.hs | 4 +- compiler/deSugar/DsUtils.hs | 4 +- compiler/deSugar/Match.hs | 4 +- compiler/deSugar/MatchLit.hs | 38 +-- compiler/ghci/ByteCodeAsm.hs | 20 +- compiler/ghci/ByteCodeGen.hs | 42 +-- compiler/llvmGen/Llvm/Types.hs | 3 +- compiler/main/Finder.hs | 6 +- compiler/nativeGen/Dwarf/Constants.hs | 2 +- compiler/nativeGen/Dwarf/Types.hs | 2 +- compiler/nativeGen/PPC/Ppr.hs | 6 +- compiler/nativeGen/SPARC/Ppr.hs | 8 +- compiler/nativeGen/X86/Ppr.hs | 46 +-- compiler/prelude/PrelRules.hs | 86 ++--- compiler/simplCore/SetLevels.hs | 2 +- compiler/simplCore/Simplify.hs | 4 +- compiler/simplStg/UnariseStg.hs | 4 +- compiler/stgSyn/CoreToStg.hs | 4 +- compiler/stranal/WwLib.hs | 2 +- compiler/typecheck/TcEvTerm.hs | 2 +- compiler/typecheck/TcSplice.hs | 2 +- compiler/utils/BufWrite.hs | 8 +- compiler/utils/FastString.hs | 58 ++-- compiler/utils/Outputable.hs | 2 +- compiler/utils/Pretty.hs | 22 +- testsuite/tests/plugins/HomePackagePlugin.hs | 2 +- .../tests/plugins/simple-plugin/Simple/Plugin.hs | 4 +- 40 files changed, 442 insertions(+), 427 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 13bb4bf44e6e690133be334bbf0c63fcae5db34a From git at git.haskell.org Thu Nov 22 18:42:47 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Nov 2018 18:42:47 +0000 (UTC) Subject: [commit: ghc] master: Fix GhostScript detection (Trac #15856) (011e39d) Message-ID: <20181122184247.C0DFA3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/011e39d7fe533ca772beeed8529749c4750d4817/ghc >--------------------------------------------------------------- commit 011e39d7fe533ca772beeed8529749c4750d4817 Author: Krzysztof Gogolewski Date: Thu Nov 22 11:32:55 2018 -0500 Fix GhostScript detection (Trac #15856) The option `confdir` (used in GhostScript test) was set correctly via `--config` in `test.mk` and incorrectly via `config/ghc`. AFAICT, some time ago this was working because the incorrect assignment was done first, and later it broke. Hardian doesn't pass `confdir`. I removed `confdir` and use `config.top` to determine the directory of the `good.ps` and `bad.ps` files. This is simpler. I also removed some redundant assignments in `config/ghc`. Test Plan: manually set config.have_profiling and make test Reviewers: bgamari Subscribers: rwbarton, carter GHC Trac Issues: #15856 Differential Revision: https://phabricator.haskell.org/D5298 >--------------------------------------------------------------- 011e39d7fe533ca772beeed8529749c4750d4817 testsuite/config/ghc | 7 ------- testsuite/driver/testlib.py | 4 ++-- testsuite/mk/test.mk | 4 +--- 3 files changed, 3 insertions(+), 12 deletions(-) diff --git a/testsuite/config/ghc b/testsuite/config/ghc index eae88ed..247ddb8 100644 --- a/testsuite/config/ghc +++ b/testsuite/config/ghc @@ -4,15 +4,8 @@ import re # # This file is Python source # -config.compiler = 'ghc' config.compiler_always_flags = ghc_compiler_always_flags.split() -config.haddock = 'haddock' -config.hp2ps = 'hp2ps' -config.hpc = 'hpc' -config.gs = 'gs' -config.confdir = '.' - # By default, the 'normal' and 'hpc' ways are enabled. In addition, certain # ways are enabled automatically if this GHC supports them. Ways that fall in # this group are 'optasm', 'optllvm', 'profasm', 'threaded1', 'threaded2', diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index 761ba67..b2f14d1 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -1921,9 +1921,9 @@ global gs_working gs_working = False if config.have_profiling: if config.gs != '': - resultGood = runCmd(genGSCmd(config.confdir + '/good.ps')); + resultGood = runCmd(genGSCmd(config.top + '/config/good.ps')); if resultGood == 0: - resultBad = runCmd(genGSCmd(config.confdir + '/bad.ps') + + resultBad = runCmd(genGSCmd(config.top + '/config/bad.ps') + ' >/dev/null 2>&1') if resultBad != 0: print("GhostScript available for hp2ps tests") diff --git a/testsuite/mk/test.mk b/testsuite/mk/test.mk index 65e897d..6c995a4 100644 --- a/testsuite/mk/test.mk +++ b/testsuite/mk/test.mk @@ -25,8 +25,7 @@ export MAKE RUNTESTS = $(TOP)/driver/runtests.py COMPILER = ghc -CONFIGDIR = $(TOP)/config -CONFIG = $(CONFIGDIR)/$(COMPILER) +CONFIG = $(TOP)/config/$(COMPILER) ifeq "$(GhcUnregisterised)" "YES" # Otherwise C backend generates many warnings about @@ -243,7 +242,6 @@ endif RUNTEST_OPTS += \ --rootdir=. \ --config-file=$(CONFIG) \ - -e 'config.confdir="$(CONFIGDIR)"' \ -e 'config.platform="$(TARGETPLATFORM)"' \ -e 'config.os="$(TargetOS_CPP)"' \ -e 'config.arch="$(TargetARCH_CPP)"' \ From git at git.haskell.org Thu Nov 22 18:43:03 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Nov 2018 18:43:03 +0000 (UTC) Subject: [commit: ghc] master: base: Mention openFile throwing does-not-exist-errors on FIFOs (4ba3fa3) Message-ID: <20181122184303.35AA13A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4ba3fa31ddfa12b428bd67216a2d4118dc9e8311/ghc >--------------------------------------------------------------- commit 4ba3fa31ddfa12b428bd67216a2d4118dc9e8311 Author: Ben Gamari Date: Thu Nov 22 11:33:39 2018 -0500 base: Mention openFile throwing does-not-exist-errors on FIFOs As discussed in #15715, the POSIX specification specifies that attempting to open a FIFO in write-only mode when the FIFO has no readers will fail with -ENOENT. [skip ci] Test Plan: Read it Reviewers: hvr Subscribers: rwbarton, carter GHC Trac Issues: #15715 Differential Revision: https://phabricator.haskell.org/D5295 >--------------------------------------------------------------- 4ba3fa31ddfa12b428bd67216a2d4118dc9e8311 libraries/base/GHC/IO/Handle/FD.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/libraries/base/GHC/IO/Handle/FD.hs b/libraries/base/GHC/IO/Handle/FD.hs index 883bc5f..6417976 100644 --- a/libraries/base/GHC/IO/Handle/FD.hs +++ b/libraries/base/GHC/IO/Handle/FD.hs @@ -131,7 +131,9 @@ addFilePathToIOError fun fp ioe -- * 'System.IO.Error.isAlreadyInUseError' if the file is already open and -- cannot be reopened; -- --- * 'System.IO.Error.isDoesNotExistError' if the file does not exist; or +-- * 'System.IO.Error.isDoesNotExistError' if the file does not exist or +-- (on POSIX systems) is a FIFO without a reader and 'WriteMode' was +-- requested; or -- -- * 'System.IO.Error.isPermissionError' if the user does not have permission -- to open the file. From git at git.haskell.org Thu Nov 22 18:43:18 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Nov 2018 18:43:18 +0000 (UTC) Subject: [commit: ghc] master: Add test for #15437 (ea01517) Message-ID: <20181122184318.EFD983A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ea01517247c9667b0728daadc5f687ef8fcf945e/ghc >--------------------------------------------------------------- commit ea01517247c9667b0728daadc5f687ef8fcf945e Author: Matthew Pickering Date: Thu Nov 22 11:38:10 2018 -0500 Add test for #15437 Reviewers: bgamari Subscribers: rwbarton, carter GHC Trac Issues: #15437 Differential Revision: https://phabricator.haskell.org/D5291 >--------------------------------------------------------------- ea01517247c9667b0728daadc5f687ef8fcf945e testsuite/tests/th/T15437.hs | 7 +++++++ testsuite/tests/th/T15437A.hs | 12 ++++++++++++ testsuite/tests/th/all.T | 2 ++ 3 files changed, 21 insertions(+) diff --git a/testsuite/tests/th/T15437.hs b/testsuite/tests/th/T15437.hs new file mode 100644 index 0000000..2251927 --- /dev/null +++ b/testsuite/tests/th/T15437.hs @@ -0,0 +1,7 @@ +{-# LANGUAGE TemplateHaskell #-} +module T15437 where + +import T15437A + +f :: Int +f = $$(foo) diff --git a/testsuite/tests/th/T15437A.hs b/testsuite/tests/th/T15437A.hs new file mode 100644 index 0000000..c46581a --- /dev/null +++ b/testsuite/tests/th/T15437A.hs @@ -0,0 +1,12 @@ +{-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE TemplateHaskell #-} +{-# LANGUAGE TypeApplications #-} +module T15437A where + +import Language.Haskell.TH.Syntax (Q, TExp) + +get :: forall a. Int +get = 1 + +foo :: forall a. Q (TExp Int) +foo = [|| get @a ||] diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index adf8970..b158313 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -449,3 +449,5 @@ test('T15792', normal, compile, ['-v0 -dsuppress-uniques']) test('T15815', normal, multimod_compile, ['T15815B', '-v0 ' + config.ghc_th_way_flags]) test('T15845', normal, compile, ['-v0 -dsuppress-uniques']) +test('T15437', expect_broken(15437), multimod_compile, + ['T15437', '-v0 ' + config.ghc_th_way_flags]) From git at git.haskell.org Thu Nov 22 18:43:34 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Nov 2018 18:43:34 +0000 (UTC) Subject: [commit: ghc] master: rts/M32Alloc: Abort if m32 linker mmap fails (86f6890) Message-ID: <20181122184334.29D883A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/86f6890e3689f2f75ecca8172eda0338fe3e9769/ghc >--------------------------------------------------------------- commit 86f6890e3689f2f75ecca8172eda0338fe3e9769 Author: Ben Gamari Date: Sat Nov 10 15:35:37 2018 -0500 rts/M32Alloc: Abort if m32 linker mmap fails Previously we should just blinding dereference a NULL pointer. >--------------------------------------------------------------- 86f6890e3689f2f75ecca8172eda0338fe3e9769 rts/linker/M32Alloc.c | 3 +++ 1 file changed, 3 insertions(+) diff --git a/rts/linker/M32Alloc.c b/rts/linker/M32Alloc.c index 6a2996d..52b182e 100644 --- a/rts/linker/M32Alloc.c +++ b/rts/linker/M32Alloc.c @@ -158,6 +158,9 @@ m32_allocator_init(void) // fragment the memory. size_t pgsz = getPageSize(); char* bigchunk = mmapForLinker(pgsz * M32_MAX_PAGES,MAP_ANONYMOUS,-1,0); + if (bigchunk == NULL) + barf("m32_allocator_init: Failed to map"); + int i; for (i=0; i Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/06a09a5b5764717121be41d32f7b30f58ae33e08/ghc >--------------------------------------------------------------- commit 06a09a5b5764717121be41d32f7b30f58ae33e08 Author: Tamar Christina Date: Thu Nov 22 11:43:15 2018 -0500 rts: Fix bss initialization on Windows This patch fixes BSS initialization such that it is initialized to 0 as you'd expect. Test Plan: ./validate, test T7040_ghci Reviewers: bgamari, erikd, simonmar Reviewed By: bgamari Subscribers: rwbarton, carter GHC Trac Issues: #15669 Differential Revision: https://phabricator.haskell.org/D5364 >--------------------------------------------------------------- 06a09a5b5764717121be41d32f7b30f58ae33e08 rts/linker/PEi386.c | 13 ++++++------- 1 file changed, 6 insertions(+), 7 deletions(-) diff --git a/rts/linker/PEi386.c b/rts/linker/PEi386.c index ab4583d..fbd1264 100644 --- a/rts/linker/PEi386.c +++ b/rts/linker/PEi386.c @@ -1437,8 +1437,8 @@ ocGetNames_PEi386 ( ObjectCode* oc ) { bool has_code_section = false; - SymbolName* sname; - SymbolAddr* addr; + SymbolName* sname = NULL; + SymbolAddr* addr = NULL; unsigned int i; COFF_HEADER_INFO *info = oc->info->ch_info; @@ -1567,11 +1567,10 @@ ocGetNames_PEi386 ( ObjectCode* oc ) Allocate zeroed space for it */ bss_sz = section.info->virtualSize; if (bss_sz < section.size) { bss_sz = section.size; } - bss_sz = section.info->alignment; zspace = stgCallocBytes(1, bss_sz, "ocGetNames_PEi386(anonymous bss)"); - oc->sections[i].start = getAlignedMemory(zspace, section); + oc->sections[i].start = zspace; oc->sections[i].size = bss_sz; - addProddableBlock(oc, zspace, bss_sz); + section = oc->sections[i]; /* debugBelch("BSS anon section at 0x%x\n", zspace); */ } @@ -1592,9 +1591,9 @@ ocGetNames_PEi386 ( ObjectCode* oc ) if (sz < section.info->virtualSize) sz = section.info->virtualSize; start = section.start; - end = start + sz - 1; + end = start + sz; - if (kind != SECTIONKIND_OTHER && end >= start) { + if (kind != SECTIONKIND_OTHER && end > start) { /* See Note [Section alignment]. */ addCopySection(oc, &oc->sections[i], kind, SECTION_NOMEM, start, sz); addProddableBlock(oc, oc->sections[i].start, sz); From git at git.haskell.org Thu Nov 22 18:44:04 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Nov 2018 18:44:04 +0000 (UTC) Subject: [commit: ghc] master: testuite: update more windows tests outputs (67277e7) Message-ID: <20181122184404.1D6113A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/67277e7c783dac1fb66d1b113a8b1f2be784b24b/ghc >--------------------------------------------------------------- commit 67277e7c783dac1fb66d1b113a8b1f2be784b24b Author: Tamar Christina Date: Thu Nov 22 11:43:37 2018 -0500 testuite: update more windows tests outputs Test Plan: ./validate Reviewers: bgamari, simonmar Subscribers: rwbarton, carter Differential Revision: https://phabricator.haskell.org/D5362 >--------------------------------------------------------------- 67277e7c783dac1fb66d1b113a8b1f2be784b24b testsuite/driver/testlib.py | 5 +++-- testsuite/tests/ghci/scripts/T9293.stdout-mingw32 | 20 ++++++++++++++++++++ testsuite/tests/ghci/scripts/ghci024.stdout-mingw32 | 5 +++++ testsuite/tests/ghci/scripts/ghci057.stdout-mingw32 | 20 ++++++++++++++++++++ testsuite/tests/numeric/should_run/all.T | 3 ++- testsuite/tests/rts/all.T | 4 +++- 6 files changed, 53 insertions(+), 4 deletions(-) diff --git a/testsuite/driver/testlib.py b/testsuite/driver/testlib.py index b2f14d1..94211df 100644 --- a/testsuite/driver/testlib.py +++ b/testsuite/driver/testlib.py @@ -902,9 +902,10 @@ def do_test(name, way, func, args, files): stderr = subprocess.STDOUT, print_output = config.verbose >= 3) - if exit_code != 0: + # If user used expect_broken then don't record failures of pre_cmd + if exit_code != 0 and opts.expect not in ['fail']: framework_fail(name, way, 'pre_cmd failed: {0}'.format(exit_code)) - if_verbose(1, '** pre_cmd was "{0}". Running trace'.format(override_options(opts.pre_cmd))) + if_verbose(1, '** pre_cmd was "{0}".'.format(override_options(opts.pre_cmd))) result = func(*[name,way] + args) diff --git a/testsuite/tests/ghci/scripts/T9293.stdout-mingw32 b/testsuite/tests/ghci/scripts/T9293.stdout-mingw32 index c5be11a..be028c5 100644 --- a/testsuite/tests/ghci/scripts/T9293.stdout-mingw32 +++ b/testsuite/tests/ghci/scripts/T9293.stdout-mingw32 @@ -12,6 +12,11 @@ other dynamic, non-language, flag settings: -fimplicit-import-qualified -fshow-warning-groups warning settings: + -Wimplicit-kind-vars + -Wmissing-monadfail-instances + -Wsemigroup + -Wnoncanonical-monoid-instances + -Wstar-is-type Should fail, GADTs is not enabled options currently set: none. base language is: Haskell2010 @@ -30,6 +35,11 @@ other dynamic, non-language, flag settings: -fimplicit-import-qualified -fshow-warning-groups warning settings: + -Wimplicit-kind-vars + -Wmissing-monadfail-instances + -Wsemigroup + -Wnoncanonical-monoid-instances + -Wstar-is-type Should work, GADTs is in force from :set options currently set: none. base language is: Haskell2010 @@ -47,6 +57,11 @@ other dynamic, non-language, flag settings: -fimplicit-import-qualified -fshow-warning-groups warning settings: + -Wimplicit-kind-vars + -Wmissing-monadfail-instances + -Wsemigroup + -Wnoncanonical-monoid-instances + -Wstar-is-type Should fail, GADTs is now disabled base language is: Haskell2010 with the following modifiers: @@ -66,5 +81,10 @@ other dynamic, non-language, flag settings: -fimplicit-import-qualified -fshow-warning-groups warning settings: + -Wimplicit-kind-vars + -Wmissing-monadfail-instances + -Wsemigroup + -Wnoncanonical-monoid-instances + -Wstar-is-type Should fail, GADTs is only enabled at the prompt C :: T Int diff --git a/testsuite/tests/ghci/scripts/ghci024.stdout-mingw32 b/testsuite/tests/ghci/scripts/ghci024.stdout-mingw32 index 1247616..b0f4c73 100644 --- a/testsuite/tests/ghci/scripts/ghci024.stdout-mingw32 +++ b/testsuite/tests/ghci/scripts/ghci024.stdout-mingw32 @@ -13,6 +13,11 @@ other dynamic, non-language, flag settings: -fimplicit-import-qualified -fshow-warning-groups warning settings: + -Wimplicit-kind-vars + -Wmissing-monadfail-instances + -Wsemigroup + -Wnoncanonical-monoid-instances + -Wstar-is-type ~~~~~~~~~~ Testing :set -a options currently set: none. base language is: Haskell2010 diff --git a/testsuite/tests/ghci/scripts/ghci057.stdout-mingw32 b/testsuite/tests/ghci/scripts/ghci057.stdout-mingw32 index c5be11a..be028c5 100644 --- a/testsuite/tests/ghci/scripts/ghci057.stdout-mingw32 +++ b/testsuite/tests/ghci/scripts/ghci057.stdout-mingw32 @@ -12,6 +12,11 @@ other dynamic, non-language, flag settings: -fimplicit-import-qualified -fshow-warning-groups warning settings: + -Wimplicit-kind-vars + -Wmissing-monadfail-instances + -Wsemigroup + -Wnoncanonical-monoid-instances + -Wstar-is-type Should fail, GADTs is not enabled options currently set: none. base language is: Haskell2010 @@ -30,6 +35,11 @@ other dynamic, non-language, flag settings: -fimplicit-import-qualified -fshow-warning-groups warning settings: + -Wimplicit-kind-vars + -Wmissing-monadfail-instances + -Wsemigroup + -Wnoncanonical-monoid-instances + -Wstar-is-type Should work, GADTs is in force from :set options currently set: none. base language is: Haskell2010 @@ -47,6 +57,11 @@ other dynamic, non-language, flag settings: -fimplicit-import-qualified -fshow-warning-groups warning settings: + -Wimplicit-kind-vars + -Wmissing-monadfail-instances + -Wsemigroup + -Wnoncanonical-monoid-instances + -Wstar-is-type Should fail, GADTs is now disabled base language is: Haskell2010 with the following modifiers: @@ -66,5 +81,10 @@ other dynamic, non-language, flag settings: -fimplicit-import-qualified -fshow-warning-groups warning settings: + -Wimplicit-kind-vars + -Wmissing-monadfail-instances + -Wsemigroup + -Wnoncanonical-monoid-instances + -Wstar-is-type Should fail, GADTs is only enabled at the prompt C :: T Int diff --git a/testsuite/tests/numeric/should_run/all.T b/testsuite/tests/numeric/should_run/all.T index 140fa6c..295e818 100644 --- a/testsuite/tests/numeric/should_run/all.T +++ b/testsuite/tests/numeric/should_run/all.T @@ -41,7 +41,8 @@ test('arith018', normal, compile_and_run, ['']) test('arith019', normal, compile_and_run, ['']) test('expfloat', normal, compile_and_run, ['']) -test('FloatFnInverses', normal, compile_and_run, ['']) +test('FloatFnInverses', [when(opsys('mingw32'), expect_broken(15670))], + compile_and_run, ['']) test('T1603', skip, compile_and_run, ['']) test('T3676', expect_broken(3676), compile_and_run, ['']) diff --git a/testsuite/tests/rts/all.T b/testsuite/tests/rts/all.T index 8d2f37b..e42d970 100644 --- a/testsuite/tests/rts/all.T +++ b/testsuite/tests/rts/all.T @@ -453,6 +453,7 @@ test('nursery-chunks1', test('keep-cafs-fail', [ extra_files(['KeepCafsBase.hs', 'KeepCafs1.hs', 'KeepCafs2.hs', 'KeepCafsMain.hs']), + when(opsys('mingw32'), expect_broken (5987)), filter_stdout_lines('Evaluated a CAF|exit.*'), ignore_stderr, # on OS X the shell emits an "Abort trap" message to stderr ], @@ -462,7 +463,8 @@ test('keep-cafs-fail', # Test the -fkeep-cafs flag test('keep-cafs', [ extra_files(['KeepCafsBase.hs', 'KeepCafs1.hs', - 'KeepCafs2.hs', 'KeepCafsMain.hs']) + 'KeepCafs2.hs', 'KeepCafsMain.hs']), + when(opsys('mingw32'), expect_broken (5987)), ], run_command, ['$MAKE -s --no-print-directory KeepCafs']) From git at git.haskell.org Thu Nov 22 18:44:19 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Nov 2018 18:44:19 +0000 (UTC) Subject: [commit: ghc] master: Fixup the new code layout patch for SplitObjs. (6c26b3f) Message-ID: <20181122184419.242933A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6c26b3f85dfdc87f1caa7f4dd7ab4fd7bbb9e922/ghc >--------------------------------------------------------------- commit 6c26b3f85dfdc87f1caa7f4dd7ab4fd7bbb9e922 Author: klebinger.andreas at gmx.at Date: Thu Nov 22 11:43:53 2018 -0500 Fixup the new code layout patch for SplitObjs. When splitting objects we sometimes generate dummy CmmProcs containing bottom in some fields. Code introduced in the new code layout patch looked at these which blew up the compiler. Now we instead check first if the function actually contains code. Reviewers: bgamari Subscribers: simonpj, rwbarton, carter Differential Revision: https://phabricator.haskell.org/D5357 >--------------------------------------------------------------- 6c26b3f85dfdc87f1caa7f4dd7ab4fd7bbb9e922 compiler/nativeGen/CFG.hs | 10 +++++++--- 1 file changed, 7 insertions(+), 3 deletions(-) diff --git a/compiler/nativeGen/CFG.hs b/compiler/nativeGen/CFG.hs index a52c92f..8207859 100644 --- a/compiler/nativeGen/CFG.hs +++ b/compiler/nativeGen/CFG.hs @@ -481,9 +481,13 @@ addNodesBetween m updates = -} -- | Generate weights for a Cmm proc based on some simple heuristics. getCfgProc :: D.CfgWeights -> RawCmmDecl -> CFG -getCfgProc _ (CmmData {}) = mapEmpty -getCfgProc weights (CmmProc _info _lab _live graph) = - getCfg weights graph +getCfgProc _ (CmmData {}) = mapEmpty +-- Sometimes GHC generates dummy procs which don't actually contain code. +-- But they might contain bottoms in some fields so we check for an empty +-- body first. In particular this happens with SplitObjs enabled. +getCfgProc weights (CmmProc _info _lab _live graph) + | null (toBlockList graph) = mapEmpty + | otherwise = getCfg weights graph getCfg :: D.CfgWeights -> CmmGraph -> CFG From git at git.haskell.org Thu Nov 22 18:44:33 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Nov 2018 18:44:33 +0000 (UTC) Subject: [commit: ghc] master: Don't reverse explicit export lists during renaming (7cba71f) Message-ID: <20181122184433.F35293A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7cba71fc25af8287db61f6f6aa80d45ce96404a7/ghc >--------------------------------------------------------------- commit 7cba71fc25af8287db61f6f6aa80d45ce96404a7 Author: Simon Jakobi Date: Thu Nov 22 11:45:35 2018 -0500 Don't reverse explicit export lists during renaming This will be useful for Hi Haddock / D5067. Previously any export list in 'tcg_rn_exports' would be in reverse order. Also remove a redundant setSrcSpan. Test Plan: ./validate Reviewers: bgamari Subscribers: rwbarton, carter Differential Revision: https://phabricator.haskell.org/D5347 >--------------------------------------------------------------- 7cba71fc25af8287db61f6f6aa80d45ce96404a7 compiler/typecheck/TcRnExports.hs | 55 +++++++++++++++++++++++---------------- compiler/typecheck/TcRnMonad.hs | 2 +- 2 files changed, 33 insertions(+), 24 deletions(-) diff --git a/compiler/typecheck/TcRnExports.hs b/compiler/typecheck/TcRnExports.hs index a2f892b..4d05037 100644 --- a/compiler/typecheck/TcRnExports.hs +++ b/compiler/typecheck/TcRnExports.hs @@ -32,6 +32,7 @@ import ConLike import DataCon import PatSyn import Maybes +import UniqSet import Util (capitalise) import FastString (fsLit) @@ -91,13 +92,21 @@ You just have to use an explicit export list: data ExportAccum -- The type of the accumulating parameter of -- the main worker function in rnExports = ExportAccum - [(LIE GhcRn, Avails)] -- Export items with names and - -- their exported stuff - -- Not nub'd! ExportOccMap -- Tracks exported occurrence names + (UniqSet ModuleName) -- Tracks (re-)exported module names emptyExportAccum :: ExportAccum -emptyExportAccum = ExportAccum [] emptyOccEnv +emptyExportAccum = ExportAccum emptyOccEnv emptyUniqSet + +accumExports :: (ExportAccum -> x -> TcRn (Maybe (ExportAccum, y))) + -> [x] + -> TcRn [y] +accumExports f = fmap (catMaybes . snd) . mapAccumLM f' emptyExportAccum + where f' acc x = do + m <- try_m (f acc x) + pure $ case m of + Right (Just (acc', y)) -> (acc', Just y) + _ -> (acc, Nothing) type ExportOccMap = OccEnv (Name, IE GhcPs) -- Tracks what a particular exported OccName @@ -207,12 +216,12 @@ exports_from_avail Nothing rdr_env _imports _this_mod exports_from_avail (Just (L _ rdr_items)) rdr_env imports this_mod - = do ExportAccum ie_avails _ - <- foldAndRecoverM do_litem emptyExportAccum rdr_items + = do ie_avails <- accumExports do_litem rdr_items let final_exports = nubAvails (concat (map snd ie_avails)) -- Combine families return (Just ie_avails, final_exports) where - do_litem :: ExportAccum -> LIE GhcPs -> RnM ExportAccum + do_litem :: ExportAccum -> LIE GhcPs + -> RnM (Maybe (ExportAccum, (LIE GhcRn, Avails))) do_litem acc lie = setSrcSpan (getLoc lie) (exports_from_item acc lie) -- Maps a parent to its in-scope children @@ -224,16 +233,14 @@ exports_from_avail (Just (L _ rdr_items)) rdr_env imports this_mod | xs <- moduleEnvElts $ imp_mods imports , imv <- importedByUser xs ] - exports_from_item :: ExportAccum -> LIE GhcPs -> RnM ExportAccum - exports_from_item acc@(ExportAccum ie_avails occs) - (L loc ie@(IEModuleContents _ (L lm mod))) - | let earlier_mods - = [ mod - | ((L _ (IEModuleContents _ (L _ mod))), _) <- ie_avails ] - , mod `elem` earlier_mods -- Duplicate export of M + exports_from_item :: ExportAccum -> LIE GhcPs + -> RnM (Maybe (ExportAccum, (LIE GhcRn, Avails))) + exports_from_item (ExportAccum occs earlier_mods) + (L loc ie@(IEModuleContents _ lmod@(L _ mod))) + | mod `elementOfUniqSet` earlier_mods -- Duplicate export of M = do { warnIfFlag Opt_WarnDuplicateExports True (dupModuleExport mod) ; - return acc } + return Nothing } | otherwise = do { let { exportValid = (mod `elem` imported_modules) @@ -241,6 +248,7 @@ exports_from_avail (Just (L _ rdr_items)) rdr_env imports this_mod ; gre_prs = pickGREsModExp mod (globalRdrEnvElts rdr_env) ; new_exports = map (availFromGRE . fst) gre_prs ; all_gres = foldr (\(gre1,gre2) gres -> gre1 : gre2 : gres) [] gre_prs + ; mods = addOneToUniqSet earlier_mods mod } ; checkErr exportValid (moduleNotImported mod) @@ -262,24 +270,25 @@ exports_from_avail (Just (L _ rdr_items)) rdr_env imports this_mod (vcat [ ppr mod , ppr new_exports ]) - ; return (ExportAccum (((L loc (IEModuleContents noExt (L lm mod))) - , new_exports) : ie_avails) occs') } + ; return (Just ( ExportAccum occs' mods + , ( L loc (IEModuleContents noExt lmod) + , new_exports))) } - exports_from_item acc@(ExportAccum lie_avails occs) (L loc ie) + exports_from_item acc@(ExportAccum occs mods) (L loc ie) | isDoc ie = do new_ie <- lookup_doc_ie ie - return (ExportAccum ((L loc new_ie, []) : lie_avails) occs) + return (Just (acc, (L loc new_ie, []))) | otherwise - = do (new_ie, avail) <- - setSrcSpan loc $ lookup_ie ie + = do (new_ie, avail) <- lookup_ie ie if isUnboundName (ieName new_ie) - then return acc -- Avoid error cascade + then return Nothing -- Avoid error cascade else do occs' <- check_occs ie occs [avail] - return (ExportAccum ((L loc new_ie, [avail]) : lie_avails) occs') + return (Just ( ExportAccum occs' mods + , (L loc new_ie, [avail]))) ------------- lookup_ie :: IE GhcPs -> RnM (IE GhcRn, AvailInfo) diff --git a/compiler/typecheck/TcRnMonad.hs b/compiler/typecheck/TcRnMonad.hs index bef1044..eb5a63a 100644 --- a/compiler/typecheck/TcRnMonad.hs +++ b/compiler/typecheck/TcRnMonad.hs @@ -68,7 +68,7 @@ module TcRnMonad( -- * Shared error message stuff: renamer and typechecker mkLongErrAt, mkErrDocAt, addLongErrAt, reportErrors, reportError, reportWarning, recoverM, mapAndRecoverM, mapAndReportM, foldAndRecoverM, - tryTc, + try_m, tryTc, askNoErrs, discardErrs, tryTcDiscardingErrs, checkNoErrs, whenNoErrs, ifErrsM, failIfErrsM, From git at git.haskell.org Thu Nov 22 18:44:48 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Nov 2018 18:44:48 +0000 (UTC) Subject: [commit: ghc] master: rts: fix Windows megablock allocator (676f1f2) Message-ID: <20181122184448.E61D23A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/676f1f2d2eb39740fe5d88e72f6aa8e89cb0ebc0/ghc >--------------------------------------------------------------- commit 676f1f2d2eb39740fe5d88e72f6aa8e89cb0ebc0 Author: Tamar Christina Date: Thu Nov 22 11:47:10 2018 -0500 rts: fix Windows megablock allocator The megablock allocator does not currently check that after aligning the free region if it still has enough space to actually do the allocation. This causes it to return a memory region which it didn't fully allocate itself. Even worse, it can cause it to return a block with a region that will be present in two allocation pools. This causes if you're lucky an error from the OS that you're committing memory that has never been reserved, or causes random heap corruption. This change makes it consider the alignment as well. Test Plan: ./validate , testcase testmblockalloc Reviewers: bgamari, erikd, simonmar Reviewed By: simonmar Subscribers: rwbarton, carter Differential Revision: https://phabricator.haskell.org/D5363 >--------------------------------------------------------------- 676f1f2d2eb39740fe5d88e72f6aa8e89cb0ebc0 rts/win32/OSMem.c | 19 ++++++++++++++----- 1 file changed, 14 insertions(+), 5 deletions(-) diff --git a/rts/win32/OSMem.c b/rts/win32/OSMem.c index c62ee3b..57997b1 100644 --- a/rts/win32/OSMem.c +++ b/rts/win32/OSMem.c @@ -144,8 +144,11 @@ findFreeBlocks(uint32_t n) { temp.next=free_blocks; temp.base=0; temp.size=0; prev=&temp; /* TODO: Don't just take first block, find smallest sufficient block */ - for( ; it!=0 && it->sizenext ) {} - if(it!=0) { + for ( ; it; prev=it, it=it->next ) + { + if (!it || it->size < required_size) + continue; + if( (((W_)it->base) & MBLOCK_MASK) == 0) { /* MBlock aligned */ ret = (void*)it->base; if(it->size==required_size) { @@ -155,24 +158,30 @@ findFreeBlocks(uint32_t n) { it->base += required_size; it->size -=required_size; } + break; } else { char* need_base; block_rec* next; int new_size; need_base = (char*)(((W_)it->base) & ((W_)~MBLOCK_MASK)) + MBLOCK_SIZE; + new_size = need_base - it->base; + /* Make sure that after alignment we have enough space. */ + W_ total_size = new_size + required_size; + if (total_size > it->size) + continue; next = (block_rec*)stgMallocBytes( sizeof(block_rec) , "getMBlocks: findFreeBlocks: splitting"); - new_size = need_base - it->base; next->base = need_base +required_size; - next->size = it->size - (new_size+required_size); + next->size = it->size - total_size; it->size = new_size; next->next = it->next; it->next = next; ret=(void*)need_base; + break; } - } + } free_blocks=temp.next; return ret; } From git at git.haskell.org Thu Nov 22 18:45:04 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Nov 2018 18:45:04 +0000 (UTC) Subject: [commit: ghc] master: Hadrian: work around Cabal's/GHC's different Arch/OS strings (19ffddc) Message-ID: <20181122184504.3029F3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/19ffddc1f479fcd5a0f265330cc1041366e8c43d/ghc >--------------------------------------------------------------- commit 19ffddc1f479fcd5a0f265330cc1041366e8c43d Author: Alec Theriault Date: Thu Nov 22 11:47:27 2018 -0500 Hadrian: work around Cabal's/GHC's different Arch/OS strings The path to the 'include' subdirectory of 'rts' includes a folder that whose name is generated by Cabal and mentiones the architecture and OS. For example: _build/stage1/lib/x86_64-osx-ghc-8.7.20181120/rts-1.0/include Hadrian needs to be aware that Cabal renders architectures and OSes in a slightly different way than GHC. There is already symmetric logic in Cabal (for working with GHC environment files, which follow GHC's naming conventions). Test Plan: ./hadrian/build.sh -c "binary-dist" # on mac Reviewers: snowleopard, alpmestan, bgamari Reviewed By: snowleopard Subscribers: rwbarton, carter GHC Trac Issues: #15922 Differential Revision: https://phabricator.haskell.org/D5361 >--------------------------------------------------------------- 19ffddc1f479fcd5a0f265330cc1041366e8c43d hadrian/src/Hadrian/Haskell/Cabal.hs | 20 +++++++++++++++++++- hadrian/src/Rules/BinaryDist.hs | 6 +++--- 2 files changed, 22 insertions(+), 4 deletions(-) diff --git a/hadrian/src/Hadrian/Haskell/Cabal.hs b/hadrian/src/Hadrian/Haskell/Cabal.hs index 327e6a0..91de7b2 100644 --- a/hadrian/src/Hadrian/Haskell/Cabal.hs +++ b/hadrian/src/Hadrian/Haskell/Cabal.hs @@ -11,7 +11,8 @@ ----------------------------------------------------------------------------- module Hadrian.Haskell.Cabal ( pkgVersion, pkgIdentifier, pkgSynopsis, pkgDescription, pkgDependencies, - pkgGenericDescription + pkgGenericDescription, + cabalArchString, cabalOsString, ) where import Development.Shake @@ -54,3 +55,20 @@ pkgDependencies = fmap (map pkgName . packageDependencies) . readPackageData -- file is tracked. pkgGenericDescription :: Package -> Action GenericPackageDescription pkgGenericDescription = fmap genericPackageDescription . readPackageData + +-- | Cabal's rendering of an architecture as used in its directory structure. +-- +-- Inverse of 'Cabal.Distribution.Simple.GHC.ghcArchString'. +cabalArchString :: String -> String +cabalArchString "powerpc" = "ppc" +cabalArchString "powerpc64" = "ppc64" +cabalArchString other = other + +-- | Cabal's rendering of an OS as used in its directory structure. +-- +-- Inverse of 'Cabal.Distribution.Simple.GHC.ghcOsString'. +cabalOsString :: String -> String +cabalOsString "mingw32" = "windows" +cabalOsString "darwin" = "osx" +cabalOsString "solaris2" = "solaris" +cabalOsString other = other diff --git a/hadrian/src/Rules/BinaryDist.hs b/hadrian/src/Rules/BinaryDist.hs index f0aeb4b..667fbf1 100644 --- a/hadrian/src/Rules/BinaryDist.hs +++ b/hadrian/src/Rules/BinaryDist.hs @@ -19,14 +19,14 @@ bindistRules = do need targets version <- setting ProjectVersion targetPlatform <- setting TargetPlatformFull - hostOs <- setting BuildOs - hostArch <- setting BuildArch + cabalHostOs <- cabalOsString <$> setting BuildOs + cabalHostArch <- cabalArchString <$> setting BuildArch rtsDir <- pkgIdentifier rts let ghcBuildDir = root -/- stageString Stage1 bindistFilesDir = root -/- "bindist" -/- ghcVersionPretty ghcVersionPretty = "ghc-" ++ version ++ "-" ++ targetPlatform - distDir = hostArch ++ "-" ++ hostOs ++ "-ghc-" ++ version + distDir = cabalHostArch ++ "-" ++ cabalHostOs ++ "-ghc-" ++ version rtsIncludeDir = ghcBuildDir -/- "lib" -/- distDir -/- rtsDir -/- "include" From git at git.haskell.org Thu Nov 22 18:45:20 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Nov 2018 18:45:20 +0000 (UTC) Subject: [commit: ghc] master: rts.cabal.in: force inclusion of findPtr/_findPtr symbol only with debug flag (561748c) Message-ID: <20181122184520.798393A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/561748cb507505bd5b7bd76bdc57796d896b62a2/ghc >--------------------------------------------------------------- commit 561748cb507505bd5b7bd76bdc57796d896b62a2 Author: Alp Mestanogullari Date: Thu Nov 22 11:47:48 2018 -0500 rts.cabal.in: force inclusion of findPtr/_findPtr symbol only with debug flag The previous strategy caused problems on Windows, as pointed out at [1] [1]: https://phabricator.haskell.org/rGHC900c47f88784#133905 Reviewers: Phyx, bgamari, erikd, simonmar Reviewed By: Phyx Subscribers: rwbarton, carter GHC Trac Issues: #15671 Differential Revision: https://phabricator.haskell.org/D5356 >--------------------------------------------------------------- 561748cb507505bd5b7bd76bdc57796d896b62a2 rts/Printer.c | 11 +++-------- rts/package.conf.in | 4 ++++ rts/rts.cabal.in | 16 +++++++++++----- 3 files changed, 18 insertions(+), 13 deletions(-) diff --git a/rts/Printer.c b/rts/Printer.c index 7f7e83c..291f529 100644 --- a/rts/Printer.c +++ b/rts/Printer.c @@ -24,8 +24,6 @@ #include -void findPtr(P_ p, int follow); - #if defined(DEBUG) #include "Disassembler.h" @@ -777,6 +775,8 @@ extern void DEBUG_LoadSymbols( const char *name STG_UNUSED ) #endif /* USING_LIBBFD */ +void findPtr(P_ p, int); /* keep gcc -Wall happy */ + int searched = 0; static int @@ -876,12 +876,7 @@ void printObj( StgClosure *obj ) debugBelch("obj 0x%p (enable -DDEBUG for more info) " , obj ); } -void findPtr(P_ p, int follow) -{ - // we're printing the arguments just to silence the unused parameter warning - debugBelch("recompile your program with -debug in order to run "); - debugBelch("findPtr(0x%p, %d)\n", p, follow); -} + #endif /* DEBUG */ /* ----------------------------------------------------------------------------- diff --git a/rts/package.conf.in b/rts/package.conf.in index b6dac76..b5ed26d 100644 --- a/rts/package.conf.in +++ b/rts/package.conf.in @@ -174,9 +174,11 @@ ld-options: #if WORD_SIZE_IN_BITS == 64 , "-Wl,-u,_hs_atomicwrite64" #endif +#if defined(DEBUG) /* This symbol is useful in gdb, but not referred to anywhere, * so we need to force it to be included in the binary. */ , "-Wl,-u,_findPtr" +#endif #else "-Wl,-u,base_GHCziTopHandler_runIO_closure" , "-Wl,-u,base_GHCziTopHandler_runNonIO_closure" @@ -275,10 +277,12 @@ ld-options: #if WORD_SIZE_IN_BITS == 64 , "-Wl,-u,hs_atomicwrite64" #endif +#if defined(DEBUG) /* This symbol is useful in gdb, but not referred to anywhere, * so we need to force it to be included in the binary. */ , "-Wl,-u,findPtr" #endif +#endif /* Pick up static libraries in preference over dynamic if in earlier search * path. This is important to use the static gmp in preference on Mac OS. diff --git a/rts/rts.cabal.in b/rts/rts.cabal.in index 76fd353..a20aa57 100644 --- a/rts/rts.cabal.in +++ b/rts/rts.cabal.in @@ -260,9 +260,13 @@ library "-Wl,-u,_hs_atomicwrite8" "-Wl,-u,_hs_atomicwrite16" "-Wl,-u,_hs_atomicwrite32" - -- This symbol is useful in gdb, but not referred to anywhere, - -- so we need to force it to be included in the binary. "-Wl,-u,_findPtr" + + if flag(debug) + -- This symbol is useful in gdb, but not referred to anywhere, + -- so we need to force it to be included in the binary. + ld-options: "-Wl,-u,_findPtr" + else ld-options: "-Wl,-u,base_GHCziTopHandler_runIO_closure" @@ -333,9 +337,11 @@ library "-Wl,-u,hs_atomicwrite8" "-Wl,-u,hs_atomicwrite16" "-Wl,-u,hs_atomicwrite32" - -- This symbol is useful in gdb, but not referred to anywhere, - -- so we need to force it to be included in the binary. - "-Wl,-u,findPtr" + + if flag(debug) + -- This symbol is useful in gdb, but not referred to anywhere, + -- so we need to force it to be included in the binary. + ld-options: "-Wl,-u,_findPtr" if os(osx) ld-options: "-Wl,-search_paths_first" From git at git.haskell.org Thu Nov 22 18:45:35 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Nov 2018 18:45:35 +0000 (UTC) Subject: [commit: ghc] master: plugins10 no longer broken (1f74f7d) Message-ID: <20181122184535.9D2D43A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1f74f7dd9ffec3540b9bd74225665dfa1519c46e/ghc >--------------------------------------------------------------- commit 1f74f7dd9ffec3540b9bd74225665dfa1519c46e Author: Christiaan Baaij Date: Thu Nov 22 11:49:37 2018 -0500 plugins10 no longer broken Reviewers: bgamari, tdammers Reviewed By: tdammers Subscribers: rwbarton, carter GHC Trac Issues: #15216 Differential Revision: https://phabricator.haskell.org/D5350 >--------------------------------------------------------------- 1f74f7dd9ffec3540b9bd74225665dfa1519c46e testsuite/tests/plugins/all.T | 3 +-- testsuite/tests/plugins/plugins10.stdout | 5 ++++- 2 files changed, 5 insertions(+), 3 deletions(-) diff --git a/testsuite/tests/plugins/all.T b/testsuite/tests/plugins/all.T index cc412fa..9a1a7ea 100644 --- a/testsuite/tests/plugins/all.T +++ b/testsuite/tests/plugins/all.T @@ -65,8 +65,7 @@ test('plugins09', run_command, ['$MAKE -s --no-print-directory plugins09']) test('plugins10', - [expect_broken(15216), - extra_files(['simple-plugin/', 'QuasiQuotation.hs']), + [extra_files(['simple-plugin/', 'QuasiQuotation.hs']), when(opsys('mingw32'), multi_cpu_race), only_ways([config.ghc_plugin_way]), pre_cmd('$MAKE -s --no-print-directory -C simple-plugin package.plugins10 TOP={top}')], diff --git a/testsuite/tests/plugins/plugins10.stdout b/testsuite/tests/plugins/plugins10.stdout index 737789c..f010ce9 100644 --- a/testsuite/tests/plugins/plugins10.stdout +++ b/testsuite/tests/plugins/plugins10.stdout @@ -5,14 +5,17 @@ interfacePlugin: Language.Haskell.TH.Quote interfacePlugin: GHC.Float interfacePlugin: GHC.Base interfacePlugin: Language.Haskell.TH.Syntax -interfacePlugin: GHC.Types typeCheckPlugin (rn) +interfacePlugin: GHC.Types typeCheckPlugin (tc) interfacePlugin: GHC.Integer.Type +interfacePlugin: GHC.Natural parsePlugin(a) +typeCheckPlugin (rn) interfacePlugin: Language.Haskell.TH.Lib.Internal metaPlugin: return [] metaPlugin: quoteExp stringify "x" interfacePlugin: GHC.CString typeCheckPlugin (rn) +typeCheckPlugin (rn) typeCheckPlugin (tc) From git at git.haskell.org Thu Nov 22 18:45:50 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Nov 2018 18:45:50 +0000 (UTC) Subject: [commit: ghc] master: Fix deadlock bug when mkFastStringWith is duplicated (f088c2d) Message-ID: <20181122184550.B7AD73A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f088c2d42aaa38b32482ea8c4324786123835e62/ghc >--------------------------------------------------------------- commit f088c2d42aaa38b32482ea8c4324786123835e62 Author: Zejun Wu Date: Thu Nov 22 11:49:51 2018 -0500 Fix deadlock bug when mkFastStringWith is duplicated In D5211, we use `withMVar` to guard writes to the same segment, this is unsafe to be duplicated. It can lead to deadlock if it is only run partially and `putMVar` is not called after `takeMVar`. Test Plan: ./validate We used to see deadlock when building stackage without this fix, and it no longer happens. Reviewers: simonmar, bgamari Reviewed By: simonmar Subscribers: rwbarton, carter Differential Revision: https://phabricator.haskell.org/D5349 >--------------------------------------------------------------- f088c2d42aaa38b32482ea8c4324786123835e62 compiler/utils/FastFunctions.hs | 2 +- compiler/utils/FastString.hs | 6 ++++-- 2 files changed, 5 insertions(+), 3 deletions(-) diff --git a/compiler/utils/FastFunctions.hs b/compiler/utils/FastFunctions.hs index be3f3cb..9a09bb7 100644 --- a/compiler/utils/FastFunctions.hs +++ b/compiler/utils/FastFunctions.hs @@ -15,7 +15,7 @@ import GhcPrelude () import GHC.Exts import GHC.IO (IO(..)) --- Just like unsafePerformIO, but we inline it. +-- Just like unsafeDupablePerformIO, but we inline it. {-# INLINE inlinePerformIO #-} inlinePerformIO :: IO a -> a inlinePerformIO (IO m) = case m realWorld# of (# _, r #) -> r diff --git a/compiler/utils/FastString.hs b/compiler/utils/FastString.hs index c53eff1..f9fbeb0 100644 --- a/compiler/utils/FastString.hs +++ b/compiler/utils/FastString.hs @@ -114,14 +114,13 @@ import qualified Data.ByteString.Unsafe as BS import Foreign.C import GHC.Exts import System.IO -import System.IO.Unsafe ( unsafePerformIO ) import Data.Data import Data.IORef import Data.Maybe ( isJust ) import Data.Char import Data.Semigroup as Semi -import GHC.IO ( IO(..), unIO, unsafeDupablePerformIO ) +import GHC.IO import Foreign @@ -400,6 +399,9 @@ mkFastStringWith mk_fs !ptr !len = do case res of Just found -> return found Nothing -> do + -- The withMVar below is not dupable. It can lead to deadlock if it is + -- only run partially and putMVar is not called after takeMVar. + noDuplicate n <- get_uid new_fs <- mk_fs n withMVar lock $ \_ -> insert new_fs From git at git.haskell.org Thu Nov 22 18:46:07 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Nov 2018 18:46:07 +0000 (UTC) Subject: [commit: ghc] master: Load plugins in interactive session (599eaad) Message-ID: <20181122184607.A91393A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/599eaada382d04722219bfc319bde94591be3fb1/ghc >--------------------------------------------------------------- commit 599eaada382d04722219bfc319bde94591be3fb1 Author: Christiaan Baaij Date: Thu Nov 22 11:50:51 2018 -0500 Load plugins in interactive session Reviewers: bgamari, tdammers Reviewed By: tdammers Subscribers: monoidal, rwbarton, carter GHC Trac Issues: #15633 Differential Revision: https://phabricator.haskell.org/D5348 >--------------------------------------------------------------- 599eaada382d04722219bfc319bde94591be3fb1 ghc/GHCi/UI.hs | 8 +++++++- ghc/Main.hs | 17 ++++++++++++----- testsuite/tests/ghci/should_run/T15633a.script | 1 + testsuite/tests/ghci/should_run/T15633a.stderr | 1 + testsuite/tests/ghci/should_run/T15633a.stdout | 1 + testsuite/tests/ghci/should_run/T15633b.script | 2 ++ testsuite/tests/ghci/should_run/T15633b.stderr | 1 + testsuite/tests/ghci/should_run/T15633b.stdout | 1 + testsuite/tests/ghci/should_run/all.T | 18 ++++++++++++++++++ .../should_run/tc-plugin-ghci}/LICENSE | 0 .../should_run/tc-plugin-ghci}/Makefile | 0 .../should_run/tc-plugin-ghci}/Setup.hs | 0 .../should_run/tc-plugin-ghci/TcPluginGHCi.hs} | 5 +++-- .../should_run/tc-plugin-ghci/tc-plugin-ghci.cabal} | 9 +++------ 14 files changed, 50 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 599eaada382d04722219bfc319bde94591be3fb1 From git at git.haskell.org Thu Nov 22 18:46:24 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Nov 2018 18:46:24 +0000 (UTC) Subject: [commit: ghc] master: Fix uninformative hp2ps error when the cmdline contains double quotes (390df8b) Message-ID: <20181122184624.182C03A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/390df8b51b917fb6409cbde8e73fe838d61d8832/ghc >--------------------------------------------------------------- commit 390df8b51b917fb6409cbde8e73fe838d61d8832 Author: Zejun Wu Date: Thu Nov 22 11:51:15 2018 -0500 Fix uninformative hp2ps error when the cmdline contains double quotes The format of hp file didn't allow double quotes inside strings, and under prof build, we include args in JOB, which may have double quotes. When this happens, the error message is confusing to the user. This can also happen under normal build if the executable name contains double quite, which is unlikely though. We fix this issue by introducing escaping for double quotes inside a string by repeating it twice. We also fix a buffer overflow bug when the length of the string happen to be multiple of 5000. Test Plan: new tests, which used to fail with error message: ``` hp2ps: "T15904".hp, line 2: integer must follow identifier ``` use new ghc and hp2ps to profile a simple program. Reviewers: simonmar, bgamari, erikd Reviewed By: simonmar Subscribers: rwbarton, carter GHC Trac Issues: #15904 Differential Revision: https://phabricator.haskell.org/D5346 >--------------------------------------------------------------- 390df8b51b917fb6409cbde8e73fe838d61d8832 rts/ProfHeap.c | 30 ++++++++++++++++++++-------- testsuite/tests/hp2ps/Makefile | 9 +++++++++ testsuite/tests/hp2ps/T15904.hs | 8 ++++++++ testsuite/tests/hp2ps/T15904.stdout | 7 +++++++ testsuite/tests/hp2ps/all.T | 1 + utils/hp2ps/HpFile.c | 39 +++++++++++++++++-------------------- 6 files changed, 65 insertions(+), 29 deletions(-) diff --git a/rts/ProfHeap.c b/rts/ProfHeap.c index de3d2b6..517702f 100644 --- a/rts/ProfHeap.c +++ b/rts/ProfHeap.c @@ -361,6 +361,18 @@ void endProfiling( void ) #endif /* !PROFILING */ static void +printEscapedString(const char* string) +{ + for (const char* p = string; *p != '\0'; ++p) { + if (*p == '\"') { + // Escape every " as "" + fputc('"', hp_file); + } + fputc(*p, hp_file); + } +} + +static void printSample(bool beginSample, StgDouble sampleValue) { fprintf(hp_file, "%s %f\n", @@ -428,16 +440,18 @@ initHeapProfiling(void) initEra( &censuses[era] ); /* initProfilingLogFile(); */ - fprintf(hp_file, "JOB \"%s", prog_name); + fprintf(hp_file, "JOB \""); + printEscapedString(prog_name); #if defined(PROFILING) - { - int count; - for(count = 1; count < prog_argc; count++) - fprintf(hp_file, " %s", prog_argv[count]); - fprintf(hp_file, " +RTS"); - for(count = 0; count < rts_argc; count++) - fprintf(hp_file, " %s", rts_argv[count]); + for (int i = 1; i < prog_argc; ++i) { + fputc(' ', hp_file); + printEscapedString(prog_argv[i]); + } + fprintf(hp_file, " +RTS"); + for (int i = 0; i < rts_argc; ++i) { + fputc(' ', hp_file); + printEscapedString(rts_argv[i]); } #endif /* PROFILING */ diff --git a/testsuite/tests/hp2ps/Makefile b/testsuite/tests/hp2ps/Makefile new file mode 100644 index 0000000..4618db7 --- /dev/null +++ b/testsuite/tests/hp2ps/Makefile @@ -0,0 +1,9 @@ +TOP=../.. +include $(TOP)/mk/boilerplate.mk +include $(TOP)/mk/test.mk + +.PHONY: T15904 +T15904: + "$(TEST_HC)" $(TEST_HC_OPTS) -rtsopts -main-is "$@" "$@.hs" -o "\"$@\"" + "./\"$@\"" '{"e": 2.72, "pi": 3.14}' $$'\n' "\\" "" +RTS -h + "$(HP2PS_ABS)" "\"$@\".hp" diff --git a/testsuite/tests/hp2ps/T15904.hs b/testsuite/tests/hp2ps/T15904.hs new file mode 100644 index 0000000..7c009ff --- /dev/null +++ b/testsuite/tests/hp2ps/T15904.hs @@ -0,0 +1,8 @@ +module T15904 (main) where + +import System.Environment + +main :: IO () +main = do + args <- getArgs + mapM_ putStrLn args diff --git a/testsuite/tests/hp2ps/T15904.stdout b/testsuite/tests/hp2ps/T15904.stdout new file mode 100644 index 0000000..6b08737 --- /dev/null +++ b/testsuite/tests/hp2ps/T15904.stdout @@ -0,0 +1,7 @@ +[1 of 1] Compiling T15904 ( T15904.hs, T15904.o ) +Linking "T15904" ... +{"e": 2.72, "pi": 3.14} + + +\ + diff --git a/testsuite/tests/hp2ps/all.T b/testsuite/tests/hp2ps/all.T new file mode 100644 index 0000000..bebeb56 --- /dev/null +++ b/testsuite/tests/hp2ps/all.T @@ -0,0 +1 @@ +test('T15904', [], run_command, ['$MAKE -s --no-print-directory T15904']) diff --git a/utils/hp2ps/HpFile.c b/utils/hp2ps/HpFile.c index e21acf3..bcdf7aa 100644 --- a/utils/hp2ps/HpFile.c +++ b/utils/hp2ps/HpFile.c @@ -398,45 +398,42 @@ GetIdent(FILE *infp) /* - * Read a sequence of characters that make up a string and - * assign the result to "thestring". + * Read a sequence of characters that make up a string and assign the result to + * "thestring". A string is surrounded by double quotes, with a double quote + * itself escaped as two contiguous double quotes. */ void GetString(FILE *infp) { - unsigned int i; - char *stringbuffer; - size_t stringbuffersize; + size_t stringbuffersize = 5000; + char *stringbuffer = xmalloc(stringbuffersize); ASSERT(ch == '\"'); - stringbuffersize = 5000; - stringbuffer = xmalloc(stringbuffersize); - - ch = getc(infp); /* skip the '\"' that begins the string */ + ch = getc(infp); /* skip the '\"' that begins the string */ - i = 0; - while (ch != '\"') { + for (size_t i = 0; ; ++i) { if (ch == EOF) { - Error("%s, line %d: EOF when expecting \"", hpfile, linenum, ch); + Error("%s, line %d: EOF when expecting \"", hpfile, linenum, ch); } - else if (i == stringbuffersize - 1) { - stringbuffersize = 2 * stringbuffersize; + if (i == stringbuffersize) { + stringbuffersize *= 2; stringbuffer = xrealloc(stringbuffer, stringbuffersize); } - stringbuffer[ i++ ] = ch; + if (ch == '\"') { + ch = getc(infp); + if (ch != '\"') { + stringbuffer[i] = '\0'; + break; + } + } + stringbuffer[i] = ch; ch = getc(infp); } - stringbuffer[i] = '\0'; thestring = copystring(stringbuffer); - free(stringbuffer); - - ASSERT(ch == '\"'); - - ch = getc(infp); /* skip the '\"' that terminates the string */ } boolish From git at git.haskell.org Thu Nov 22 18:46:39 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Nov 2018 18:46:39 +0000 (UTC) Subject: [commit: ghc] master: Refactor TcRnMonad.mapAndRecoverM (66f0056) Message-ID: <20181122184639.1DFDC3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/66f0056ae1279c3149053aa600c7fe09575212b1/ghc >--------------------------------------------------------------- commit 66f0056ae1279c3149053aa600c7fe09575212b1 Author: Simon Jakobi Date: Thu Nov 22 11:51:53 2018 -0500 Refactor TcRnMonad.mapAndRecoverM This version doesn't require the 'reverse' step after the monadic fold. Test Plan: ./validate Reviewers: bgamari, tdammers Reviewed By: tdammers Subscribers: monoidal, rwbarton, carter Differential Revision: https://phabricator.haskell.org/D5343 >--------------------------------------------------------------- 66f0056ae1279c3149053aa600c7fe09575212b1 compiler/typecheck/TcRnMonad.hs | 2 +- compiler/utils/Maybes.hs | 5 +++++ 2 files changed, 6 insertions(+), 1 deletion(-) diff --git a/compiler/typecheck/TcRnMonad.hs b/compiler/typecheck/TcRnMonad.hs index eb5a63a..a033bc4 100644 --- a/compiler/typecheck/TcRnMonad.hs +++ b/compiler/typecheck/TcRnMonad.hs @@ -990,7 +990,7 @@ recoverM recover thing -- | Drop elements of the input that fail, so the result -- list can be shorter than the argument list mapAndRecoverM :: (a -> TcRn b) -> [a] -> TcRn [b] -mapAndRecoverM f = fmap reverse . foldAndRecoverM (\xs x -> (:xs) <$> f x ) [] +mapAndRecoverM f = mapMaybeM (fmap rightToMaybe . try_m . f) -- | The accumulator is not updated if the action fails foldAndRecoverM :: (b -> a -> TcRn b) -> b -> [a] -> TcRn b diff --git a/compiler/utils/Maybes.hs b/compiler/utils/Maybes.hs index 3a139a5..14bc46b 100644 --- a/compiler/utils/Maybes.hs +++ b/compiler/utils/Maybes.hs @@ -18,6 +18,7 @@ module Maybes ( firstJust, firstJusts, whenIsJust, expectJust, + rightToMaybe, -- * MaybeT MaybeT(..), liftMaybeT, tryMaybeT @@ -62,6 +63,10 @@ whenIsJust Nothing _ = return () orElse :: Maybe a -> a -> a orElse = flip fromMaybe +rightToMaybe :: Either a b -> Maybe b +rightToMaybe (Left _) = Nothing +rightToMaybe (Right x) = Just x + {- ************************************************************************ * * From git at git.haskell.org Thu Nov 22 18:46:55 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Nov 2018 18:46:55 +0000 (UTC) Subject: [commit: ghc] master: Fix #15852 by eta expanding data family instance RHSes, too (014d6c1) Message-ID: <20181122184655.ADD6A3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/014d6c1f08808c4dab6cba80efdc634527d91086/ghc >--------------------------------------------------------------- commit 014d6c1f08808c4dab6cba80efdc634527d91086 Author: Ryan Scott Date: Thu Nov 22 11:52:12 2018 -0500 Fix #15852 by eta expanding data family instance RHSes, too When I defined `etaExpandFamInstLHS`, I blatantly forgot to eta expand the RHSes of data family instances. (Actually, I claimed that they didn't //need// to be eta expanded. I'm not sure what I was thinking.) This fixes the issue by changing `etaExpandFamInstLHS` to `etaExpandFamInst` and, well, making it actually eta expand the RHS. Test Plan: make test TEST=T15852 Reviewers: goldfire, bgamari Reviewed By: goldfire Subscribers: rwbarton, carter GHC Trac Issues: #15852 Differential Revision: https://phabricator.haskell.org/D5328 >--------------------------------------------------------------- 014d6c1f08808c4dab6cba80efdc634527d91086 compiler/basicTypes/OccName.hs | 30 ++++++++++++++++++++ compiler/iface/ToIface.hs-boot | 2 ++ compiler/typecheck/TcSplice.hs | 8 +++--- compiler/types/Coercion.hs | 25 +++++++++++------ compiler/types/FamInstEnv.hs | 2 +- compiler/types/TyCoRep.hs | 22 +++++++++------ compiler/types/Type.hs | 32 ++++++++++------------ testsuite/tests/deSugar/should_run/T5472.stdout | 1 - .../tests/indexed-types/should_compile/T15852.hs | 10 +++++++ .../indexed-types/should_compile/T15852.stderr | 13 +++++++++ testsuite/tests/indexed-types/should_compile/all.T | 1 + .../should_compile/DataFamilyInstanceLHS.stderr | 2 +- .../NamedWildcardInDataFamilyInstanceLHS.stderr | 2 +- .../should_compile/TypeFamilyInstanceLHS.stderr | 12 ++++---- 14 files changed, 115 insertions(+), 47 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 014d6c1f08808c4dab6cba80efdc634527d91086 From git at git.haskell.org Thu Nov 22 18:47:13 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Nov 2018 18:47:13 +0000 (UTC) Subject: [commit: ghc] master: Calling gcc: Pass optc flags as last options (#14452) (f2d9fb0) Message-ID: <20181122184713.45DF53A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f2d9fb0c288788abeb796a13d600295a526290cd/ghc >--------------------------------------------------------------- commit f2d9fb0c288788abeb796a13d600295a526290cd Author: Roland Senn Date: Thu Nov 22 11:52:33 2018 -0500 Calling gcc: Pass optc flags as last options (#14452) Test Plan: make test TEST=T14452 Reviewers: hvr, bgamari, monoidal, thomie, osa1 Reviewed By: osa1 Subscribers: rwbarton, carter GHC Trac Issues: #14452 Differential Revision: https://phabricator.haskell.org/D5318 >--------------------------------------------------------------- f2d9fb0c288788abeb796a13d600295a526290cd compiler/main/SysTools/Tasks.hs | 4 +++- testsuite/tests/driver/Makefile | 5 +++++ testsuite/tests/driver/T14452.hs | 5 +++++ testsuite/tests/driver/T14452.stdout | 1 + testsuite/tests/driver/all.T | 1 + 5 files changed, 15 insertions(+), 1 deletion(-) diff --git a/compiler/main/SysTools/Tasks.hs b/compiler/main/SysTools/Tasks.hs index 66cc1ec..a986db2 100644 --- a/compiler/main/SysTools/Tasks.hs +++ b/compiler/main/SysTools/Tasks.hs @@ -62,7 +62,9 @@ runCc :: DynFlags -> [Option] -> IO () runCc dflags args = do let (p,args0) = pgm_c dflags args1 = map Option (getOpts dflags opt_c) - args2 = args0 ++ args1 ++ args + args2 = args0 ++ args ++ args1 + -- We take care to pass -optc flags in args1 last to ensure that the + -- user can override flags passed by GHC. See #14452. mb_env <- getGccEnv args2 runSomethingResponseFile dflags cc_filter "C Compiler" p args2 mb_env where diff --git a/testsuite/tests/driver/Makefile b/testsuite/tests/driver/Makefile index 540f158..e60df7a 100644 --- a/testsuite/tests/driver/Makefile +++ b/testsuite/tests/driver/Makefile @@ -668,3 +668,8 @@ T12955: T12971: mkdir -p ä TMP=ä "$(TEST_HC)" $(TEST_HC_OPTS) --make T12971 + +.PHONY: T14452 +T14452: + "$(TEST_HC)" $(TEST_HC_OPTS) -v -c -O2 T14452.hs 2>&1 | grep 'O3' \ + | awk 'NF{print $$NF; exit}' # awk: extract last word of line diff --git a/testsuite/tests/driver/T14452.hs b/testsuite/tests/driver/T14452.hs new file mode 100644 index 0000000..2fb3cfc --- /dev/null +++ b/testsuite/tests/driver/T14452.hs @@ -0,0 +1,5 @@ +{-# LANGUAGE CApiFFI #-} +{-# OPTIONS_GHC -optc-O3 #-} + +module T14452 where +foreign import capi unsafe "stdlib.h exit" c_exit :: Int -> IO () diff --git a/testsuite/tests/driver/T14452.stdout b/testsuite/tests/driver/T14452.stdout new file mode 100644 index 0000000..d15a710 --- /dev/null +++ b/testsuite/tests/driver/T14452.stdout @@ -0,0 +1 @@ +-O3 diff --git a/testsuite/tests/driver/all.T b/testsuite/tests/driver/all.T index be91a26..a33dba1 100644 --- a/testsuite/tests/driver/all.T +++ b/testsuite/tests/driver/all.T @@ -283,4 +283,5 @@ test('inline-check', omit_ways(['hpc', 'profasm']) , compile , ['-dinline-check foo -O -ddebug-output']) +test('T14452', [], run_command, ['$MAKE -s --no-print-directory T14452']) test('T15396', normal, compile_and_run, ['-package ghc']) From git at git.haskell.org Thu Nov 22 18:47:28 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Nov 2018 18:47:28 +0000 (UTC) Subject: [commit: ghc] master: Remove warnings-silencing flags for code generated by Alex (699e507) Message-ID: <20181122184728.5D0E33A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/699e507237ccda65fe9f37651d2358129390e2de/ghc >--------------------------------------------------------------- commit 699e507237ccda65fe9f37651d2358129390e2de Author: Simon Jakobi Date: Thu Nov 22 11:52:53 2018 -0500 Remove warnings-silencing flags for code generated by Alex Current versions of Alex don't seem to produce as many warnings any more. In order to silence a warning and to avoid overlong lines, I've taken the liberty of refactoring 'tok_num'. Test Plan: ./validate Reviewers: bgamari, simonmar Reviewed By: simonmar Subscribers: erikd, rwbarton, carter Differential Revision: https://phabricator.haskell.org/D5319 >--------------------------------------------------------------- 699e507237ccda65fe9f37651d2358129390e2de aclocal.m4 | 10 ++------- compiler/cmm/CmmLex.x | 7 ------ compiler/parser/Lexer.x | 54 ++++++++------------------------------------- mk/config.mk.in | 3 --- utils/genprimopcode/Lexer.x | 8 ------- 5 files changed, 11 insertions(+), 71 deletions(-) diff --git a/aclocal.m4 b/aclocal.m4 index 18e0d7e..447fd61 100644 --- a/aclocal.m4 +++ b/aclocal.m4 @@ -958,16 +958,10 @@ else fi; changequote([, ])dnl ]) -FP_COMPARE_VERSIONS([$fptools_cv_alex_version],[-ge],[3.0], - [Alex3=YES],[Alex3=NO]) -if test ! -f compiler/cmm/CmmLex.hs || test ! -f compiler/parser/Lexer.hs -then - FP_COMPARE_VERSIONS([$fptools_cv_alex_version],[-lt],[3.1.0], - [AC_MSG_ERROR([Alex version 3.1.0 or later is required to compile GHC.])])[] -fi +FP_COMPARE_VERSIONS([$fptools_cv_alex_version],[-lt],[3.1.7], + [AC_MSG_ERROR([Alex version 3.1.7 or later is required to compile GHC.])])[] AlexVersion=$fptools_cv_alex_version; AC_SUBST(AlexVersion) -AC_SUBST(Alex3) ]) diff --git a/compiler/cmm/CmmLex.x b/compiler/cmm/CmmLex.x index 691ca5e..468ea00 100644 --- a/compiler/cmm/CmmLex.x +++ b/compiler/cmm/CmmLex.x @@ -11,13 +11,6 @@ ----------------------------------------------------------------------------- { --- See Note [Warnings in code generated by Alex] in compiler/parser/Lexer.x -{-# OPTIONS_GHC -fno-warn-unused-matches #-} -{-# OPTIONS_GHC -fno-warn-unused-binds #-} -{-# OPTIONS_GHC -fno-warn-unused-imports #-} -{-# OPTIONS_GHC -fno-warn-tabs #-} -{-# OPTIONS_GHC -fno-warn-missing-signatures #-} - module CmmLex ( CmmToken(..), cmmlex, ) where diff --git a/compiler/parser/Lexer.x b/compiler/parser/Lexer.x index f99a344..9597f10 100644 --- a/compiler/parser/Lexer.x +++ b/compiler/parser/Lexer.x @@ -42,13 +42,7 @@ { {-# LANGUAGE BangPatterns #-} - --- See Note [Warnings in code generated by Alex] in compiler/parser/Lexer.x -{-# OPTIONS_GHC -fno-warn-unused-matches #-} -{-# OPTIONS_GHC -fno-warn-unused-binds #-} -{-# OPTIONS_GHC -fno-warn-unused-imports #-} -{-# OPTIONS_GHC -fno-warn-tabs #-} -{-# OPTIONS_GHC -fno-warn-missing-signatures #-} +{-# LANGUAGE LambdaCase #-} {-# OPTIONS_GHC -funbox-strict-fields #-} @@ -1388,13 +1382,15 @@ tok_integral itint transint transbuf translen (radix,char_to_int) span buf len = (offsetBytes transbuf buf) (subtract translen len) radix char_to_int tok_num :: (Integer -> Integer) - -> Int -> Int - -> (Integer, (Char->Int)) -> Action -tok_num = tok_integral itint + -> Int -> Int + -> (Integer, (Char->Int)) -> Action +tok_num = tok_integral $ \case + st@(SourceText ('-':_)) -> itint st (const True) + st@(SourceText _) -> itint st (const False) + st at NoSourceText -> itint st (< 0) where - itint st@(SourceText ('-':str)) val = ITinteger (((IL $! st) $! True) $! val) - itint st@(SourceText str ) val = ITinteger (((IL $! st) $! False) $! val) - itint st@(NoSourceText ) val = ITinteger (((IL $! st) $! (val < 0)) $! val) + itint :: SourceText -> (Integer -> Bool) -> Integer -> Token + itint !st is_negative !val = ITinteger ((IL st $! is_negative val) val) tok_primint :: (Integer -> Integer) -> Int -> Int @@ -3114,36 +3110,4 @@ isDocComment (ITdocCommentNamed _) = True isDocComment (ITdocSection _ _) = True isDocComment (ITdocOptions _) = True isDocComment _ = False - -{- Note [Warnings in code generated by Alex] - -We add the following warning suppression flags to all code generated by Alex: - -{-# OPTIONS_GHC -fno-warn-unused-matches #-} -{-# OPTIONS_GHC -fno-warn-unused-binds #-} -{-# OPTIONS_GHC -fno-warn-unused-imports #-} -{-# OPTIONS_GHC -fno-warn-tabs #-} -{-# OPTIONS_GHC -fno-warn-missing-signatures #-} - -Without these flags, current versions of Alex will generate code that is not -warning free. Note that this is the result of Alex' internals, not of the way -we have written our (Lexer).x files. - -As always, we need code to be warning free when validating with -Werror. - -The list of flags is as short as possible (at the time of writing), to try to -avoid suppressing warnings for bugs in our own code. - -TODO. Reevaluate this situation once Alex >3.1.4 is released. Hopefully you -can remove these flags from all (Lexer).x files in the repository, and also -delete this Note. Don't forget to update aclocal.m4, and send a HEADS UP -message to ghc-devs. - -The first release of Alex after 3.1.4 will either suppress all warnings itself -[1] (bad), or most warnings will be fixed and only a few select ones will be -suppressed by default [2] (better). - -[1] https://github.com/simonmar/alex/commit/1eefcde22ba1bb9b51d523814415714e20f0761e -[2] https://github.com/simonmar/alex/pull/69 --} } diff --git a/mk/config.mk.in b/mk/config.mk.in index 7fa0f77..fb823ae 100644 --- a/mk/config.mk.in +++ b/mk/config.mk.in @@ -859,16 +859,13 @@ SRC_HAPPY_OPTS = -agc --strict # ALEX = @AlexCmd@ ALEX_VERSION = @AlexVersion@ -Alex3 = @Alex3@ # # Options to pass to Alex when we're going to compile the output with GHC # SRC_ALEX_OPTS = -g -ifeq "$(Alex3)" "YES" # The compiler isn't using the Unicode support in Alex 3.0 yet, in fact we do our own # Unicode handling, so diable Alex's. compiler_ALEX_OPTS = --latin1 -endif # Should we build haddock docs? HADDOCK_DOCS = YES diff --git a/utils/genprimopcode/Lexer.x b/utils/genprimopcode/Lexer.x index 06624b2..0de81f9 100644 --- a/utils/genprimopcode/Lexer.x +++ b/utils/genprimopcode/Lexer.x @@ -1,12 +1,4 @@ - { --- See Note [Warnings in code generated by Alex] in compiler/parser/Lexer.x -{-# OPTIONS_GHC -fno-warn-unused-matches #-} -{-# OPTIONS_GHC -fno-warn-unused-binds #-} -{-# OPTIONS_GHC -fno-warn-tabs #-} -{-# OPTIONS_GHC -fno-warn-missing-signatures #-} -{-# OPTIONS_GHC -fno-warn-unused-imports #-} - module Lexer (lex_tok) where import ParserM (ParserM (..), mkT, mkTv, Token(..), start_code, From git at git.haskell.org Thu Nov 22 18:47:43 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Nov 2018 18:47:43 +0000 (UTC) Subject: [commit: ghc] master: Hadrian: Misc. fixes in Haddock rules (ff61955) Message-ID: <20181122184743.8D61C3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ff619555439a8fc671fffb239910972b054a7d96/ghc >--------------------------------------------------------------- commit ff619555439a8fc671fffb239910972b054a7d96 Author: Alec Theriault Date: Thu Nov 22 11:53:10 2018 -0500 Hadrian: Misc. fixes in Haddock rules * Pass 'GHC/Prim.hs' to Haddock when processing 'ghc-prim'. This file is autogenerated for the sole purpose of giving Haddock something to process, so we really should make sure it gets through to Haddock! * Add a "docs-haddock" build rule, which should build all Haddock docs that the Makefile builds by default (all libs + index for libs + ghc) * Prune some unnecessary rules (esp. `gen_contents_index`) Reviewers: bgamari, snowleopard Reviewed By: snowleopard Subscribers: alpmestan, snowleopard, rwbarton, carter Differential Revision: https://phabricator.haskell.org/D5316 >--------------------------------------------------------------- ff619555439a8fc671fffb239910972b054a7d96 hadrian/src/Rules/Documentation.hs | 51 +++++++++++++++++++++++++------------- hadrian/src/Rules/Generate.hs | 2 +- 2 files changed, 35 insertions(+), 18 deletions(-) diff --git a/hadrian/src/Rules/Documentation.hs b/hadrian/src/Rules/Documentation.hs index 92b5ff5..963bc4c 100644 --- a/hadrian/src/Rules/Documentation.hs +++ b/hadrian/src/Rules/Documentation.hs @@ -9,9 +9,10 @@ module Rules.Documentation ( import Hadrian.Haskell.Cabal import Hadrian.Haskell.Cabal.Type +import Rules.Generate (ghcPrimDependencies) import Base import Context -import Expression (getContextData, interpretInContext) +import Expression (getContextData, interpretInContext, (?), package) import Flavour import Oracles.ModuleFiles import Packages @@ -19,6 +20,8 @@ import Settings import Target import Utilities +import Data.List (union) + docRoot :: FilePath docRoot = "docs" @@ -67,15 +70,20 @@ documentationRules = do buildManPage buildPdfDocumentation + -- a phony rule that runs Haddock for "Haskell Hierarchical Libraries" and + -- the "GHC-API" + "docs-haddock" ~> do + root <- buildRoot + need [ root -/- pathIndex "libraries" ] + + -- a phony rule that runs Haddock, builds the User's guide, builds + -- Haddock's manual, and builds man pages "docs" ~> do root <- buildRoot - let html = htmlRoot -/- "index.html" + let html = htmlRoot -/- "index.html" -- also implies "docs-haddock" archives = map pathArchive docPaths pdfs = map pathPdf $ docPaths \\ ["libraries"] - need $ map (root -/-) $ [html] ++ archives ++ pdfs - need [ root -/- htmlRoot -/- "libraries" -/- "gen_contents_index" - , root -/- htmlRoot -/- "libraries" -/- "prologue.txt" - , root -/- manPageBuildPath ] + need $ map (root -/-) $ [html] ++ archives ++ pdfs ++ [manPageBuildPath] ------------------------------------- HTML ------------------------------------- @@ -85,11 +93,6 @@ buildHtmlDocumentation = do mapM_ buildSphinxHtml $ docPaths \\ ["libraries"] buildLibraryDocumentation root <- buildRootRules - root -/- htmlRoot -/- "libraries/gen_contents_index" %> - copyFile "libraries/gen_contents_index" - - root -/- htmlRoot -/- "libraries/prologue.txt" %> - copyFile "libraries/prologue.txt" root -/- htmlRoot -/- "index.html" %> \file -> do need [root -/- haddockHtmlLib] @@ -116,13 +119,19 @@ buildLibraryDocumentation = do root -/- haddockHtmlLib %> \_ -> copyDirectory "utils/haddock/haddock-api/resources/html" (root -/- docRoot) + -- Building the "Haskell Hierarchical Libraries" index root -/- htmlRoot -/- "libraries/index.html" %> \file -> do - need [root -/- haddockHtmlLib] + need [ root -/- haddockHtmlLib + , "libraries/prologue.txt" ] + + -- We want Haddocks for everything except `rts` to be built, but we + -- don't want the index to be polluted by stuff from `ghc`-the-library + -- (there will be a seperate top-level link to those Haddocks). haddocks <- allHaddocks - let libDocs = filter - (\x -> takeFileName x `notElem` ["ghc.haddock", "rts.haddock"]) - haddocks - need (root -/- haddockHtmlLib : libDocs) + let neededDocs = filter (\x -> takeFileName x /= "rts.haddock") haddocks + libDocs = filter (\x -> takeFileName x /= "ghc.haddock") neededDocs + + need neededDocs build $ target docContext (Haddock BuildIndex) libDocs [file] allHaddocks :: Action [FilePath] @@ -150,7 +159,15 @@ buildPackageDocumentation context at Context {..} = when (stage == Stage1 && packag root -/- htmlRoot -/- "libraries" -/- pkgName package -/- pkgName package <.> "haddock" %> \file -> do need [root -/- htmlRoot -/- "libraries" -/- pkgName package -/- "haddock-prologue.txt"] haddocks <- haddockDependencies context - srcs <- hsSources context + + -- `ghc-prim` has a source file for 'GHC.Prim' which is generated just + -- for Haddock. We need to 'union' (instead of '++') to avoid passing + -- 'GHC.PrimopWrappers' (which unfortunately shows up in both + -- `generatedSrcs` and `vanillaSrcs`) to Haddock twice. + generatedSrcs <- interpretInContext context (Expression.package ghcPrim ? ghcPrimDependencies) + vanillaSrcs <- hsSources context + let srcs = vanillaSrcs `union` generatedSrcs + need $ srcs ++ haddocks ++ [root -/- haddockHtmlLib] -- Build Haddock documentation diff --git a/hadrian/src/Rules/Generate.hs b/hadrian/src/Rules/Generate.hs index c3650c3..7c59899 100644 --- a/hadrian/src/Rules/Generate.hs +++ b/hadrian/src/Rules/Generate.hs @@ -1,6 +1,6 @@ module Rules.Generate ( isGeneratedCmmFile, generatePackageCode, generateRules, copyRules, - includesDependencies, generatedDependencies + includesDependencies, generatedDependencies, ghcPrimDependencies ) where import Base From git at git.haskell.org Thu Nov 22 18:47:59 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Nov 2018 18:47:59 +0000 (UTC) Subject: [commit: ghc] master: Overhaul -fprint-explicit-kinds to use VKA (f5d2083) Message-ID: <20181122184759.7AD2F3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f5d2083807a03c57f194fcc3a7baf82e34aad524/ghc >--------------------------------------------------------------- commit f5d2083807a03c57f194fcc3a7baf82e34aad524 Author: Ryan Scott Date: Thu Nov 22 11:55:00 2018 -0500 Overhaul -fprint-explicit-kinds to use VKA This patch changes the behavior of `-fprint-explicit-kinds` so that it displays kind argument using visible kind application. In other words, the flag now: 1. Prints instantiations of specified variables with `@(...)`. 2. Prints instantiations of inferred variables with `@{...}`. In addition, this patch removes the `Use -fprint-explicit-kinds to see the kind arguments` error message that often arises when a type mismatch occurs due to different kinds. Instead, whenever there is a kind mismatch, we now enable the `-fprint-explicit-kinds` flag locally to help cue to the programmer where the error lies. (See `Note [Kind arguments in error messages]` in `TcErrors`.) As a result, these funny `@{...}` things can now appear to the user even without turning on the `-fprint-explicit-kinds` flag explicitly, so I took the liberty of documenting them in the users' guide. Test Plan: ./validate Reviewers: goldfire, simonpj, bgamari Reviewed By: simonpj Subscribers: rwbarton, carter GHC Trac Issues: #15871 Differential Revision: https://phabricator.haskell.org/D5314 >--------------------------------------------------------------- f5d2083807a03c57f194fcc3a7baf82e34aad524 compiler/backpack/RnModIface.hs | 4 +- compiler/basicTypes/Var.hs | 2 +- compiler/iface/IfaceSyn.hs | 7 +- compiler/iface/IfaceType.hs | 224 +++++--- compiler/iface/ToIface.hs | 7 +- compiler/typecheck/FamInst.hs | 9 +- compiler/typecheck/FunDeps.hs | 6 +- compiler/typecheck/TcErrors.hs | 78 ++- compiler/typecheck/TcType.hs | 95 +++- compiler/typecheck/TcValidity.hs | 48 +- compiler/types/TyCoRep.hs | 17 +- compiler/types/Type.hs | 4 +- docs/users_guide/using.rst | 20 +- .../tests/dependent/should_fail/T15825.stderr | 5 +- .../tests/generics/T10604/T10604_deriving.stderr | 597 ++++++++++----------- testsuite/tests/ghci/scripts/GhciKinds.stdout | 2 +- testsuite/tests/ghci/scripts/T11376.stdout | 8 +- testsuite/tests/ghci/scripts/T15341.stdout | 4 +- testsuite/tests/ghci/scripts/T6018ghcifail.stderr | 14 +- .../tests/indexed-types/should_fail/T9171.stderr | 7 +- .../partial-sigs/should_compile/T15039b.stderr | 10 +- .../partial-sigs/should_compile/T15039d.stderr | 10 +- testsuite/tests/polykinds/T10570.stderr | 3 +- testsuite/tests/polykinds/T14520.stderr | 2 +- testsuite/tests/polykinds/T9144.stderr | 5 +- testsuite/tests/polykinds/TidyClassKinds.stderr | 2 +- .../tests/typecheck/should_fail/T15515.stderr | 3 +- .../tests/typecheck/should_fail/T6018fail.stderr | 17 +- .../typecheck/should_fail/T6018failclosed.stderr | 7 +- 29 files changed, 674 insertions(+), 543 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 f5d2083807a03c57f194fcc3a7baf82e34aad524 From git at git.haskell.org Thu Nov 22 18:48:16 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Nov 2018 18:48:16 +0000 (UTC) Subject: [commit: ghc] master: UNREG: PprC: Add support for adjacent floats (35a8977) Message-ID: <20181122184816.371443A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/35a897782b6b0a252da7fdcf4921198ad4e1d96c/ghc >--------------------------------------------------------------- commit 35a897782b6b0a252da7fdcf4921198ad4e1d96c Author: James Clarke Date: Thu Nov 22 11:55:17 2018 -0500 UNREG: PprC: Add support for adjacent floats When two 32-bit floats are adjacent for a 64-bit target, there is no padding between them to force alignment, so we must combine their bit representations into a single word. Reviewers: bgamari, simonmar Reviewed By: simonmar Subscribers: rwbarton, carter GHC Trac Issues: #15853 Differential Revision: https://phabricator.haskell.org/D5306 >--------------------------------------------------------------- 35a897782b6b0a252da7fdcf4921198ad4e1d96c compiler/cmm/PprC.hs | 24 +++++++++++++++++++++++- 1 file changed, 23 insertions(+), 1 deletion(-) diff --git a/compiler/cmm/PprC.hs b/compiler/cmm/PprC.hs index 17fef7f..6ebfd20 100644 --- a/compiler/cmm/PprC.hs +++ b/compiler/cmm/PprC.hs @@ -512,9 +512,12 @@ pprLit1 other = pprLit other pprStatics :: DynFlags -> [CmmStatic] -> [SDoc] pprStatics _ [] = [] pprStatics dflags (CmmStaticLit (CmmFloat f W32) : rest) - -- floats are padded to a word by padLitToWord, see #1852 + -- odd numbers of floats are padded to a word by mkVirtHeapOffsetsWithPadding | wORD_SIZE dflags == 8, CmmStaticLit (CmmInt 0 W32) : rest' <- rest = pprLit1 (floatToWord dflags f) : pprStatics dflags rest' + -- adjacent floats aren't padded but combined into a single word + | wORD_SIZE dflags == 8, CmmStaticLit (CmmFloat g W32) : rest' <- rest + = pprLit1 (floatPairToWord dflags f g) : pprStatics dflags rest' | wORD_SIZE dflags == 4 = pprLit1 (floatToWord dflags f) : pprStatics dflags rest | otherwise @@ -1270,6 +1273,25 @@ floatToWord dflags r , wORDS_BIGENDIAN dflags = 32 | otherwise = 0 +floatPairToWord :: DynFlags -> Rational -> Rational -> CmmLit +floatPairToWord dflags r1 r2 + = runST (do + arr <- newArray_ ((0::Int),1) + writeArray arr 0 (fromRational r1) + writeArray arr 1 (fromRational r2) + arr' <- castFloatToWord32Array arr + w32_1 <- readArray arr' 0 + w32_2 <- readArray arr' 1 + return (pprWord32Pair w32_1 w32_2) + ) + where pprWord32Pair w32_1 w32_2 + | wORDS_BIGENDIAN dflags = + CmmInt ((shiftL i1 32) .|. i2) W64 + | otherwise = + CmmInt ((shiftL i2 32) .|. i1) W64 + where i1 = toInteger w32_1 + i2 = toInteger w32_2 + doubleToWords :: DynFlags -> Rational -> [CmmLit] doubleToWords dflags r = runST (do From git at git.haskell.org Thu Nov 22 21:02:46 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Nov 2018 21:02:46 +0000 (UTC) Subject: [commit: ghc] master: llvmGen: Eliminate duplicate definition (d0fc761) Message-ID: <20181122210246.859713A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d0fc76189b9b709378849d071814342983c3a5df/ghc >--------------------------------------------------------------- commit d0fc76189b9b709378849d071814342983c3a5df Author: Gabor Greif Date: Tue Nov 20 14:35:09 2018 +0100 llvmGen: Eliminate duplicate definition remove local >--------------------------------------------------------------- d0fc76189b9b709378849d071814342983c3a5df compiler/llvmGen/LlvmCodeGen/Base.hs | 3 +-- compiler/llvmGen/LlvmCodeGen/Ppr.hs | 2 +- 2 files changed, 2 insertions(+), 3 deletions(-) diff --git a/compiler/llvmGen/LlvmCodeGen/Base.hs b/compiler/llvmGen/LlvmCodeGen/Base.hs index 6e20da4..21b45e5 100644 --- a/compiler/llvmGen/LlvmCodeGen/Base.hs +++ b/compiler/llvmGen/LlvmCodeGen/Base.hs @@ -474,8 +474,7 @@ generateExternDecls = do -- @$def@ suffix, and generate the appropriate alias. aliasify :: LMGlobal -> LlvmM [LMGlobal] aliasify (LMGlobal var val) = do - let i8Ptr = LMPointer (LMInt 8) - LMGlobalVar lbl ty link sect align const = var + let LMGlobalVar lbl ty link sect align const = var defLbl = lbl `appendFS` fsLit "$def" defVar = LMGlobalVar defLbl ty Internal sect align const diff --git a/compiler/llvmGen/LlvmCodeGen/Ppr.hs b/compiler/llvmGen/LlvmCodeGen/Ppr.hs index 2a8340b..c1378aa 100644 --- a/compiler/llvmGen/LlvmCodeGen/Ppr.hs +++ b/compiler/llvmGen/LlvmCodeGen/Ppr.hs @@ -89,7 +89,7 @@ pprLlvmCmmDecl (CmmProc mb_info entry_lbl live (ListGraph blks)) Alias alias = LMGlobal funVar (Just $ LMBitc (LMStaticPointer defVar) - (LMPointer $ LMInt 8)) + i8Ptr) return (ppLlvmGlobal alias $+$ ppLlvmFunction fun', []) From git at git.haskell.org Thu Nov 22 21:03:02 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Nov 2018 21:03:02 +0000 (UTC) Subject: [commit: ghc] master: circleci: Actually build with in-tree GMP on Darwin (3584bd4) Message-ID: <20181122210302.D2E823A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/3584bd4255eb59be043252c9b4ef16bcbd835c9b/ghc >--------------------------------------------------------------- commit 3584bd4255eb59be043252c9b4ef16bcbd835c9b Author: Dario Bertini Date: Fri Nov 16 10:25:32 2018 +0100 circleci: Actually build with in-tree GMP on Darwin Fixes #15404. >--------------------------------------------------------------- 3584bd4255eb59be043252c9b4ef16bcbd835c9b .circleci/config.yml | 4 +--- .circleci/prepare-system.sh | 1 + 2 files changed, 2 insertions(+), 3 deletions(-) diff --git a/.circleci/config.yml b/.circleci/config.yml index f80b2b3..5e49cde 100644 --- a/.circleci/config.yml +++ b/.circleci/config.yml @@ -41,7 +41,7 @@ aliases: - &configure_unix run: name: Configure - command: ./configure $CONFIGURE_OPTS + command: ./configure - &configure_unix_32 run: name: Configure @@ -162,8 +162,6 @@ jobs: # Only Sierra and onwards supports clock_gettime. See #12858 ac_cv_func_clock_gettime: "no" GHC_COLLECTOR_FLAVOR: x86_64-darwin - # Build with in-tree GMP since this isn't available on OS X by default. - CONFIGURE_OPTS: --with-intree-gmp <<: *buildenv TEST_ENV: x86_64-darwin steps: diff --git a/.circleci/prepare-system.sh b/.circleci/prepare-system.sh index dbb1011..4be1b64 100755 --- a/.circleci/prepare-system.sh +++ b/.circleci/prepare-system.sh @@ -69,6 +69,7 @@ case "$(uname)" in ln -s $HOME/.cabal/bin/alex /usr/local/bin/alex || true ln -s $HOME/.cabal/bin/happy /usr/local/bin/happy || true ln -s $HOME/.cabal/bin/HsColour /usr/local/bin/HsColour || true + echo "libraries/integer-gmp_CONFIGURE_OPTS += --configure-option=--with-intree-gmp" >> mk/build.mk ;; *) fail "uname=$(uname) not supported" From git at git.haskell.org Thu Nov 22 21:05:09 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Nov 2018 21:05:09 +0000 (UTC) Subject: [commit: ghc] master: rts/MachO: Add a bit more debugging output to getNames (9e0a23b) Message-ID: <20181122210509.C69E13A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9e0a23b95c285c4019fd2d36102374ee582f1dcb/ghc >--------------------------------------------------------------- commit 9e0a23b95c285c4019fd2d36102374ee582f1dcb Author: Dario Bertini Date: Fri Nov 16 15:46:54 2018 +0100 rts/MachO: Add a bit more debugging output to getNames >--------------------------------------------------------------- 9e0a23b95c285c4019fd2d36102374ee582f1dcb rts/linker/MachO.c | 11 +++++++---- 1 file changed, 7 insertions(+), 4 deletions(-) diff --git a/rts/linker/MachO.c b/rts/linker/MachO.c index e28d173..46fb657 100644 --- a/rts/linker/MachO.c +++ b/rts/linker/MachO.c @@ -1613,14 +1613,17 @@ ocGetNames_MachO(ObjectCode* oc) "ocGetNames_MachO(oc->symbols)"); if (oc->info->symCmd) { + debugBelch("ocGetNames_MachO: %d macho symbols\n", oc->info->n_macho_symbols); for (size_t i = 0; i < oc->info->n_macho_symbols; i++) { + SymbolName* nm = oc->info->macho_symbols[i].name; if(oc->info->nlist[i].n_type & N_STAB) - ; + { + IF_DEBUG(linker, debugBelch("ocGetNames_MachO: Skip STAB: %s\n", nm)); + } else if((oc->info->nlist[i].n_type & N_TYPE) == N_SECT) { if(oc->info->nlist[i].n_type & N_EXT) { - SymbolName* nm = oc->info->macho_symbols[i].name; if ( (oc->info->nlist[i].n_desc & N_WEAK_DEF) && lookupSymbol_(nm)) { // weak definition, and we already have a definition @@ -1644,12 +1647,12 @@ ocGetNames_MachO(ObjectCode* oc) } else { - IF_DEBUG(linker, debugBelch("ocGetNames_MachO: \t...not external, skipping\n")); + IF_DEBUG(linker, debugBelch("ocGetNames_MachO: \t...not external, skipping %s\n", nm)); } } else { - IF_DEBUG(linker, debugBelch("ocGetNames_MachO: \t...not defined in this section, skipping\n")); + IF_DEBUG(linker, debugBelch("ocGetNames_MachO: \t...not defined in this section, skipping %s\n", nm)); } } } From git at git.haskell.org Thu Nov 22 21:05:24 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Nov 2018 21:05:24 +0000 (UTC) Subject: [commit: ghc] master: rts/MachO: A bit of refactoring in ocGetNames (b2f6f89) Message-ID: <20181122210524.8825F3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b2f6f896a0bae0e68ec629bd6817a2cb2533a12c/ghc >--------------------------------------------------------------- commit b2f6f896a0bae0e68ec629bd6817a2cb2533a12c Author: Dario Bertini Date: Fri Nov 16 15:48:36 2018 +0100 rts/MachO: A bit of refactoring in ocGetNames Eliminates a bit of repetition. >--------------------------------------------------------------- b2f6f896a0bae0e68ec629bd6817a2cb2533a12c rts/linker/MachO.c | 15 +++++++-------- 1 file changed, 7 insertions(+), 8 deletions(-) diff --git a/rts/linker/MachO.c b/rts/linker/MachO.c index 46fb657..87888e9 100644 --- a/rts/linker/MachO.c +++ b/rts/linker/MachO.c @@ -1613,7 +1613,6 @@ ocGetNames_MachO(ObjectCode* oc) "ocGetNames_MachO(oc->symbols)"); if (oc->info->symCmd) { - debugBelch("ocGetNames_MachO: %d macho symbols\n", oc->info->n_macho_symbols); for (size_t i = 0; i < oc->info->n_macho_symbols; i++) { SymbolName* nm = oc->info->macho_symbols[i].name; if(oc->info->nlist[i].n_type & N_STAB) @@ -1663,14 +1662,14 @@ ocGetNames_MachO(ObjectCode* oc) if (oc->info->symCmd) { for (int i = 0; i < oc->n_symbols; i++) { - if((oc->info->nlist[i].n_type & N_TYPE) == N_UNDF - && (oc->info->nlist[i].n_type & N_EXT) - && (oc->info->nlist[i].n_value != 0)) { - - SymbolName* nm = oc->info->macho_symbols[i].name; - unsigned long sz = oc->info->nlist[i].n_value; + SymbolName* nm = oc->info->macho_symbols[i].name; + MachONList *nlist = &oc->info->nlist[i]; + if((nlist->n_type & N_TYPE) == N_UNDF + && (nlist->n_type & N_EXT) + && (nlist->n_value != 0)) { + unsigned long sz = nlist->n_value; - oc->info->nlist[i].n_value = commonCounter; + nlist->n_value = commonCounter; /* also set the final address to the macho_symbol */ oc->info->macho_symbols[i].addr = (void*)commonCounter; From git at git.haskell.org Thu Nov 22 21:05:40 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Nov 2018 21:05:40 +0000 (UTC) Subject: [commit: ghc] master: rts/MachO: Iterate through N (all) symbols, not M external symbols (2548908) Message-ID: <20181122210540.4EA1D3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/254890855ee04762cc0392da19e0c42fc039a718/ghc >--------------------------------------------------------------- commit 254890855ee04762cc0392da19e0c42fc039a718 Author: Dario Bertini Date: Fri Nov 16 15:49:37 2018 +0100 rts/MachO: Iterate through N (all) symbols, not M external symbols Fixes #15105 >--------------------------------------------------------------- 254890855ee04762cc0392da19e0c42fc039a718 rts/linker/MachO.c | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/rts/linker/MachO.c b/rts/linker/MachO.c index 87888e9..fd36cd2 100644 --- a/rts/linker/MachO.c +++ b/rts/linker/MachO.c @@ -1661,7 +1661,7 @@ ocGetNames_MachO(ObjectCode* oc) commonCounter = (unsigned long)commonStorage; if (oc->info->symCmd) { - for (int i = 0; i < oc->n_symbols; i++) { + for (size_t i = 0; i < oc->info->n_macho_symbols; i++) { SymbolName* nm = oc->info->macho_symbols[i].name; MachONList *nlist = &oc->info->nlist[i]; if((nlist->n_type & N_TYPE) == N_UNDF From git at git.haskell.org Thu Nov 22 21:05:55 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Nov 2018 21:05:55 +0000 (UTC) Subject: [commit: ghc] master: LLVM: Use generic code for small size quot-rem ops (9f3e22b) Message-ID: <20181122210555.8A0793A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9f3e22b9eb2e67323f965b652c37fdd73628b007/ghc >--------------------------------------------------------------- commit 9f3e22b9eb2e67323f965b652c37fdd73628b007 Author: Peter Trommler Date: Sun Nov 18 16:41:38 2018 +0100 LLVM: Use generic code for small size quot-rem ops >--------------------------------------------------------------- 9f3e22b9eb2e67323f965b652c37fdd73628b007 compiler/codeGen/StgCmmPrim.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/codeGen/StgCmmPrim.hs b/compiler/codeGen/StgCmmPrim.hs index eb4d681..015eece 100644 --- a/compiler/codeGen/StgCmmPrim.hs +++ b/compiler/codeGen/StgCmmPrim.hs @@ -885,7 +885,7 @@ callishPrimOpSupported dflags op | otherwise -> Right (genericIntQuotRemOp W8) Int16QuotRemOp | (ncg && x86ish) - || llvm -> Left (MO_S_QuotRem W16) + -> Left (MO_S_QuotRem W16) | otherwise -> Right (genericIntQuotRemOp W16) @@ -904,7 +904,7 @@ callishPrimOpSupported dflags op | otherwise -> Right (genericWordQuotRemOp W8) Word16QuotRemOp| (ncg && x86ish) - || llvm -> Left (MO_U_QuotRem W16) + -> Left (MO_U_QuotRem W16) | otherwise -> Right (genericWordQuotRemOp W16) WordAdd2Op | (ncg && (x86ish From git at git.haskell.org Thu Nov 22 21:07:26 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Nov 2018 21:07:26 +0000 (UTC) Subject: [commit: ghc] master: Doc-only fixes (a1bbb56) Message-ID: <20181122210726.A74E63A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/a1bbb56f40b679f4841f0b044c0f5445ff6d3c5b/ghc >--------------------------------------------------------------- commit a1bbb56f40b679f4841f0b044c0f5445ff6d3c5b Author: Alec Theriault Date: Thu Sep 20 23:31:00 2018 -0700 Doc-only fixes * laws are capitalized definition lists, no emphasis on the labels * adds missing hyperlinks * fixes other misc. Haddock markup issues. >--------------------------------------------------------------- a1bbb56f40b679f4841f0b044c0f5445ff6d3c5b libraries/base/Control/Applicative.hs | 4 +- libraries/base/Control/Category.hs | 9 ++--- libraries/base/Control/Monad/Fix.hs | 8 ++-- libraries/base/Control/Monad/Zip.hs | 17 ++++---- libraries/base/Data/Bifoldable.hs | 8 +++- libraries/base/Data/Bitraversable.hs | 6 +-- libraries/base/Data/Fixed.hs | 15 +++---- libraries/base/Data/Functor/Classes.hs | 14 ++++--- libraries/base/Data/Functor/Contravariant.hs | 25 ++++-------- libraries/base/Data/Proxy.hs | 2 +- libraries/base/Data/STRef.hs | 2 +- libraries/base/Data/Traversable.hs | 54 ++++++++++---------------- libraries/base/Data/Type/Equality.hs | 4 +- libraries/base/GHC/Base.hs | 48 +++++++++++------------ libraries/base/GHC/Float.hs | 1 + libraries/base/GHC/IORef.hs | 4 +- libraries/base/Text/ParserCombinators/ReadP.hs | 2 +- libraries/base/Text/Printf.hs | 12 +++--- libraries/base/Text/Show/Functions.hs | 2 +- libraries/base/Type/Reflection.hs | 4 +- libraries/base/Unsafe/Coerce.hs | 9 +++-- 21 files changed, 114 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 a1bbb56f40b679f4841f0b044c0f5445ff6d3c5b From git at git.haskell.org Thu Nov 22 21:07:41 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Nov 2018 21:07:41 +0000 (UTC) Subject: [commit: ghc] master: 'DynFlag'-free version of 'mkParserFlags' (5aa2923) Message-ID: <20181122210741.57F5A3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5aa29231ab7603537284eff5e4caff3a73dba6d2/ghc >--------------------------------------------------------------- commit 5aa29231ab7603537284eff5e4caff3a73dba6d2 Author: Alec Theriault Date: Thu Nov 22 14:39:41 2018 -0500 'DynFlag'-free version of 'mkParserFlags' Obtaining a `DynFlags` is difficult, making using the lexer/parser for pure parsing/lexing unreasonably difficult, even with `mkPStatePure`. This is despite the fact that we only really need * language extension flags * warning flags * a handful of boolean options The new `mkParserFlags'` function makes is easier to directly construct a `ParserFlags`. Furthermore, since `pExtsBitmap` is just a footgun, I've gone ahead and made `ParserFlags` an abstract type. Reviewers: bgamari, alanz, sjakobi Reviewed By: bgamari, sjakobi Subscribers: mpickering, sjakobi, rwbarton, carter GHC Trac Issues: #11301 Differential Revision: https://phabricator.haskell.org/D5269 >--------------------------------------------------------------- 5aa29231ab7603537284eff5e4caff3a73dba6d2 compiler/parser/Lexer.x | 106 ++++++++++++++++++++++++++++---------------- compiler/parser/Parser.y | 10 ++--- compiler/parser/RdrHsSyn.hs | 22 +++++---- 3 files changed, 83 insertions(+), 55 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 5aa29231ab7603537284eff5e4caff3a73dba6d2 From git at git.haskell.org Thu Nov 22 21:07:42 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Nov 2018 21:07:42 +0000 (UTC) Subject: [commit: ghc] master: 'DynFlag'-free version of 'mkParserFlags' (5aa2923) Message-ID: <20181122210742.1B1383A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/5aa29231ab7603537284eff5e4caff3a73dba6d2/ghc >--------------------------------------------------------------- commit 5aa29231ab7603537284eff5e4caff3a73dba6d2 Author: Alec Theriault Date: Thu Nov 22 14:39:41 2018 -0500 'DynFlag'-free version of 'mkParserFlags' Obtaining a `DynFlags` is difficult, making using the lexer/parser for pure parsing/lexing unreasonably difficult, even with `mkPStatePure`. This is despite the fact that we only really need * language extension flags * warning flags * a handful of boolean options The new `mkParserFlags'` function makes is easier to directly construct a `ParserFlags`. Furthermore, since `pExtsBitmap` is just a footgun, I've gone ahead and made `ParserFlags` an abstract type. Reviewers: bgamari, alanz, sjakobi Reviewed By: bgamari, sjakobi Subscribers: mpickering, sjakobi, rwbarton, carter GHC Trac Issues: #11301 Differential Revision: https://phabricator.haskell.org/D5269 >--------------------------------------------------------------- 5aa29231ab7603537284eff5e4caff3a73dba6d2 compiler/parser/Lexer.x | 106 ++++++++++++++++++++++++++++---------------- compiler/parser/Parser.y | 10 ++--- compiler/parser/RdrHsSyn.hs | 22 +++++---- 3 files changed, 83 insertions(+), 55 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 5aa29231ab7603537284eff5e4caff3a73dba6d2 From git at git.haskell.org Thu Nov 22 21:09:15 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Nov 2018 21:09:15 +0000 (UTC) Subject: [commit: ghc] master: Simplify 'ExtBits' in the lexer (d2fbc33) Message-ID: <20181122210915.3D0A93A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/d2fbc33c4ff3074126ab71654af8bbf8a46e4e11/ghc >--------------------------------------------------------------- commit d2fbc33c4ff3074126ab71654af8bbf8a46e4e11 Author: Alec Theriault Date: Thu Nov 22 14:40:08 2018 -0500 Simplify 'ExtBits' in the lexer The main change is to export 'ExtBits' instead of defining/exporting a bunch of boilerplate functions that test for a particular 'ExtBits'. In the process, I also * cleaned up an unneeded special case for 'ITstatic' * made 'UsePosPrags' another variant of 'ExtBits' * made the logic in 'reservedSymsFM' match that of 'reservedWordsFM' Test Plan: make test Reviewers: bgamari, alanz Subscribers: sjakobi, rwbarton, mpickering, carter Differential Revision: https://phabricator.haskell.org/D5332 >--------------------------------------------------------------- d2fbc33c4ff3074126ab71654af8bbf8a46e4e11 compiler/parser/Lexer.x | 498 +++++++++++++++++++------------------------- compiler/parser/Parser.y | 14 +- compiler/parser/RdrHsSyn.hs | 32 +-- 3 files changed, 238 insertions(+), 306 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 d2fbc33c4ff3074126ab71654af8bbf8a46e4e11 From git at git.haskell.org Thu Nov 22 21:09:30 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Nov 2018 21:09:30 +0000 (UTC) Subject: [commit: ghc] master: Don't pass -no-pie when -pgmc is supplied (8d008b7) Message-ID: <20181122210930.C025F3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8d008b71db53f7a59673f894f329b8d71f84c8ee/ghc >--------------------------------------------------------------- commit 8d008b71db53f7a59673f894f329b8d71f84c8ee Author: Krzysztof Gogolewski Date: Thu Nov 22 14:46:27 2018 -0500 Don't pass -no-pie when -pgmc is supplied Test Plan: validate Reviewers: bgamari Reviewed By: bgamari Subscribers: rwbarton, carter GHC Trac Issues: #15319 Differential Revision: https://phabricator.haskell.org/D5317 >--------------------------------------------------------------- 8d008b71db53f7a59673f894f329b8d71f84c8ee compiler/main/DynFlags.hs | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs index 2b19922..654c347 100644 --- a/compiler/main/DynFlags.hs +++ b/compiler/main/DynFlags.hs @@ -2935,7 +2935,10 @@ dynamic_flags_deps = [ , make_ord_flag defFlag "pgmF" (hasArg (\f -> alterSettings (\s -> s { sPgm_F = f}))) , make_ord_flag defFlag "pgmc" - (hasArg (\f -> alterSettings (\s -> s { sPgm_c = (f,[])}))) + (hasArg (\f -> alterSettings (\s -> s { sPgm_c = (f,[]), + -- Don't pass -no-pie with -pgmc + -- (see Trac #15319) + sGccSupportsNoPie = False}))) , make_ord_flag defFlag "pgms" (hasArg (\f -> alterSettings (\s -> s { sPgm_s = (f,[])}))) , make_ord_flag defFlag "pgma" From git at git.haskell.org Thu Nov 22 21:10:44 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Nov 2018 21:10:44 +0000 (UTC) Subject: [commit: ghc] master: Fix unused-import warnings (6353efc) Message-ID: <20181122211044.EF67D3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6353efc7694ba8ec86c091918e02595662169ae2/ghc >--------------------------------------------------------------- commit 6353efc7694ba8ec86c091918e02595662169ae2 Author: David Eichmann Date: Thu Nov 22 14:48:05 2018 -0500 Fix unused-import warnings This patch fixes a fairly long-standing bug (dating back to 2015) in RdrName.bestImport, namely commit 9376249b6b78610db055a10d05f6592d6bbbea2f Author: Simon Peyton Jones Date: Wed Oct 28 17:16:55 2015 +0000 Fix unused-import stuff in a better way In that patch got the sense of the comparison back to front, and thereby failed to implement the unused-import rules described in Note [Choosing the best import declaration] in RdrName This led to Trac #13064 and #15393 Fixing this bug revealed a bunch of unused imports in libraries; the ones in the GHC repo are part of this commit. The two important changes are * Fix the bug in bestImport * Modified the rules by adding (a) in Note [Choosing the best import declaration] in RdrName Reason: the previosu rules made Trac #5211 go bad again. And the new rule (a) makes sense to me. In unravalling this I also ended up doing a few other things * Refactor RnNames.ImportDeclUsage to use a [GlobalRdrElt] for the things that are used, rather than [AvailInfo]. This is simpler and more direct. * Rename greParentName to greParent_maybe, to follow GHC naming conventions * Delete dead code RdrName.greUsedRdrName Bumps a few submodules. Reviewers: hvr, goldfire, bgamari, simonmar, jrtc27 Subscribers: rwbarton, carter Differential Revision: https://phabricator.haskell.org/D5312 >--------------------------------------------------------------- 6353efc7694ba8ec86c091918e02595662169ae2 compiler/basicTypes/RdrName.hs | 102 ++++++--- compiler/cmm/Bitmap.hs | 1 - compiler/cmm/CmmCommonBlockElim.hs | 1 - compiler/cmm/CmmLayoutStack.hs | 2 +- compiler/cmm/CmmProcPoint.hs | 2 +- compiler/cmm/Hoopl/Collections.hs | 2 +- compiler/codeGen/StgCmmProf.hs | 1 - compiler/coreSyn/CoreOpt.hs | 2 +- compiler/coreSyn/CorePrep.hs | 2 +- compiler/coreSyn/CoreStats.hs | 2 - compiler/deSugar/DsBinds.hs | 2 +- compiler/ghci/ByteCodeLink.hs | 1 - compiler/ghci/RtClosureInspect.hs | 5 +- compiler/hsSyn/Convert.hs | 1 - compiler/hsSyn/HsBinds.hs | 1 - compiler/hsSyn/HsExtension.hs | 1 - compiler/hsSyn/HsImpExp.hs | 3 + compiler/hsSyn/HsTypes.hs | 1 - compiler/llvmGen/LlvmCodeGen/CodeGen.hs | 1 - compiler/main/Ar.hs | 1 - compiler/main/DynFlags.hs | 2 + compiler/main/DynamicLoading.hs | 5 +- compiler/main/Finder.hs | 1 - compiler/main/GHC.hs | 2 - compiler/main/HscMain.hs | 1 - compiler/main/HscStats.hs | 1 - compiler/main/Packages.hs | 1 - .../nativeGen/RegAlloc/Linear/JoinToTargets.hs | 2 - compiler/nativeGen/RegAlloc/Linear/PPC/FreeRegs.hs | 1 - .../nativeGen/RegAlloc/Linear/SPARC/FreeRegs.hs | 1 - compiler/nativeGen/RegAlloc/Linear/X86/FreeRegs.hs | 1 - .../nativeGen/RegAlloc/Linear/X86_64/FreeRegs.hs | 1 - compiler/parser/RdrHsSyn.hs | 1 - compiler/rename/RnEnv.hs | 19 +- compiler/rename/RnExpr.hs-boot | 1 - compiler/rename/RnNames.hs | 233 +++++++++++---------- compiler/rename/RnSource.hs | 2 +- compiler/simplStg/RepType.hs | 2 +- compiler/specialise/Specialise.hs | 1 - compiler/typecheck/ClsInst.hs | 2 - compiler/typecheck/TcBackpack.hs | 2 +- compiler/typecheck/TcCanonical.hs | 2 +- compiler/typecheck/TcDeriv.hs | 2 +- compiler/typecheck/TcErrors.hs | 2 +- compiler/typecheck/TcHoleErrors.hs | 1 - compiler/typecheck/TcHsSyn.hs | 1 - compiler/typecheck/TcInstDcls.hs-boot | 1 - compiler/typecheck/TcInteract.hs | 4 +- compiler/typecheck/TcPatSyn.hs | 4 +- compiler/typecheck/TcRnTypes.hs | 5 +- compiler/typecheck/TcSMonad.hs | 3 +- compiler/typecheck/TcType.hs | 2 +- compiler/typecheck/TcTypeable.hs | 1 - compiler/types/TyCon.hs | 4 +- compiler/utils/OrdList.hs | 1 - compiler/utils/Outputable.hs | 1 - compiler/utils/UniqSet.hs | 1 - ghc/GHCi/Leak.hs | 2 +- hadrian/hadrian.cabal | 2 +- hadrian/src/Hadrian/Haskell/Cabal/Parse.hs | 2 +- libraries/Cabal | 2 +- libraries/base/Data/Functor/Classes.hs | 1 - libraries/base/Data/Functor/Compose.hs | 2 - libraries/base/Data/Functor/Contravariant.hs | 1 - libraries/base/Data/Functor/Product.hs | 3 - libraries/base/Data/Functor/Sum.hs | 2 - libraries/base/Data/Semigroup.hs | 3 - libraries/base/GHC/Event/PSQ.hs | 1 - libraries/base/GHC/Generics.hs | 2 +- libraries/base/GHC/Show.hs | 1 - libraries/base/GHC/StaticPtr.hs | 1 - libraries/bytestring | 2 +- libraries/ghc-prim/GHC/Magic.hs | 10 +- libraries/ghci/GHCi/CreateBCO.hs | 2 +- testsuite/tests/driver/T4437.hs | 1 - testsuite/tests/module/mod177.stderr | 2 +- testsuite/tests/rename/should_compile/T13064.hs | 8 + .../tests/rename/should_compile/T13064.stderr | 3 + testsuite/tests/rename/should_compile/T4239.stdout | 2 +- testsuite/tests/rename/should_compile/all.T | 1 + .../check-api-annotations.cabal | 2 +- utils/check-ppr/check-ppr.cabal | 2 +- utils/ghc-cabal/ghc-cabal.cabal | 2 +- utils/ghctags/Main.hs | 2 +- utils/ghctags/ghctags.cabal | 2 +- 85 files changed, 277 insertions(+), 240 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 6353efc7694ba8ec86c091918e02595662169ae2 From git at git.haskell.org Thu Nov 22 21:54:13 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Nov 2018 21:54:13 +0000 (UTC) Subject: [commit: ghc] ghc-8.6: libiserv: Generate cabal file with autoconf (cbde272) Message-ID: <20181122215413.DC76A3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.6 Link : http://ghc.haskell.org/trac/ghc/changeset/cbde2726f10b8f4c19483bbb755ad42356098c51/ghc >--------------------------------------------------------------- commit cbde2726f10b8f4c19483bbb755ad42356098c51 Author: Ben Gamari Date: Tue Nov 6 10:33:01 2018 -0500 libiserv: Generate cabal file with autoconf Previously the version number was set by hand. This seems like unnecessary busywork for what is mostly an internal library. >--------------------------------------------------------------- cbde2726f10b8f4c19483bbb755ad42356098c51 configure.ac | 2 +- libraries/libiserv/{libiserv.cabal => libiserv.cabal.in} | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/configure.ac b/configure.ac index 2556561..f305ca9 100644 --- a/configure.ac +++ b/configure.ac @@ -1334,7 +1334,7 @@ checkMake380() { checkMake380 make checkMake380 gmake -AC_CONFIG_FILES([mk/config.mk mk/install.mk mk/project.mk rts/rts.cabal compiler/ghc.cabal ghc/ghc-bin.cabal utils/runghc/runghc.cabal utils/gen-dll/gen-dll.cabal libraries/ghc-boot/ghc-boot.cabal libraries/ghc-boot-th/ghc-boot-th.cabal libraries/ghci/ghci.cabal libraries/ghc-heap/ghc-heap.cabal settings docs/users_guide/ghc_config.py docs/index.html libraries/prologue.txt distrib/configure.ac]) +AC_CONFIG_FILES([mk/config.mk mk/install.mk mk/project.mk rts/rts.cabal compiler/ghc.cabal ghc/ghc-bin.cabal utils/runghc/runghc.cabal utils/gen-dll/gen-dll.cabal libraries/ghc-boot/ghc-boot.cabal libraries/ghc-boot-th/ghc-boot-th.cabal libraries/ghci/ghci.cabal libraries/ghc-heap/ghc-heap.cabal libraries/libiserv/libiserv.cabal settings docs/users_guide/ghc_config.py docs/index.html libraries/prologue.txt distrib/configure.ac]) AC_OUTPUT [ if test "$print_make_warning" = "true"; then diff --git a/libraries/libiserv/libiserv.cabal b/libraries/libiserv/libiserv.cabal.in similarity index 97% rename from libraries/libiserv/libiserv.cabal rename to libraries/libiserv/libiserv.cabal.in index fc0a022..84471a2 100644 --- a/libraries/libiserv/libiserv.cabal +++ b/libraries/libiserv/libiserv.cabal.in @@ -1,5 +1,5 @@ Name: libiserv -Version: 8.6.1 +Version: @ProjectVersionMunged@ Copyright: XXX License: BSD3 License-File: LICENSE From git at git.haskell.org Thu Nov 22 21:54:24 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Nov 2018 21:54:24 +0000 (UTC) Subject: [commit: ghc] ghc-8.6: distrib/configure: Set RanlibCmd (130b91d) Message-ID: <20181122215424.82C6E3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.6 Link : http://ghc.haskell.org/trac/ghc/changeset/130b91dbdca6ef3a82e2b178e04bda0a694a4ca4/ghc >--------------------------------------------------------------- commit 130b91dbdca6ef3a82e2b178e04bda0a694a4ca4 Author: Ben Gamari Date: Wed Nov 7 21:02:19 2018 -0500 distrib/configure: Set RanlibCmd This fixes #15875. >--------------------------------------------------------------- 130b91dbdca6ef3a82e2b178e04bda0a694a4ca4 distrib/configure.ac.in | 2 ++ 1 file changed, 2 insertions(+) diff --git a/distrib/configure.ac.in b/distrib/configure.ac.in index ed1c296..e064a5d 100644 --- a/distrib/configure.ac.in +++ b/distrib/configure.ac.in @@ -187,6 +187,8 @@ dnl ** how to invoke `ar' and `ranlib' # FP_PROG_AR_SUPPORTS_ATFILE FP_PROG_AR_NEEDS_RANLIB +RanlibCmd="$RANLIB" +AC_SUBST([RanlibCmd]) dnl ** Have libdw? dnl -------------------------------------------------------------- From git at git.haskell.org Thu Nov 22 21:54:35 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Nov 2018 21:54:35 +0000 (UTC) Subject: [commit: ghc] ghc-8.6: Fix heap corruption during stable name allocation (22cd729) Message-ID: <20181122215435.33B1C3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.6 Link : http://ghc.haskell.org/trac/ghc/changeset/22cd729abc4bcda999e3563759d8cb33160e6af6/ghc >--------------------------------------------------------------- commit 22cd729abc4bcda999e3563759d8cb33160e6af6 Author: Ömer Sinan Ağacan Date: Wed Nov 21 20:03:38 2018 +0300 Fix heap corruption during stable name allocation See #15906 for the problem. To fix we simply call `allocate()` instead of `ALLOC_PRIM()`. `allocate()` does not trigger GC when the nursery is full, instead it extends it. Test Plan: This validates. memo001 now passes with `-debug` compile parameter. I'll add another test that runs memo001 with `-debug` once I figure out how to use stdout files for multiple tests. Reviewers: simonmar, bgamari, erikd Reviewed By: simonmar Subscribers: rwbarton, carter GHC Trac Issues: #15906 Differential Revision: https://phabricator.haskell.org/D5342 (cherry picked from commit 691aa715cf43bf9d88ee32bca37e471bae35adfb) >--------------------------------------------------------------- 22cd729abc4bcda999e3563759d8cb33160e6af6 rts/PrimOps.cmm | 15 +++++++++++++-- 1 file changed, 13 insertions(+), 2 deletions(-) diff --git a/rts/PrimOps.cmm b/rts/PrimOps.cmm index 6081fab..cbb8e54 100644 --- a/rts/PrimOps.cmm +++ b/rts/PrimOps.cmm @@ -1848,14 +1848,25 @@ stg_makeStableNamezh ( P_ obj ) { W_ index, sn_obj; + MAYBE_GC_P(stg_makeStableNamezh, obj); + (index) = ccall lookupStableName(obj "ptr"); /* Is there already a StableName for this heap object? * stable_name_table is a pointer to an array of snEntry structs. */ if ( snEntry_sn_obj(W_[stable_name_table] + index*SIZEOF_snEntry) == NULL ) { - ALLOC_PRIM (SIZEOF_StgStableName); - sn_obj = Hp - SIZEOF_StgStableName + WDS(1); + // At this point we have a snEntry, but it doesn't look as used to the + // GC yet because we don't have a StableName object for the sn_obj field + // (remember that sn_obj == NULL means the entry is free). So if we call + // GC here we end up skipping the snEntry in gcStableNameTable(). This + // caused #15906. Solution: use allocate(), which does not call GC. + // + // (Alternatively we could use a special value for the sn_obj field to + // indicate that the entry is being allocated and not free, but that's + // too complicated and doesn't buy us much. See D5342?id=18700.) + ("ptr" sn_obj) = ccall allocate(MyCapability() "ptr", + BYTES_TO_WDS(SIZEOF_StgStableName)); SET_HDR(sn_obj, stg_STABLE_NAME_info, CCCS); StgStableName_sn(sn_obj) = index; snEntry_sn_obj(W_[stable_name_table] + index*SIZEOF_snEntry) = sn_obj; From git at git.haskell.org Thu Nov 22 21:54:46 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Nov 2018 21:54:46 +0000 (UTC) Subject: [commit: ghc] ghc-8.6: users guide: We no longer build libraries with -split-objs (14ae4ab) Message-ID: <20181122215446.08E843A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.6 Link : http://ghc.haskell.org/trac/ghc/changeset/14ae4ab6d2ffc907ffe0a438acc51c614b72140e/ghc >--------------------------------------------------------------- commit 14ae4ab6d2ffc907ffe0a438acc51c614b72140e Author: Ben Gamari Date: Wed Nov 21 19:17:41 2018 -0500 users guide: We no longer build libraries with -split-objs We now generally use split-sections instead. (cherry picked from commit f5fbecc85967218fd8ba6512f10eea2daf2812ac) >--------------------------------------------------------------- 14ae4ab6d2ffc907ffe0a438acc51c614b72140e docs/users_guide/phases.rst | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/docs/users_guide/phases.rst b/docs/users_guide/phases.rst index 27948e7..48cd3e7 100644 --- a/docs/users_guide/phases.rst +++ b/docs/users_guide/phases.rst @@ -745,7 +745,7 @@ for example). However, assembling all the sections separately is expensive, so this is slower than compiling normally. Additionally, the size of the library itself (the ``.a`` file) can be a factor of 2 to 2.5 - larger. We use this feature for building GHC's libraries. + larger. .. ghc-flag:: -split-sections :shortdesc: Split sections for link-time dead-code stripping From git at git.haskell.org Thu Nov 22 21:54:56 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Nov 2018 21:54:56 +0000 (UTC) Subject: [commit: ghc] ghc-8.6: rts/M32Alloc: Abort if m32 linker mmap fails (c8b24dc) Message-ID: <20181122215456.853D73A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.6 Link : http://ghc.haskell.org/trac/ghc/changeset/c8b24dce7bba394ca60c8eba04c5bed7a7e9534e/ghc >--------------------------------------------------------------- commit c8b24dce7bba394ca60c8eba04c5bed7a7e9534e Author: Ben Gamari Date: Sat Nov 10 15:35:37 2018 -0500 rts/M32Alloc: Abort if m32 linker mmap fails Previously we should just blinding dereference a NULL pointer. (cherry picked from commit 86f6890e3689f2f75ecca8172eda0338fe3e9769) >--------------------------------------------------------------- c8b24dce7bba394ca60c8eba04c5bed7a7e9534e rts/linker/M32Alloc.c | 3 +++ 1 file changed, 3 insertions(+) diff --git a/rts/linker/M32Alloc.c b/rts/linker/M32Alloc.c index 6a2996d..52b182e 100644 --- a/rts/linker/M32Alloc.c +++ b/rts/linker/M32Alloc.c @@ -158,6 +158,9 @@ m32_allocator_init(void) // fragment the memory. size_t pgsz = getPageSize(); char* bigchunk = mmapForLinker(pgsz * M32_MAX_PAGES,MAP_ANONYMOUS,-1,0); + if (bigchunk == NULL) + barf("m32_allocator_init: Failed to map"); + int i; for (i=0; i Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.6 Link : http://ghc.haskell.org/trac/ghc/changeset/e67bebbf735db498c2cbf191d1878644ca5ed5cc/ghc >--------------------------------------------------------------- commit e67bebbf735db498c2cbf191d1878644ca5ed5cc Author: Christiaan Baaij Date: Thu Nov 22 11:50:51 2018 -0500 Load plugins in interactive session Reviewers: bgamari, tdammers Reviewed By: tdammers Subscribers: monoidal, rwbarton, carter GHC Trac Issues: #15633 Differential Revision: https://phabricator.haskell.org/D5348 (cherry picked from commit 599eaada382d04722219bfc319bde94591be3fb1) >--------------------------------------------------------------- e67bebbf735db498c2cbf191d1878644ca5ed5cc ghc/GHCi/UI.hs | 8 +++++++- ghc/Main.hs | 17 ++++++++++++----- testsuite/tests/ghci/should_run/T15633a.script | 1 + testsuite/tests/ghci/should_run/T15633a.stderr | 1 + testsuite/tests/ghci/should_run/T15633a.stdout | 1 + testsuite/tests/ghci/should_run/T15633b.script | 2 ++ testsuite/tests/ghci/should_run/T15633b.stderr | 1 + testsuite/tests/ghci/should_run/T15633b.stdout | 1 + testsuite/tests/ghci/should_run/all.T | 18 ++++++++++++++++++ .../should_run/tc-plugin-ghci}/LICENSE | 0 .../should_run/tc-plugin-ghci}/Makefile | 0 .../should_run/tc-plugin-ghci}/Setup.hs | 0 .../should_run/tc-plugin-ghci/TcPluginGHCi.hs} | 5 +++-- .../should_run/tc-plugin-ghci/tc-plugin-ghci.cabal} | 9 +++------ 14 files changed, 50 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 e67bebbf735db498c2cbf191d1878644ca5ed5cc From git at git.haskell.org Thu Nov 22 21:55:21 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Nov 2018 21:55:21 +0000 (UTC) Subject: [commit: ghc] ghc-8.6: Fix a bug in SRT generation (#15892) (4519d98) Message-ID: <20181122215521.C21873A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.6 Link : http://ghc.haskell.org/trac/ghc/changeset/4519d98d5399c2a958b2592b0ab50d89980d48b5/ghc >--------------------------------------------------------------- commit 4519d98d5399c2a958b2592b0ab50d89980d48b5 Author: Simon Marlow Date: Thu Nov 15 06:31:35 2018 +0300 Fix a bug in SRT generation (#15892) Summary: The logic in `Note [recursive SRTs]` was correct. However, my implementation of it wasn't: I got the associativity of `Set.difference` wrong, which led to an extremely subtle and difficult to find bug. Fortunately now we have a test case. I was able to cut down the code to something manageable, and I've added it to the test suite. Test Plan: Before (using my stage 1 compiler without the fix): ``` ====> T15892(normal) 1 of 1 [0, 0, 0] cd "T15892.run" && "/home/smarlow/ghc/inplace/bin/ghc-stage1" -o T15892 T15892.hs -dcore-lint -dcmm-lint -no-user-package-db -rtsopts -fno-warn-missed-specialisations -fshow-warning-groups -fdiagnostics-color=never -fno-diagnostics-show-caret -Werror=compat -dno-debug-output -O cd "T15892.run" && ./T15892 +RTS -G1 -A32k -RTS Wrong exit code for T15892(normal)(expected 0 , actual 134 ) Stderr ( T15892 ): T15892: internal error: evacuate: strange closure type 0 (GHC version 8.7.20181113 for x86_64_unknown_linux) Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug Aborted (core dumped) *** unexpected failure for T15892(normal) =====> T15892(g1) 1 of 1 [0, 1, 0] cd "T15892.run" && "/home/smarlow/ghc/inplace/bin/ghc-stage1" -o T15892 T15892.hs -dcore-lint -dcmm-lint -no-user-package-db -rtsopts -fno-warn-missed-specialisations -fshow-warning-groups -fdiagnostics-color=never -fno-diagnostics-show-caret -Werror=compat -dno-debug-output -O cd "T15892.run" && ./T15892 +RTS -G1 -RTS +RTS -G1 -A32k -RTS Wrong exit code for T15892(g1)(expected 0 , actual 134 ) Stderr ( T15892 ): T15892: internal error: evacuate: strange closure type 0 (GHC version 8.7.20181113 for x86_64_unknown_linux) Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug Aborted (core dumped) ``` After (using my stage 2 compiler with the fix): ``` =====> T15892(normal) 1 of 1 [0, 0, 0] cd "T15892.run" && "/home/smarlow/ghc/inplace/test spaces/ghc-stage2" -o T15892 T15892.hs -dcore-lint -dcmm-lint -no-user-package-db -rtsopts -fno-warn-missed-specialisations -fshow-warning-groups -fdiagnostics-color=never -fno-diagnostics-show-caret -Werror=compat -dno-debug-output cd "T15892.run" && ./T15892 +RTS -G1 -A32k -RTS =====> T15892(g1) 1 of 1 [0, 0, 0] cd "T15892.run" && "/home/smarlow/ghc/inplace/test spaces/ghc-stage2" -o T15892 T15892.hs -dcore-lint -dcmm-lint -no-user-package-db -rtsopts -fno-warn-missed-specialisations -fshow-warning-groups -fdiagnostics-color=never -fno-diagnostics-show-caret -Werror=compat -dno-debug-output cd "T15892.run" && ./T15892 +RTS -G1 -RTS +RTS -G1 -A32k -RTS ``` Reviewers: bgamari, osa1, erikd Reviewed By: osa1 Subscribers: rwbarton, carter GHC Trac Issues: #15892 Differential Revision: https://phabricator.haskell.org/D5334 >--------------------------------------------------------------- 4519d98d5399c2a958b2592b0ab50d89980d48b5 compiler/cmm/CmmBuildInfoTables.hs | 2 +- testsuite/tests/codeGen/should_run/T15892.hs | 67 ++++++++++++++++++++++++++++ testsuite/tests/codeGen/should_run/all.T | 7 +++ 3 files changed, 75 insertions(+), 1 deletion(-) diff --git a/compiler/cmm/CmmBuildInfoTables.hs b/compiler/cmm/CmmBuildInfoTables.hs index a8f89a1..be96fba 100644 --- a/compiler/cmm/CmmBuildInfoTables.hs +++ b/compiler/cmm/CmmBuildInfoTables.hs @@ -703,7 +703,7 @@ oneSRT dflags staticFuns blockids lbls isCAF cafs = do -- Remove recursive references from the SRT, except for (all but -- one of the) static functions. See Note [recursive SRTs]. nonRec = cafs `Set.difference` - Set.fromList lbls `Set.difference` Set.fromList otherFunLabels + (Set.fromList lbls `Set.difference` Set.fromList otherFunLabels) -- First resolve all the CAFLabels to SRTEntries -- Implements the [Inline] optimisation. diff --git a/testsuite/tests/codeGen/should_run/T15892.hs b/testsuite/tests/codeGen/should_run/T15892.hs new file mode 100644 index 0000000..d132943 --- /dev/null +++ b/testsuite/tests/codeGen/should_run/T15892.hs @@ -0,0 +1,67 @@ +{-# LANGUAGE RankNTypes #-} +{-# LANGUAGE BangPatterns #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE MagicHash, UnboxedTuples #-} + +module Main (enumFromCallbackCatch, consume, next, main) where + +import Control.Monad +import Foreign +import GHC.ForeignPtr +import GHC.Base (realWorld#) +import Data.Word (Word8) +import Foreign.Storable (peek) +import GHC.IO + +data ByteString = PS {-# UNPACK #-} !(ForeignPtr Word8) {-# UNPACK #-} !Int + +instance Show ByteString where + showsPrec p ps r = showsPrec p (unpackAppendCharsStrict ps []) r + +unpackAppendCharsStrict :: ByteString -> [Char] -> [Char] +unpackAppendCharsStrict (PS fp len) xs = + unsafeDupablePerformIO $ withForeignPtr fp $ \base -> + loop (base `plusPtr` (-1)) (base `plusPtr` 960) xs + where + loop !sentinal !p acc + | p == sentinal = return acc + | otherwise = do x <- peek p + loop sentinal (p `plusPtr` (-1)) (w2c x:acc) + +w2c :: Word8 -> Char +w2c = toEnum . fromEnum + +packCStringLen :: Int -> IO ByteString +packCStringLen l = do + p <- callocBytes bufsize + fp <- newForeignPtr finalizerFree p + return $! PS fp l +{-# NOINLINE packCStringLen #-} + +bufsize :: Int +bufsize = 8192 + +{-# NOINLINE readFromPtr #-} +readFromPtr :: IO ByteString +readFromPtr = do + bs <- packCStringLen bufsize + length (show bs) `seq` return bs + +newtype Iteratee s = Iteratee { runIter :: forall r. + ((s -> Iteratee s) -> IO r) -> + IO r} + +enumFromCallbackCatch :: IO () +enumFromCallbackCatch = produce 500 consume + where + produce 0 (Iteratee f) = return () + produce n (Iteratee f) = f onCont + where onCont k = do bs <- readFromPtr; produce (n-1) (k bs) + +consume = Iteratee $ \onCont -> onCont next +next x = Iteratee $ \onCont -> print x >> onCont (\_ -> consume) + +main :: IO () +main = do + _ <- enumFromCallbackCatch + pure () diff --git a/testsuite/tests/codeGen/should_run/all.T b/testsuite/tests/codeGen/should_run/all.T index 3935574..1dec2a6 100644 --- a/testsuite/tests/codeGen/should_run/all.T +++ b/testsuite/tests/codeGen/should_run/all.T @@ -181,3 +181,10 @@ test('T15696_1', normal, compile_and_run, ['-O']) test('T15696_2', normal, compile_and_run, ['-O']) # This requires -O test('T15696_3', normal, compile_and_run, ['-O']) + +test('T15892', + [ ignore_stdout, + # we want to do lots of major GC to make the bug more likely to + # happen, so -G1 -A32k: + extra_run_opts('+RTS -G1 -A32k -RTS') ], + compile_and_run, ['-O']) From git at git.haskell.org Thu Nov 22 21:55:35 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Nov 2018 21:55:35 +0000 (UTC) Subject: [commit: ghc] ghc-8.6: circleci: Actually build with in-tree GMP on Darwin (b6d2d83) Message-ID: <20181122215535.708FC3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.6 Link : http://ghc.haskell.org/trac/ghc/changeset/b6d2d8375e4c1425690e26d1f6bc1578f7ed1043/ghc >--------------------------------------------------------------- commit b6d2d8375e4c1425690e26d1f6bc1578f7ed1043 Author: Dario Bertini Date: Fri Nov 16 10:25:32 2018 +0100 circleci: Actually build with in-tree GMP on Darwin Fixes #15404. (cherry picked from commit 3584bd4255eb59be043252c9b4ef16bcbd835c9b) >--------------------------------------------------------------- b6d2d8375e4c1425690e26d1f6bc1578f7ed1043 .circleci/config.yml | 4 +--- .circleci/prepare-system.sh | 1 + 2 files changed, 2 insertions(+), 3 deletions(-) diff --git a/.circleci/config.yml b/.circleci/config.yml index 4414357..6dcb218 100644 --- a/.circleci/config.yml +++ b/.circleci/config.yml @@ -33,7 +33,7 @@ aliases: - &configure_unix run: name: Configure - command: ./configure $CONFIGURE_OPTS + command: ./configure - &configure_unix_32 run: name: Configure @@ -140,8 +140,6 @@ jobs: # Only Sierra and onwards supports clock_gettime. See #12858 ac_cv_func_clock_gettime: "no" GHC_COLLECTOR_FLAVOR: x86_64-darwin - # Build with in-tree GMP since this isn't available on OS X by default. - CONFIGURE_OPTS: --with-intree-gmp <<: *buildenv steps: - checkout diff --git a/.circleci/prepare-system.sh b/.circleci/prepare-system.sh index 636b792..7d8cac6 100755 --- a/.circleci/prepare-system.sh +++ b/.circleci/prepare-system.sh @@ -69,6 +69,7 @@ case "$(uname)" in ln -s $HOME/.cabal/bin/alex /usr/local/bin/alex || true ln -s $HOME/.cabal/bin/happy /usr/local/bin/happy || true ln -s $HOME/.cabal/bin/HsColour /usr/local/bin/HsColour || true + echo "libraries/integer-gmp_CONFIGURE_OPTS += --configure-option=--with-intree-gmp" >> mk/build.mk ;; *) fail "uname=$(uname) not supported" From git at git.haskell.org Thu Nov 22 21:55:46 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Nov 2018 21:55:46 +0000 (UTC) Subject: [commit: ghc] ghc-8.6: rts/MachO: Add a bit more debugging output to getNames (65ced24) Message-ID: <20181122215546.66DBA3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.6 Link : http://ghc.haskell.org/trac/ghc/changeset/65ced246a0e0b1387a998cc70f4476be06bf67c3/ghc >--------------------------------------------------------------- commit 65ced246a0e0b1387a998cc70f4476be06bf67c3 Author: Dario Bertini Date: Fri Nov 16 15:46:54 2018 +0100 rts/MachO: Add a bit more debugging output to getNames (cherry picked from commit 9e0a23b95c285c4019fd2d36102374ee582f1dcb) >--------------------------------------------------------------- 65ced246a0e0b1387a998cc70f4476be06bf67c3 rts/linker/MachO.c | 11 +++++++---- 1 file changed, 7 insertions(+), 4 deletions(-) diff --git a/rts/linker/MachO.c b/rts/linker/MachO.c index 5812e89..70acb16 100644 --- a/rts/linker/MachO.c +++ b/rts/linker/MachO.c @@ -1612,14 +1612,17 @@ ocGetNames_MachO(ObjectCode* oc) "ocGetNames_MachO(oc->symbols)"); if (oc->info->symCmd) { + debugBelch("ocGetNames_MachO: %d macho symbols\n", oc->info->n_macho_symbols); for (size_t i = 0; i < oc->info->n_macho_symbols; i++) { + SymbolName* nm = oc->info->macho_symbols[i].name; if(oc->info->nlist[i].n_type & N_STAB) - ; + { + IF_DEBUG(linker, debugBelch("ocGetNames_MachO: Skip STAB: %s\n", nm)); + } else if((oc->info->nlist[i].n_type & N_TYPE) == N_SECT) { if(oc->info->nlist[i].n_type & N_EXT) { - SymbolName* nm = oc->info->macho_symbols[i].name; if ( (oc->info->nlist[i].n_desc & N_WEAK_DEF) && lookupSymbol_(nm)) { // weak definition, and we already have a definition @@ -1643,12 +1646,12 @@ ocGetNames_MachO(ObjectCode* oc) } else { - IF_DEBUG(linker, debugBelch("ocGetNames_MachO: \t...not external, skipping\n")); + IF_DEBUG(linker, debugBelch("ocGetNames_MachO: \t...not external, skipping %s\n", nm)); } } else { - IF_DEBUG(linker, debugBelch("ocGetNames_MachO: \t...not defined in this section, skipping\n")); + IF_DEBUG(linker, debugBelch("ocGetNames_MachO: \t...not defined in this section, skipping %s\n", nm)); } } } From git at git.haskell.org Thu Nov 22 21:55:57 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Nov 2018 21:55:57 +0000 (UTC) Subject: [commit: ghc] ghc-8.6: rts/MachO: A bit of refactoring in ocGetNames (b44caa0) Message-ID: <20181122215557.476BC3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.6 Link : http://ghc.haskell.org/trac/ghc/changeset/b44caa05ad949519431059b07370615c0f513c9c/ghc >--------------------------------------------------------------- commit b44caa05ad949519431059b07370615c0f513c9c Author: Dario Bertini Date: Fri Nov 16 15:48:36 2018 +0100 rts/MachO: A bit of refactoring in ocGetNames Eliminates a bit of repetition. (cherry picked from commit b2f6f896a0bae0e68ec629bd6817a2cb2533a12c) >--------------------------------------------------------------- b44caa05ad949519431059b07370615c0f513c9c rts/linker/MachO.c | 15 +++++++-------- 1 file changed, 7 insertions(+), 8 deletions(-) diff --git a/rts/linker/MachO.c b/rts/linker/MachO.c index 70acb16..b5caa7b 100644 --- a/rts/linker/MachO.c +++ b/rts/linker/MachO.c @@ -1612,7 +1612,6 @@ ocGetNames_MachO(ObjectCode* oc) "ocGetNames_MachO(oc->symbols)"); if (oc->info->symCmd) { - debugBelch("ocGetNames_MachO: %d macho symbols\n", oc->info->n_macho_symbols); for (size_t i = 0; i < oc->info->n_macho_symbols; i++) { SymbolName* nm = oc->info->macho_symbols[i].name; if(oc->info->nlist[i].n_type & N_STAB) @@ -1662,14 +1661,14 @@ ocGetNames_MachO(ObjectCode* oc) if (oc->info->symCmd) { for (int i = 0; i < oc->n_symbols; i++) { - if((oc->info->nlist[i].n_type & N_TYPE) == N_UNDF - && (oc->info->nlist[i].n_type & N_EXT) - && (oc->info->nlist[i].n_value != 0)) { - - SymbolName* nm = oc->info->macho_symbols[i].name; - unsigned long sz = oc->info->nlist[i].n_value; + SymbolName* nm = oc->info->macho_symbols[i].name; + MachONList *nlist = &oc->info->nlist[i]; + if((nlist->n_type & N_TYPE) == N_UNDF + && (nlist->n_type & N_EXT) + && (nlist->n_value != 0)) { + unsigned long sz = nlist->n_value; - oc->info->nlist[i].n_value = commonCounter; + nlist->n_value = commonCounter; /* also set the final address to the macho_symbol */ oc->info->macho_symbols[i].addr = (void*)commonCounter; From git at git.haskell.org Thu Nov 22 21:56:10 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Nov 2018 21:56:10 +0000 (UTC) Subject: [commit: ghc] ghc-8.6: rts/MachO: Iterate through N (all) symbols, not M external symbols (11fd7df) Message-ID: <20181122215610.5021F3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.6 Link : http://ghc.haskell.org/trac/ghc/changeset/11fd7df565897fb98cda9273dab28ccc654a6d95/ghc >--------------------------------------------------------------- commit 11fd7df565897fb98cda9273dab28ccc654a6d95 Author: Dario Bertini Date: Fri Nov 16 15:49:37 2018 +0100 rts/MachO: Iterate through N (all) symbols, not M external symbols Fixes #15105 (cherry picked from commit 254890855ee04762cc0392da19e0c42fc039a718) >--------------------------------------------------------------- 11fd7df565897fb98cda9273dab28ccc654a6d95 rts/linker/MachO.c | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/rts/linker/MachO.c b/rts/linker/MachO.c index b5caa7b..053a45d 100644 --- a/rts/linker/MachO.c +++ b/rts/linker/MachO.c @@ -1660,7 +1660,7 @@ ocGetNames_MachO(ObjectCode* oc) commonCounter = (unsigned long)commonStorage; if (oc->info->symCmd) { - for (int i = 0; i < oc->n_symbols; i++) { + for (size_t i = 0; i < oc->info->n_macho_symbols; i++) { SymbolName* nm = oc->info->macho_symbols[i].name; MachONList *nlist = &oc->info->nlist[i]; if((nlist->n_type & N_TYPE) == N_UNDF From git at git.haskell.org Thu Nov 22 22:05:06 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Nov 2018 22:05:06 +0000 (UTC) Subject: [commit: ghc] ghc-8.6: Revert "libiserv: Generate cabal file with autoconf" (c2c6f49) Message-ID: <20181122220506.CAD213A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.6 Link : http://ghc.haskell.org/trac/ghc/changeset/c2c6f49845698275c1e83f0c93b9c4b558c7ba08/ghc >--------------------------------------------------------------- commit c2c6f49845698275c1e83f0c93b9c4b558c7ba08 Author: Ben Gamari Date: Thu Nov 22 16:59:14 2018 -0500 Revert "libiserv: Generate cabal file with autoconf" This reverts commit cbde2726f10b8f4c19483bbb755ad42356098c51. >--------------------------------------------------------------- c2c6f49845698275c1e83f0c93b9c4b558c7ba08 configure.ac | 2 +- libraries/libiserv/{libiserv.cabal.in => libiserv.cabal} | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/configure.ac b/configure.ac index f305ca9..2556561 100644 --- a/configure.ac +++ b/configure.ac @@ -1334,7 +1334,7 @@ checkMake380() { checkMake380 make checkMake380 gmake -AC_CONFIG_FILES([mk/config.mk mk/install.mk mk/project.mk rts/rts.cabal compiler/ghc.cabal ghc/ghc-bin.cabal utils/runghc/runghc.cabal utils/gen-dll/gen-dll.cabal libraries/ghc-boot/ghc-boot.cabal libraries/ghc-boot-th/ghc-boot-th.cabal libraries/ghci/ghci.cabal libraries/ghc-heap/ghc-heap.cabal libraries/libiserv/libiserv.cabal settings docs/users_guide/ghc_config.py docs/index.html libraries/prologue.txt distrib/configure.ac]) +AC_CONFIG_FILES([mk/config.mk mk/install.mk mk/project.mk rts/rts.cabal compiler/ghc.cabal ghc/ghc-bin.cabal utils/runghc/runghc.cabal utils/gen-dll/gen-dll.cabal libraries/ghc-boot/ghc-boot.cabal libraries/ghc-boot-th/ghc-boot-th.cabal libraries/ghci/ghci.cabal libraries/ghc-heap/ghc-heap.cabal settings docs/users_guide/ghc_config.py docs/index.html libraries/prologue.txt distrib/configure.ac]) AC_OUTPUT [ if test "$print_make_warning" = "true"; then diff --git a/libraries/libiserv/libiserv.cabal.in b/libraries/libiserv/libiserv.cabal similarity index 97% rename from libraries/libiserv/libiserv.cabal.in rename to libraries/libiserv/libiserv.cabal index 84471a2..fc0a022 100644 --- a/libraries/libiserv/libiserv.cabal.in +++ b/libraries/libiserv/libiserv.cabal @@ -1,5 +1,5 @@ Name: libiserv -Version: @ProjectVersionMunged@ +Version: 8.6.1 Copyright: XXX License: BSD3 License-File: LICENSE From git at git.haskell.org Thu Nov 22 22:05:17 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Nov 2018 22:05:17 +0000 (UTC) Subject: [commit: ghc] ghc-8.6: base: Mention openFile throwing does-not-exist-errors on FIFOs (64a5044) Message-ID: <20181122220517.BD2143A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.6 Link : http://ghc.haskell.org/trac/ghc/changeset/64a5044543bdcd7983787b215a44bdfb70c9c40b/ghc >--------------------------------------------------------------- commit 64a5044543bdcd7983787b215a44bdfb70c9c40b Author: Ben Gamari Date: Thu Nov 22 11:33:39 2018 -0500 base: Mention openFile throwing does-not-exist-errors on FIFOs As discussed in #15715, the POSIX specification specifies that attempting to open a FIFO in write-only mode when the FIFO has no readers will fail with -ENOENT. [skip ci] Test Plan: Read it Reviewers: hvr Subscribers: rwbarton, carter GHC Trac Issues: #15715 Differential Revision: https://phabricator.haskell.org/D5295 (cherry picked from commit 4ba3fa31ddfa12b428bd67216a2d4118dc9e8311) >--------------------------------------------------------------- 64a5044543bdcd7983787b215a44bdfb70c9c40b libraries/base/GHC/IO/Handle/FD.hs | 6 ++++-- 1 file changed, 4 insertions(+), 2 deletions(-) diff --git a/libraries/base/GHC/IO/Handle/FD.hs b/libraries/base/GHC/IO/Handle/FD.hs index 786fccc..f7f8d04 100644 --- a/libraries/base/GHC/IO/Handle/FD.hs +++ b/libraries/base/GHC/IO/Handle/FD.hs @@ -130,7 +130,9 @@ addFilePathToIOError fun fp ioe -- -- * 'isAlreadyInUseError' if the file is already open and cannot be reopened; -- --- * 'isDoesNotExistError' if the file does not exist; or +-- * 'isDoesNotExistError' if the file does not exist or +-- (on POSIX systems) is a FIFO without a reader and 'WriteMode' was +-- requested; or -- -- * 'isPermissionError' if the user does not have permission to open the file. -- @@ -161,7 +163,7 @@ openFileBlocking fp im = -- this is undesirable; also, as usual under Microsoft operating systems, -- text mode treats control-Z as EOF. Binary mode turns off all special -- treatment of end-of-line and end-of-file characters. --- (See also 'hSetBinaryMode'.) +-- (See also 'System.IO.hSetBinaryMode'.) openBinaryFile :: FilePath -> IOMode -> IO Handle openBinaryFile fp m = From git at git.haskell.org Thu Nov 22 22:05:29 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 22 Nov 2018 22:05:29 +0000 (UTC) Subject: [commit: ghc] ghc-8.6: Fix #15859 by checking, not assuming, an ArgFlag (2594ea2) Message-ID: <20181122220529.6F42A3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : ghc-8.6 Link : http://ghc.haskell.org/trac/ghc/changeset/2594ea25641e4b27327449d40c5dd2d46d837af1/ghc >--------------------------------------------------------------- commit 2594ea25641e4b27327449d40c5dd2d46d837af1 Author: Richard Eisenberg Date: Mon Nov 5 11:01:47 2018 -0500 Fix #15859 by checking, not assuming, an ArgFlag We thought that visible dependent quantification was impossible in terms, but Iceland Jack discovered otherwise in #15859. This fixes an ASSERT failure that arose. test case: dependent/should_fail/T15859 (cherry picked from commit 72b82343b79365dc74ffafb345dd33499a7fd394) (cherry picked from commit 5693ddd071033516a1804420a903cb7e3677682b) >--------------------------------------------------------------- 2594ea25641e4b27327449d40c5dd2d46d837af1 compiler/typecheck/TcExpr.hs | 10 ++++------ testsuite/tests/dependent/should_fail/T15859.hs | 13 +++++++++++++ testsuite/tests/dependent/should_fail/T15859.stderr | 6 ++++++ testsuite/tests/dependent/should_fail/all.T | 1 + 4 files changed, 24 insertions(+), 6 deletions(-) diff --git a/compiler/typecheck/TcExpr.hs b/compiler/typecheck/TcExpr.hs index 4751a20..8557af2 100644 --- a/compiler/typecheck/TcExpr.hs +++ b/compiler/typecheck/TcExpr.hs @@ -1330,14 +1330,12 @@ tcArgs fun orig_fun_ty fun_orig orig_args herald = do { (wrap1, upsilon_ty) <- topInstantiateInferred fun_orig fun_ty -- wrap1 :: fun_ty "->" upsilon_ty ; case tcSplitForAllTy_maybe upsilon_ty of - Just (tvb, inner_ty) -> + Just (tvb, inner_ty) + | binderArgFlag tvb == Specified -> + -- It really can't be Inferred, because we've just instantiated those + -- But, oddly, it might just be Required. See #15859. do { let tv = binderVar tvb - vis = binderArgFlag tvb kind = tyVarKind tv - ; MASSERT2( vis == Specified - , (vcat [ ppr fun_ty, ppr upsilon_ty, ppr tvb - , ppr inner_ty, pprTyVar tv - , ppr vis ]) ) ; ty_arg <- tcHsTypeApp hs_ty_arg kind ; inner_ty <- zonkTcType inner_ty diff --git a/testsuite/tests/dependent/should_fail/T15859.hs b/testsuite/tests/dependent/should_fail/T15859.hs new file mode 100644 index 0000000..e8ffdf4 --- /dev/null +++ b/testsuite/tests/dependent/should_fail/T15859.hs @@ -0,0 +1,13 @@ +{-# Language PolyKinds #-} +{-# Language TypeApplications #-} +{-# Language ImpredicativeTypes #-} + +module T15859 where + +import Data.Kind + +data A k :: k -> Type + +type KindOf (a :: k) = k + +a = (undefined :: KindOf A) @Int diff --git a/testsuite/tests/dependent/should_fail/T15859.stderr b/testsuite/tests/dependent/should_fail/T15859.stderr new file mode 100644 index 0000000..e479404 --- /dev/null +++ b/testsuite/tests/dependent/should_fail/T15859.stderr @@ -0,0 +1,6 @@ + +T15859.hs:13:5: error: + • Cannot apply expression of type ‘forall k -> k -> *’ + to a visible type argument ‘Int’ + • In the expression: (undefined :: KindOf A) @Int + In an equation for ‘a’: a = (undefined :: KindOf A) @Int diff --git a/testsuite/tests/dependent/should_fail/all.T b/testsuite/tests/dependent/should_fail/all.T index 593b778..d006175 100644 --- a/testsuite/tests/dependent/should_fail/all.T +++ b/testsuite/tests/dependent/should_fail/all.T @@ -35,3 +35,4 @@ test('T15215', normal, compile_fail, ['']) test('T15308', normal, compile_fail, ['-fno-print-explicit-kinds']) test('T15343', normal, compile_fail, ['']) test('T15380', normal, compile_fail, ['']) +test('T15859', normal, compile_fail, ['']) From git at git.haskell.org Fri Nov 23 08:32:57 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Nov 2018 08:32:57 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Wibbles to checkConsistentFamInst (099edbe) Message-ID: <20181123083257.88CDD3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/099edbed1ce23e4067cda0be72c19458a1816c08/ghc >--------------------------------------------------------------- commit 099edbed1ce23e4067cda0be72c19458a1816c08 Author: Simon Peyton Jones Date: Fri Nov 23 08:31:22 2018 +0000 Wibbles to checkConsistentFamInst >--------------------------------------------------------------- 099edbed1ce23e4067cda0be72c19458a1816c08 compiler/typecheck/TcInstDcls.hs | 27 +++++++++-------- compiler/typecheck/TcTyClsDecls.hs | 62 +++++++++++++++++++++++++------------- 2 files changed, 55 insertions(+), 34 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 099edbed1ce23e4067cda0be72c19458a1816c08 From git at git.haskell.org Fri Nov 23 09:12:56 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Nov 2018 09:12:56 +0000 (UTC) Subject: [commit: ghc] master: Use handy shortcut llvm_ways (9b0d033) Message-ID: <20181123091256.4CCAC3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9b0d03331b8ef0abaef609a22dcd221f8e91b759/ghc >--------------------------------------------------------------- commit 9b0d03331b8ef0abaef609a22dcd221f8e91b759 Author: Gabor Greif Date: Fri Nov 23 10:09:57 2018 +0100 Use handy shortcut llvm_ways >--------------------------------------------------------------- 9b0d03331b8ef0abaef609a22dcd221f8e91b759 testsuite/tests/codeGen/should_compile/all.T | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/testsuite/tests/codeGen/should_compile/all.T b/testsuite/tests/codeGen/should_compile/all.T index f8e2fb0..7a5e103 100644 --- a/testsuite/tests/codeGen/should_compile/all.T +++ b/testsuite/tests/codeGen/should_compile/all.T @@ -14,12 +14,12 @@ test('T3286', [], multimod_compile, ['T3286', '-v0']) test('T3579', normal, compile, ['']) test('T2578', normal, run_command, ['$MAKE -s --no-print-directory T2578']) # skip llvm on i386 as we don't support fPIC -test('jmp_tbl', when(arch('i386'), omit_ways(['llvm', 'optllvm'])), compile, ['-fPIC -O']) +test('jmp_tbl', when(arch('i386'), omit_ways(llvm_ways)), compile, ['-fPIC -O']) test('massive_array', - [ when(arch('i386'), omit_ways(['llvm', 'optllvm'])) ], + [ when(arch('i386'), omit_ways(llvm_ways)) ], compile, ['-fPIC']) test('T7237', normal, compile, ['']) -test('T7574', [cmm_src, omit_ways(['llvm', 'optllvm'])], compile, ['']) +test('T7574', [cmm_src, omit_ways(llvm_ways)], compile, ['']) test('T8205', normal, compile, ['-O0']) test('T9155', normal, compile, ['-O2']) test('T9303', normal, compile, ['-O2']) From git at git.haskell.org Fri Nov 23 11:11:14 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Nov 2018 11:11:14 +0000 (UTC) Subject: [commit: ghc] master: Typofix in help text (7856676) Message-ID: <20181123111114.8BC323A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7856676b72526cd674e84c43064b61ff3a07a0a1/ghc >--------------------------------------------------------------- commit 7856676b72526cd674e84c43064b61ff3a07a0a1 Author: Gabor Greif Date: Fri Nov 23 12:02:49 2018 +0100 Typofix in help text >--------------------------------------------------------------- 7856676b72526cd674e84c43064b61ff3a07a0a1 hadrian/src/CommandLine.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/hadrian/src/CommandLine.hs b/hadrian/src/CommandLine.hs index 1532ec5..36f3818 100644 --- a/hadrian/src/CommandLine.hs +++ b/hadrian/src/CommandLine.hs @@ -198,7 +198,7 @@ optDescrs = , Option [] ["test-compiler"] (OptArg readTestCompiler "TEST_COMPILER") "Use given compiler [Default=stage2]." , Option [] ["test-config-file"] (OptArg readTestConfigFile "CONFIG_FILE") - "congiguration file for testsuite. Default=testsuite/config/ghc" + "configuration file for testsuite. Default=testsuite/config/ghc" , Option [] ["config"] (OptArg readTestConfig "EXTRA_TEST_CONFIG") "Configurations to run test, in key=value format." , Option [] ["summary-junit"] (OptArg readTestJUnit "TEST_SUMMARY_JUNIT") From git at git.haskell.org Fri Nov 23 15:26:58 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Nov 2018 15:26:58 +0000 (UTC) Subject: [commit: ghc] master: Implement late lambda lift (b2950e0) Message-ID: <20181123152658.28ECF3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b2950e03b551d82d62ec25eb232284aaf121b4e2/ghc >--------------------------------------------------------------- commit b2950e03b551d82d62ec25eb232284aaf121b4e2 Author: Sebastian Graf Date: Fri Nov 23 16:24:18 2018 +0100 Implement late lambda lift Summary: This implements a selective lambda-lifting pass late in the STG pipeline. Lambda lifting has the effect of avoiding closure allocation at the cost of having to make former free vars available at call sites, possibly enlarging closures surrounding call sites in turn. We identify beneficial cases by means of an analysis that estimates closure growth. There's a Wiki page at https://ghc.haskell.org/trac/ghc/wiki/LateLamLift. Reviewers: simonpj, bgamari, simonmar Reviewed By: simonpj Subscribers: rwbarton, carter GHC Trac Issues: #9476 Differential Revision: https://phabricator.haskell.org/D5224 >--------------------------------------------------------------- b2950e03b551d82d62ec25eb232284aaf121b4e2 compiler/basicTypes/Demand.hs | 16 +- compiler/basicTypes/Id.hs | 3 +- compiler/codeGen/StgCmm.hs | 4 +- compiler/codeGen/StgCmmBind.hs | 7 +- compiler/codeGen/StgCmmExpr.hs | 4 +- compiler/ghc.cabal.in | 5 + compiler/main/DynFlags.hs | 26 ++ compiler/simplStg/SimplStg.hs | 117 +++-- compiler/simplStg/StgCse.hs | 8 +- compiler/simplStg/StgLiftLams.hs | 102 +++++ compiler/simplStg/StgLiftLams/Analysis.hs | 566 ++++++++++++++++++++++++ compiler/simplStg/StgLiftLams/LiftM.hs | 349 +++++++++++++++ compiler/simplStg/StgLiftLams/Transformation.hs | 155 +++++++ compiler/simplStg/StgStats.hs | 4 +- compiler/simplStg/UnariseStg.hs | 8 +- compiler/stgSyn/CoreToStg.hs | 4 +- compiler/stgSyn/StgFVs.hs | 51 ++- compiler/stgSyn/StgLint.hs | 39 +- compiler/stgSyn/StgSubst.hs | 80 ++++ compiler/stgSyn/StgSyn.hs | 104 +++-- docs/users_guide/using-optimisation.rst | 52 +++ inplace/test | 3 - inplace/test spaces | 1 - testsuite/tests/perf/join_points/all.T | 2 +- 24 files changed, 1565 insertions(+), 145 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 b2950e03b551d82d62ec25eb232284aaf121b4e2 From git at git.haskell.org Fri Nov 23 17:34:12 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Nov 2018 17:34:12 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Comments and alpha-renaming (8be7e73) Message-ID: <20181123173412.36AD93A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/8be7e73c6881b5a73e0799e9e6602f30445cd12a/ghc >--------------------------------------------------------------- commit 8be7e73c6881b5a73e0799e9e6602f30445cd12a Author: Simon Peyton Jones Date: Wed Nov 7 23:26:05 2018 +0000 Comments and alpha-renaming >--------------------------------------------------------------- 8be7e73c6881b5a73e0799e9e6602f30445cd12a compiler/typecheck/TcHsType.hs | 2 -- compiler/typecheck/TcInstDcls.hs | 10 +++++----- compiler/typecheck/TcMType.hs | 2 +- compiler/typecheck/TcSimplify.hs | 7 ++++--- 4 files changed, 10 insertions(+), 11 deletions(-) diff --git a/compiler/typecheck/TcHsType.hs b/compiler/typecheck/TcHsType.hs index 2ce23e7..dd2995e 100644 --- a/compiler/typecheck/TcHsType.hs +++ b/compiler/typecheck/TcHsType.hs @@ -1744,7 +1744,6 @@ kcImplicitTKBndrs = kcImplicitTKBndrsX newFlexiKindedTyVarTyVar -- | Bring implicitly quantified type/kind variables into scope during -- kind checking. The returned TcTyVars are in 1-1 correspondence --- with the names passed in. --- Note [Use TyVarTvs in kind-checking pass] in TcTyClsDecls. kcImplicitTKBndrsX :: (Name -> TcM TcTyVar) -- new_tv function -> [Name] -- of the vars -> TcM a @@ -2065,7 +2064,6 @@ kcLookupTcTyCon nm -- Never emits constraints, though the thing_inside might. kcTyClTyVars :: Name -> TcM a -> TcM a kcTyClTyVars tycon_name thing_inside - -- See Note [Use TyVarTvs in kind-checking pass] in TcTyClsDecls = do { tycon <- kcLookupTcTyCon tycon_name ; tcExtendNameTyVarEnv (tcTyConScopedTyVars tycon) $ thing_inside } diff --git a/compiler/typecheck/TcInstDcls.hs b/compiler/typecheck/TcInstDcls.hs index 84f43e9..63c565d 100644 --- a/compiler/typecheck/TcInstDcls.hs +++ b/compiler/typecheck/TcInstDcls.hs @@ -465,14 +465,14 @@ tcLocalInstDecl (L _ (XInstDecl _)) = panic "tcLocalInstDecl" tcClsInstDecl :: LClsInstDecl GhcRn -> TcM ([InstInfo GhcRn], [FamInst], [DerivInfo]) -- The returned DerivInfos are for any associated data families -tcClsInstDecl (L loc (ClsInstDecl { cid_poly_ty = poly_ty, cid_binds = binds +tcClsInstDecl (L loc (ClsInstDecl { cid_poly_ty = hs_ty, cid_binds = binds , cid_sigs = uprags, cid_tyfam_insts = ats , cid_overlap_mode = overlap_mode , cid_datafam_insts = adts })) = setSrcSpan loc $ - addErrCtxt (instDeclCtxt1 poly_ty) $ + addErrCtxt (instDeclCtxt1 hs_ty) $ do { (tyvars, theta, clas, inst_tys) - <- tcHsClsInstType (InstDeclCtxt False) poly_ty + <- tcHsClsInstType (InstDeclCtxt False) hs_ty -- NB: tcHsClsInstType does checkValidInstance ; tcExtendTyVarEnv tyvars $ @@ -481,7 +481,7 @@ tcClsInstDecl (L loc (ClsInstDecl { cid_poly_ty = poly_ty, cid_binds = binds mb_info = Just (clas, tyvars, mini_env) -- Next, process any associated types. - ; traceTc "tcLocalInstDecl" (ppr poly_ty) + ; traceTc "tcLocalInstDecl" (ppr hs_ty) ; tyfam_insts0 <- mapAndRecoverM (tcTyFamInstDecl mb_info) ats ; datafam_stuff <- mapAndRecoverM (tcDataFamInstDecl mb_info) adts ; let (datafam_insts, m_deriv_infos) = unzip datafam_stuff @@ -500,7 +500,7 @@ tcClsInstDecl (L loc (ClsInstDecl { cid_poly_ty = poly_ty, cid_binds = binds -- Finally, construct the Core representation of the instance. -- (This no longer includes the associated types.) - ; dfun_name <- newDFunName clas inst_tys (getLoc (hsSigType poly_ty)) + ; dfun_name <- newDFunName clas inst_tys (getLoc (hsSigType hs_ty)) -- Dfun location is that of instance *header* ; ispec <- newClsInst (fmap unLoc overlap_mode) dfun_name tyvars theta diff --git a/compiler/typecheck/TcMType.hs b/compiler/typecheck/TcMType.hs index 8192f75..9edad0f 100644 --- a/compiler/typecheck/TcMType.hs +++ b/compiler/typecheck/TcMType.hs @@ -1499,7 +1499,7 @@ defaultTyVar default_kind tv -- Do not default TyVarTvs. Doing so would violate the invariants -- on TyVarTvs; see Note [Signature skolems] in TcType. -- Trac #13343 is an example; #14555 is another - -- See Note [Kind generalisation and TyVarTvs] + -- See Note [Inferring kinds for type declarations] in TcTyClsDecls = return False diff --git a/compiler/typecheck/TcSimplify.hs b/compiler/typecheck/TcSimplify.hs index 750b621..e1a3532 100644 --- a/compiler/typecheck/TcSimplify.hs +++ b/compiler/typecheck/TcSimplify.hs @@ -2008,9 +2008,10 @@ promoteTyVarTcS tv defaultTyVarTcS :: TcTyVar -> TcS Bool defaultTyVarTcS the_tv | isRuntimeRepVar the_tv - , not (isTyVarTyVar the_tv) -- TyVarTvs should only be unified with a tyvar - -- never with a type; c.f. TcMType.defaultTyVar - -- See Note [Kind generalisation and TyVarTvs] + , not (isTyVarTyVar the_tv) + -- TyVarTvs should only be unified with a tyvar + -- never with a type; c.f. TcMType.defaultTyVar + -- and Note [Inferring kinds for type declarations] in TcTyClsDecls = do { traceTcS "defaultTyVarTcS RuntimeRep" (ppr the_tv) ; unifyTyVar the_tv liftedRepTy ; return True } From git at git.haskell.org Fri Nov 23 17:34:15 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Nov 2018 17:34:15 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Tc-tracing, and order of arguments only (4e42a78) Message-ID: <20181123173415.319BC3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/4e42a78536554b5edc6b9623bf3592c9712ef279/ghc >--------------------------------------------------------------- commit 4e42a78536554b5edc6b9623bf3592c9712ef279 Author: Simon Peyton Jones Date: Wed Oct 31 08:31:38 2018 +0000 Tc-tracing, and order of arguments only I changed the order of arguments to reportAllUnsolved, and the tc-tracing that surrounds it. No change in behaviour >--------------------------------------------------------------- 4e42a78536554b5edc6b9623bf3592c9712ef279 compiler/typecheck/TcErrors.hs | 29 ++++++++++++++++------------- compiler/typecheck/TcRnMonad.hs | 2 ++ compiler/typecheck/TcSimplify.hs | 4 ---- 3 files changed, 18 insertions(+), 17 deletions(-) diff --git a/compiler/typecheck/TcErrors.hs b/compiler/typecheck/TcErrors.hs index 6443fbd..3a124b4 100644 --- a/compiler/typecheck/TcErrors.hs +++ b/compiler/typecheck/TcErrors.hs @@ -146,8 +146,9 @@ reportUnsolved wanted | warn_out_of_scope = HoleWarn | otherwise = HoleDefer - ; report_unsolved binds_var type_errors expr_holes - type_holes out_of_scope_holes wanted + ; report_unsolved type_errors expr_holes + type_holes out_of_scope_holes + binds_var wanted ; ev_binds <- getTcEvBindsMap binds_var ; return (evBindMapBinds ev_binds)} @@ -162,8 +163,8 @@ reportUnsolved wanted reportAllUnsolved :: WantedConstraints -> TcM () reportAllUnsolved wanted = do { ev_binds <- newNoTcEvBinds - ; report_unsolved ev_binds TypeError - HoleError HoleError HoleError wanted } + ; report_unsolved TypeError HoleError HoleError HoleError + ev_binds wanted } -- | Report all unsolved goals as warnings (but without deferring any errors to -- run-time). See Note [Safe Haskell Overlapping Instances Implementation] in @@ -171,22 +172,23 @@ reportAllUnsolved wanted warnAllUnsolved :: WantedConstraints -> TcM () warnAllUnsolved wanted = do { ev_binds <- newTcEvBinds - ; report_unsolved ev_binds (TypeWarn NoReason) - HoleWarn HoleWarn HoleWarn wanted } + ; report_unsolved (TypeWarn NoReason) HoleWarn HoleWarn HoleWarn + ev_binds wanted } -- | Report unsolved goals as errors or warnings. -report_unsolved :: EvBindsVar -- cec_binds - -> TypeErrorChoice -- Deferred type errors +report_unsolved :: TypeErrorChoice -- Deferred type errors -> HoleChoice -- Expression holes -> HoleChoice -- Type holes -> HoleChoice -- Out of scope holes + -> EvBindsVar -- cec_binds -> WantedConstraints -> TcM () -report_unsolved mb_binds_var type_errors expr_holes - type_holes out_of_scope_holes wanted +report_unsolved type_errors expr_holes + type_holes out_of_scope_holes binds_var wanted | isEmptyWC wanted = return () | otherwise - = do { traceTc "reportUnsolved warning/error settings:" $ + = do { traceTc "reportUnsolved {" empty + ; traceTc "reportUnsolved warning/error settings:" $ vcat [ text "type errors:" <+> ppr type_errors , text "expr holes:" <+> ppr expr_holes , text "type holes:" <+> ppr type_holes @@ -219,10 +221,11 @@ report_unsolved mb_binds_var type_errors expr_holes -- See Trac #15539 and c.f. setting ic_status -- in TcSimplify.setImplicationStatus , cec_warn_redundant = warn_redundant - , cec_binds = mb_binds_var } + , cec_binds = binds_var } ; tc_lvl <- getTcLevel - ; reportWanteds err_ctxt tc_lvl wanted } + ; reportWanteds err_ctxt tc_lvl wanted + ; traceTc "reportUnsolved }" empty } -------------------------------------------- -- Internal functions diff --git a/compiler/typecheck/TcRnMonad.hs b/compiler/typecheck/TcRnMonad.hs index a033bc4..b923d49 100644 --- a/compiler/typecheck/TcRnMonad.hs +++ b/compiler/typecheck/TcRnMonad.hs @@ -1532,8 +1532,10 @@ pushLevelAndCaptureConstraints :: TcM a -> TcM (TcLevel, WantedConstraints, a) pushLevelAndCaptureConstraints thing_inside = do { env <- getLclEnv ; let tclvl' = pushTcLevel (tcl_tclvl env) + ; traceTc "pushLevelAndCaptureConstraints {" (ppr tclvl') ; (res, lie) <- setLclEnv (env { tcl_tclvl = tclvl' }) $ captureConstraints thing_inside + ; traceTc "pushLevelAndCaptureConstraints }" (ppr tclvl') ; return (tclvl', lie, res) } pushTcLevelM_ :: TcM a -> TcM a diff --git a/compiler/typecheck/TcSimplify.hs b/compiler/typecheck/TcSimplify.hs index 6ef62c8..c424a02 100644 --- a/compiler/typecheck/TcSimplify.hs +++ b/compiler/typecheck/TcSimplify.hs @@ -178,9 +178,7 @@ solveEqualities thing_inside -- vars to LiftedRep. This is needed to avoid #14991. ; traceTc "End solveEqualities }" empty - ; traceTc "reportAllUnsolved {" empty ; reportAllUnsolved final_wc - ; traceTc "reportAllUnsolved }" empty ; return result } -- | Simplify top-level constraints, but without reporting any unsolved @@ -514,9 +512,7 @@ simplifyDefault theta = do { traceTc "simplifyDefault" empty ; wanteds <- newWanteds DefaultOrigin theta ; unsolved <- runTcSDeriveds (solveWantedsAndDrop (mkSimpleWC wanteds)) - ; traceTc "reportUnsolved {" empty ; reportAllUnsolved unsolved - ; traceTc "reportUnsolved }" empty ; return () } ------------------ From git at git.haskell.org Fri Nov 23 17:34:18 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Nov 2018 17:34:18 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Start to eliminate tcFamTyPats (584cdfc) Message-ID: <20181123173418.26E563A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/584cdfc05568d8a2ea6864df81bdcdaf9f87465b/ghc >--------------------------------------------------------------- commit 584cdfc05568d8a2ea6864df81bdcdaf9f87465b Author: Simon Peyton Jones Date: Mon Nov 12 13:41:33 2018 +0000 Start to eliminate tcFamTyPats >--------------------------------------------------------------- 584cdfc05568d8a2ea6864df81bdcdaf9f87465b compiler/typecheck/TcHsType.hs | 1 + compiler/typecheck/TcTyClsDecls.hs | 20 ++++++++------------ 2 files changed, 9 insertions(+), 12 deletions(-) diff --git a/compiler/typecheck/TcHsType.hs b/compiler/typecheck/TcHsType.hs index 7f637b7..fe8c1a0 100644 --- a/compiler/typecheck/TcHsType.hs +++ b/compiler/typecheck/TcHsType.hs @@ -21,6 +21,7 @@ module TcHsType ( UserTypeCtxt(..), bindImplicitTKBndrs_Skol, bindImplicitTKBndrs_Q_Skol, bindExplicitTKBndrs_Skol, bindExplicitTKBndrs_Q_Skol, + ContextKind(..), -- Type checking type and class decls kcLookupTcTyCon, kcTyClTyVars, tcTyClTyVars, diff --git a/compiler/typecheck/TcTyClsDecls.hs b/compiler/typecheck/TcTyClsDecls.hs index 5b5d858..b9227de 100644 --- a/compiler/typecheck/TcTyClsDecls.hs +++ b/compiler/typecheck/TcTyClsDecls.hs @@ -1760,6 +1760,7 @@ tcTyFamInstEqn :: TcTyCon -> Maybe ClsInstInfo -> LTyFamInstEqn GhcRn -- (typechecked here) have TyFamInstEqns +{- tcTyFamInstEqn fam_tc mb_clsinfo (L loc (HsIB { hsib_ext = imp_vars , hsib_body = FamEqn { feqn_tycon = L _ eqn_tc_name @@ -1780,8 +1781,8 @@ tcTyFamInstEqn fam_tc mb_clsinfo ; return (mkCoAxBranch tvs' [] pats' rhs_ty' (map (const Nominal) tvs') loc) } +-} -{- tcTyFamInstEqn fam_tc mb_clsinfo eqn@(L loc (HsIB { hsib_ext = imp_vars , hsib_body = FamEqn { feqn_tycon = L _ eqn_tc_name @@ -1790,12 +1791,12 @@ tcTyFamInstEqn fam_tc mb_clsinfo , feqn_rhs = hs_ty }})) = ASSERT( getName fam_tc == eqn_tc_name ) setSrcSpan loc $ - do { traceTc "tcTyFamInstEqn {" (ppr eqn) - ; (imp_tvs, (exp_tvs, ((pats, rhs_ty)))) + do { traceTc "tcTyFamInstEqn {" (ppr eqn_tc_name <+> ppr hs_pats) + ; (_imp_tvs, (_exp_tvs, ((pats, rhs_ty)))) <- pushTcLevelM_ $ solveEqualities $ bindImplicitTKBndrs_Q_Skol imp_vars $ - bindExplicitTKBndrs_Q_Skol (mb_expl_bndrs `orElse` []) $ + bindExplicitTKBndrs_Q_Skol AnyKind (mb_expl_bndrs `orElse` []) $ do { let fam_name = tyConName fam_tc lhs_fun = L loc (HsTyVar noExt NotPromoted (L loc fam_name)) @@ -1808,21 +1809,16 @@ tcTyFamInstEqn fam_tc mb_clsinfo ; rhs_ty <- tcCheckLHsType hs_ty res_kind ; return (pats, rhs_ty) } - ; imp_tvs <- zonkAndScopedSort imp_tvs - ; let spec_req_tkvs = imp_tvs ++ exp_tvs - ; dvs <- candidateQTyVarsOfKinds $ - typeKind rhs_ty : map tyVarKind (spec_req_tkvs) - ; let final_dvs = dvs `delCandidates` spec_req_tkvs - ; inferred_kvs <- quantifyTyVars emptyVarSet final_dvs + ; dvs <- candidateQTyVarsOfTypes (rhs_ty : pats) + ; qtkvs <- quantifyTyVars emptyVarSet dvs - ; (ze, tvs') <- zonkTyBndrs (inferred_kvs ++ spec_req_tkvs) + ; (ze, tvs') <- zonkTyBndrs qtkvs ; pats' <- zonkTcTypesToTypesX ze pats ; rhs_ty' <- zonkTcTypeToTypeX ze rhs_ty ; traceTc "tcTyFamInstEqn }" (ppr fam_tc <+> pprTyVars tvs') ; return (mkCoAxBranch tvs' [] pats' rhs_ty' (map (const Nominal) tvs') loc) } --} tcTyFamInstEqn _ _ (L _ (XHsImplicitBndrs _)) = panic "tcTyFamInstEqn" From git at git.haskell.org Fri Nov 23 17:34:21 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Nov 2018 17:34:21 +0000 (UTC) Subject: [commit: ghc] wip/T15809: WIP on using level numbers for generalisation (2828e18) Message-ID: <20181123173421.312303A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/2828e1857fb5eb41fa820220ac8cedeac3d05727/ghc >--------------------------------------------------------------- commit 2828e1857fb5eb41fa820220ac8cedeac3d05727 Author: Simon Peyton Jones Date: Wed Oct 31 08:40:40 2018 +0000 WIP on using level numbers for generalisation This mostly works. So far I simply have a WARNING in quantifyTyVars which fires if the two methods (old "global-tyvars" and new "level-numbers") give different answers. Some modest but important refactoring along the way. Main thing that is still wrong: in instance declarations we are not skoelmising. Here's a partial patch to TcInstDcls, that /doesn't/ yet work -- Next, process any associated types. ; traceTc "tcLocalInstDecl" (ppr poly_ty) - ; tyfam_insts0 <- scopeTyVars InstSkol tyvars $ - mapAndRecoverM (tcTyFamInstDecl mb_info) ats - ; datafam_stuff <- scopeTyVars InstSkol tyvars $ - mapAndRecoverM (tcDataFamInstDecl mb_info) adts + ; (_subst, skol_tvs) <- tcInstSkolTyVars tyvars + ; (tyfam_insts0, datafam_stuff) + <- tcExtendNameTyVarEnv (map tyVarName tyvars `zip` skol_tvs) $ + do { tfs <- mapAndRecoverM (tcTyFamInstDecl mb_info) ats + ; dfs <- mapAndRecoverM (tcDataFamInstDecl mb_info) adts + ; return (tfs, dfs) } ; let (datafam_insts, m_deriv_infos) = unzip datafam_stuff >--------------------------------------------------------------- 2828e1857fb5eb41fa820220ac8cedeac3d05727 compiler/typecheck/TcHsType.hs | 95 ++++++++++++++++++++++++------------ compiler/typecheck/TcMType.hs | 99 ++++++++++++++++++++++++++------------ compiler/typecheck/TcSimplify.hs | 19 +++++--- compiler/typecheck/TcTyClsDecls.hs | 86 ++++++++++++++++----------------- compiler/typecheck/TcValidity.hs | 12 ++--- 5 files changed, 192 insertions(+), 119 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 2828e1857fb5eb41fa820220ac8cedeac3d05727 From git at git.haskell.org Fri Nov 23 17:34:24 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Nov 2018 17:34:24 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Progress (9c02610) Message-ID: <20181123173424.284643A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/9c02610e8e719b0e210e6399d8c65204e5cbeada/ghc >--------------------------------------------------------------- commit 9c02610e8e719b0e210e6399d8c65204e5cbeada Author: Simon Peyton Jones Date: Fri Nov 9 18:11:25 2018 +0000 Progress Allocate result kind outside tcImplicit in tc_hs_sig_type_and_gen Plus comments In flight.. may not build (but it's a wip/ branch) >--------------------------------------------------------------- 9c02610e8e719b0e210e6399d8c65204e5cbeada compiler/typecheck/TcHsType.hs | 49 +++++++++++++++++++++--------------------- compiler/typecheck/TcMType.hs | 18 ++++------------ 2 files changed, 29 insertions(+), 38 deletions(-) diff --git a/compiler/typecheck/TcHsType.hs b/compiler/typecheck/TcHsType.hs index dd2995e..7f5d4ff 100644 --- a/compiler/typecheck/TcHsType.hs +++ b/compiler/typecheck/TcHsType.hs @@ -229,19 +229,15 @@ tc_hs_sig_type_and_gen skol_info hs_sig_type ctxt_kind | HsIB { hsib_ext = sig_vars, hsib_body = hs_ty } <- hs_sig_type = do { (_inner_lvl, wanted, (tkvs, ty)) <- pushLevelAndCaptureConstraints $ - tcImplicitTKBndrs skol_info sig_vars $ - -- tcImplicitTKBndrs does a solveLocalEqualities - do { kind <- case ctxt_kind of + do { -- See Note [Levels and generalisation] + res_kind <- case ctxt_kind of TheKind k -> return k AnyKind -> newMetaKindVar OpenKind -> newOpenTypeKind - -- The kind is checked by checkValidType, and isn't necessarily - -- of kind * in a Template Haskell quote eg [t| Maybe |] - ; tc_lhs_type typeLevelMode hs_ty kind } - -- Any remaining variables (unsolved in the solveLocalEqualities - -- in the tcImplicitTKBndrs) should be in the global tyvars, - -- and therefore won't be quantified over + ; tcImplicitTKBndrs skol_info sig_vars $ + -- tcImplicitTKBndrs does a solveLocalEqualities + tc_lhs_type typeLevelMode hs_ty res_kind } ; let ty1 = mkSpecForAllTys tkvs ty ; kvs <- kindGeneralizeLocal wanted ty1 @@ -1467,20 +1463,6 @@ To avoid the double-zonk, we do two things: 2. When we are generalizing: kindGeneralize does not require a zonked type -- it zonks as it gathers free variables. So this way effectively sidesteps step 3. - -Note [TcLevel for CUSKs] -~~~~~~~~~~~~~~~~~~~~~~~~ -In getInitialKinds we are at level 1, busy making unification -variables over which we will subsequently generalise. - -But when we find a CUSK we want to jump back to top level (0) -because that's the right starting point for a completee, -stand-alone kind signature. - -More precisely, we want to make level-1 skolems, because -the end up as the TyConBinders of the TyCon, and are brought -into scope when we type-check the body of the type declaration -(in tcTyClDecl). -} tcWildCardBinders :: [Name] @@ -2003,7 +1985,26 @@ kindGeneralizeLocal wanted kind_or_type ; quantifyTyVars mono_tvs dvs } -{- +{- Note [Levels and generalisation] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Consider + f x = e +with no type signature. We are currently at level i. +We must + * Push the level to level (i+1) + * Allocate a fresh alpha[i+1] for the result type + * Check that e :: alpha[i+1], gathering constraint WC + * Solve WC as far as possible + * Zonking the result type alpha[i+1], say to beta[i-1] -> gamma[i] + * Find the free variables with level > i, in this case gamma[i] + * Skolemise those free variables and quantify over them, giving + f :: forall g. beta[i-1] -> g + * Emit the residiual constraint wrapped in an implication for g, + thus forall g. WC + +All of this happens for types too. Consider + f :: Int -> (forall a. Proxy a -> Int) + Note [Kind generalisation] ~~~~~~~~~~~~~~~~~~~~~~~~~~ We do kind generalisation only at the outer level of a type signature. diff --git a/compiler/typecheck/TcMType.hs b/compiler/typecheck/TcMType.hs index 6d9f3ca..a1cdf24 100644 --- a/compiler/typecheck/TcMType.hs +++ b/compiler/typecheck/TcMType.hs @@ -1342,16 +1342,6 @@ to be later converted to a list in a deterministic order. For more information about deterministic sets see Note [Deterministic UniqFM] in UniqDFM. - - ---------------- Note to tidy up -------- -Can we quantify over a non-unification variable? Sadly yes (Trac #15991b) - class C2 (a :: Type) (b :: Proxy a) (c :: Proxy b) where - type T4 a c - -When we come to T4 we have in Inferred b; but it is a skolem -from the (fully settled) C2. - -} quantifyTyVars @@ -1444,10 +1434,10 @@ quantifyTyVars gbl_tvs = return Nothing -- this can happen for a covar that's associated with -- a coercion hole. Test case: typecheck/should_compile/T2494 - | not (isTcTyVar tkv) - = WARN( True, text "quantifying over a TyVar" <+> ppr tkv) - return (Just tkv) -- For associated types, we have the class variables - -- in scope, and they are TyVars not TcTyVars + | not (isTcTyVar tkv) -- I don't think this can ever happen. + -- Hence the assert + = ASSERT2( False, text "quantifying over a TyVar" <+> ppr tkv) + return (Just tkv) | otherwise = do { deflt_done <- defaultTyVar default_kind tkv From git at git.haskell.org Fri Nov 23 17:34:27 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Nov 2018 17:34:27 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Comemnts only (1eddbc2) Message-ID: <20181123173427.1F6143A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/1eddbc2a8a8f6b9cf708f434ecf088eefba71729/ghc >--------------------------------------------------------------- commit 1eddbc2a8a8f6b9cf708f434ecf088eefba71729 Author: Simon Peyton Jones Date: Wed Nov 7 11:40:50 2018 +0000 Comemnts only >--------------------------------------------------------------- 1eddbc2a8a8f6b9cf708f434ecf088eefba71729 compiler/typecheck/TcTyClsDecls.hs | 74 +++++++++++++++++++++++--------------- 1 file changed, 46 insertions(+), 28 deletions(-) diff --git a/compiler/typecheck/TcTyClsDecls.hs b/compiler/typecheck/TcTyClsDecls.hs index 3f90c42..cefc9ca 100644 --- a/compiler/typecheck/TcTyClsDecls.hs +++ b/compiler/typecheck/TcTyClsDecls.hs @@ -637,37 +637,55 @@ generaliseTcTyCon tc {- Note [Required, Specified, and Inferred for types] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -We have some design choices in how we classify the tyvars bound -in a type declaration. (Here, I use "type" to refer to any TyClDecl.) -Much of the debate is memorialized in #15743. This Note documents -the final conclusion. - -First, a reminder: - * a Required argument is one that must be provided at every call site - * a Specified argument is one that can be inferred at call sites, but - may be instantiated with visible type application - * an Inferred argument is one that must be inferred at call sites; it - is unavailable for use with visible type application. - -Why have Inferred at all? Because we just can't make user-facing promises -about the ordering of some variables. These might swizzle around even between -minor released. By forbidding visible type application, we ensure users -aren't caught unawares. See also -Note [VarBndrs, TyCoVarBinders, TyConBinders, and visibility] in TyCoRep. - -When inferring the ordering of variables (that is, for those -variables that he user has not specified the order with an explicit `forall`) -we use the following order: - - 1. Inferred variables from an enclosing class (associated types only) - 2. Specified variables from an enclosing class (associated types only) - 3. Inferred variables not from an enclosing class - 4. Specified variables not from an enclosing class - 5. Required variables before a top-level :: - 6. All variables after a top-level :: +Each forall'd type variable in a type or kind is one of + + * Required: an argument must be provided at every call site + + * Specified: the argument can be inferred at call sites, but + may be instantiated with visible type/kind application + + * Inferred: the must be inferred at call sites; it + is unavailable for use with visible type/kind application. + +Why have Inferred at all? Because we just can't make user-facing +promises about the ordering of some variables. These might swizzle +around even between minor released. By forbidding visible type +application, we ensure users aren't caught unawares. + +Go read Note [VarBndrs, TyCoVarBinders, TyConBinders, and visibility] in TyCoRep. + +The question for this Note is this: + given a TyClDecl, how are its quantified type variables classified? +Much of the debate is memorialized in #15743. + +Here is our design choice. When inferring the ordering of variables +for a TyCl declaration (that is, for those variables that he user +has not specified the order with an explicit `forall`), we use the +following order: + + 1. Inferred variables + 2. Specified variables; in the left-to-right order in which + the user wrote them, modified by scopedSort (see below) + to put them in depdendency order. + 3. Required variables before a top-level :: + 4. All variables after a top-level :: If this ordering does not make a valid telescope, we reject the definition. +Example: + data SameKind :: k -> k -> * + data X a (b :: SameKind a b) (c :: k) d + +For X: + - a, b, c, d are Required; they are explicitly listed by the user + as the positional arguments of X + - k is Specified; it appears explicitly in a kind signature + - k2, the kind of d, is Inferred; it is not mentioned explicitly at all + +Putting variables in the order Inferred, Specified, Required gives us + Inferred: k2 + Specified: k (a ::kb + This idea is implemented in the generalise function within kcTyClGroup (for declarations without CUSKs), and in kcLHsQTyVars (for declarations with CUSKs). Note that neither definition worries about point (6) above, as this From git at git.haskell.org Fri Nov 23 17:34:30 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Nov 2018 17:34:30 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Comments only (2f86a8d) Message-ID: <20181123173430.1AE423A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/2f86a8d4d091b451aea7a915addc0fedfaee5083/ghc >--------------------------------------------------------------- commit 2f86a8d4d091b451aea7a915addc0fedfaee5083 Author: Simon Peyton Jones Date: Fri Nov 9 17:46:05 2018 +0000 Comments only >--------------------------------------------------------------- 2f86a8d4d091b451aea7a915addc0fedfaee5083 compiler/typecheck/TcMType.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/compiler/typecheck/TcMType.hs b/compiler/typecheck/TcMType.hs index 9edad0f..6d9f3ca 100644 --- a/compiler/typecheck/TcMType.hs +++ b/compiler/typecheck/TcMType.hs @@ -662,7 +662,8 @@ but this restriction was dropped, and ScopedTypeVariables can now refer to full types (GHC Proposal 29). The remaining uses of newTyVarTyVars are -* in kind signatures, see Note [Kind generalisation and TyVarTvs] +* In kind signatures, see + TcTyClsDecls Note [Inferring kinds for type declarations] and Note [Use TyVarTvs in kind-checking pass] * in partial type signatures, see Note [Quantified variables in partial type signatures] -} From git at git.haskell.org Fri Nov 23 17:34:33 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Nov 2018 17:34:33 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Wibbles (d5b27c7) Message-ID: <20181123173433.1F63E3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/d5b27c7a1830173f60bc1db32e60a3c098f8026d/ghc >--------------------------------------------------------------- commit d5b27c7a1830173f60bc1db32e60a3c098f8026d Author: Simon Peyton Jones Date: Mon Nov 12 17:43:48 2018 +0000 Wibbles >--------------------------------------------------------------- d5b27c7a1830173f60bc1db32e60a3c098f8026d testsuite/tests/indexed-types/should_fail/T7536.stderr | 8 ++++---- testsuite/tests/indexed-types/should_fail/T7938.hs | 6 ++---- testsuite/tests/indexed-types/should_fail/T7938.stderr | 2 +- 3 files changed, 7 insertions(+), 9 deletions(-) diff --git a/testsuite/tests/indexed-types/should_fail/T7536.stderr b/testsuite/tests/indexed-types/should_fail/T7536.stderr index 9e7ed30..34a393e 100644 --- a/testsuite/tests/indexed-types/should_fail/T7536.stderr +++ b/testsuite/tests/indexed-types/should_fail/T7536.stderr @@ -1,5 +1,5 @@ -T7536.hs:8:15: - Family instance purports to bind type variable ‘a’ - but the real LHS (expanding synonyms) is: TF Int = ... - In the type instance declaration for ‘TF’ +T7536.hs:8:15: error: + • LHS of family instance fails to bind type variable ‘a’ + The real LHS (expanding synonyms) is: TF Int + • In the type instance declaration for ‘TF’ diff --git a/testsuite/tests/indexed-types/should_fail/T7938.hs b/testsuite/tests/indexed-types/should_fail/T7938.hs index f1e8266..246015d 100644 --- a/testsuite/tests/indexed-types/should_fail/T7938.hs +++ b/testsuite/tests/indexed-types/should_fail/T7938.hs @@ -8,7 +8,5 @@ data KProxy (a :: *) = KP class Foo (a :: k1) (b :: k2) where type Bar a --- instance Foo (a :: k1) (b :: k2) where --- type Bar a = (KP :: KProxy k2) - --- \ No newline at end of file +instance Foo (a :: k1) (b :: k2) where + type Bar a = (KP :: KProxy k2) diff --git a/testsuite/tests/indexed-types/should_fail/T7938.stderr b/testsuite/tests/indexed-types/should_fail/T7938.stderr index 890be7b..5751c4e 100644 --- a/testsuite/tests/indexed-types/should_fail/T7938.stderr +++ b/testsuite/tests/indexed-types/should_fail/T7938.stderr @@ -1,6 +1,6 @@ T7938.hs:12:17: error: - • Expected a type, but ‘KP :: KProxy k2’ has kind ‘KProxy k4’ + • Expected a type, but ‘KP :: KProxy k2’ has kind ‘KProxy k2’ • In the type ‘(KP :: KProxy k2)’ In the type instance declaration for ‘Bar’ In the instance declaration for ‘Foo (a :: k1) (b :: k2)’ From git at git.haskell.org Fri Nov 23 17:34:36 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Nov 2018 17:34:36 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Combine kcImplicitTKBndrs and tcImplicitTKBndrs (f2fe11a) Message-ID: <20181123173436.3356A3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/f2fe11ad1ff6104fb7013494a55d9ab0627c16f9/ghc >--------------------------------------------------------------- commit f2fe11ad1ff6104fb7013494a55d9ab0627c16f9 Author: Simon Peyton Jones Date: Mon Nov 12 08:30:33 2018 +0000 Combine kcImplicitTKBndrs and tcImplicitTKBndrs Based on a conversation with Richard on Friday, this patch * Abolishes the distinction between kcImplicitTKBndrs and tcImplicitTKBndrs; now it is bindImplicitTKBndrs * Same for kc/tcExplicitTKBndrs * tcImplicitTKBndrs no longer does a solveLocalEqualities and sort; the caller does that Much nicer. Not quite working yet though >--------------------------------------------------------------- f2fe11ad1ff6104fb7013494a55d9ab0627c16f9 compiler/typecheck/TcBackpack.hs | 2 +- compiler/typecheck/TcDerivInfer.hs | 2 +- compiler/typecheck/TcHsType.hs | 238 +++++++++------------ compiler/typecheck/TcInstDcls.hs | 2 +- compiler/typecheck/TcRnMonad.hs | 4 +- compiler/typecheck/TcRules.hs | 34 ++- compiler/typecheck/TcSMonad.hs | 4 +- compiler/typecheck/TcSigs.hs | 46 ++-- compiler/typecheck/TcSimplify.hs | 18 +- compiler/typecheck/TcSplice.hs | 4 +- compiler/typecheck/TcTyClsDecls.hs | 205 +++++++++++------- compiler/typecheck/TcUnify.hs | 33 +-- testsuite/tests/dependent/should_compile/T13910.hs | 10 +- .../tests/indexed-types/should_compile/T12369.hs | 10 + testsuite/tests/indexed-types/should_fail/T7938.hs | 6 +- 15 files changed, 331 insertions(+), 287 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 f2fe11ad1ff6104fb7013494a55d9ab0627c16f9 From git at git.haskell.org Fri Nov 23 17:34:39 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Nov 2018 17:34:39 +0000 (UTC) Subject: [commit: ghc] wip/T15809: More progress on using level numbers for gen (5b84cbf) Message-ID: <20181123173439.3AA163A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/5b84cbfdefca37ecef0b5d935e722d61e34c84d7/ghc >--------------------------------------------------------------- commit 5b84cbfdefca37ecef0b5d935e722d61e34c84d7 Author: Simon Peyton Jones Date: Wed Oct 31 15:00:16 2018 +0000 More progress on using level numbers for gen >--------------------------------------------------------------- 5b84cbfdefca37ecef0b5d935e722d61e34c84d7 compiler/typecheck/TcHsType.hs | 196 ++++++++++++++++++------------------- compiler/typecheck/TcInstDcls.hs | 11 +-- compiler/typecheck/TcMType.hs | 5 +- compiler/typecheck/TcSimplify.hs | 11 ++- compiler/typecheck/TcTyClsDecls.hs | 8 +- 5 files changed, 112 insertions(+), 119 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 5b84cbfdefca37ecef0b5d935e722d61e34c84d7 From git at git.haskell.org Fri Nov 23 17:34:42 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Nov 2018 17:34:42 +0000 (UTC) Subject: [commit: ghc] wip/T15809: More progress (1a1e6c8) Message-ID: <20181123173442.552533A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/1a1e6c8e548e19ca3dfe9da2d78916a3fbe3e82e/ghc >--------------------------------------------------------------- commit 1a1e6c8e548e19ca3dfe9da2d78916a3fbe3e82e Author: Simon Peyton Jones Date: Tue Nov 6 08:55:37 2018 +0000 More progress >--------------------------------------------------------------- 1a1e6c8e548e19ca3dfe9da2d78916a3fbe3e82e compiler/typecheck/TcEnv.hs | 2 +- compiler/typecheck/TcHsSyn.hs | 7 ++++- compiler/typecheck/TcHsType.hs | 4 --- compiler/typecheck/TcMType.hs | 14 ++++----- compiler/typecheck/TcRnDriver.hs | 2 +- compiler/typecheck/TcSimplify.hs | 2 +- compiler/typecheck/TcTyClsDecls.hs | 61 +++++++++++++++++++++++++------------- 7 files changed, 57 insertions(+), 35 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 1a1e6c8e548e19ca3dfe9da2d78916a3fbe3e82e From git at git.haskell.org Fri Nov 23 17:34:45 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Nov 2018 17:34:45 +0000 (UTC) Subject: [commit: ghc] wip/T15809: More progress (8a932d0) Message-ID: <20181123173445.5AC853A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/8a932d0de1d899053e3584d65099579895470d11/ghc >--------------------------------------------------------------- commit 8a932d0de1d899053e3584d65099579895470d11 Author: Simon Peyton Jones Date: Wed Nov 7 07:52:16 2018 +0000 More progress A fixup in TcPatSyn >--------------------------------------------------------------- 8a932d0de1d899053e3584d65099579895470d11 compiler/typecheck/TcMType.hs | 48 ++++++++++++++++---------------- compiler/typecheck/TcPatSyn.hs | 56 +++++++++++++++++++++++++++++++------- compiler/typecheck/TcSimplify.hs | 7 +++-- compiler/typecheck/TcTyClsDecls.hs | 1 + 4 files changed, 75 insertions(+), 37 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 8a932d0de1d899053e3584d65099579895470d11 From git at git.haskell.org Fri Nov 23 17:34:48 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Nov 2018 17:34:48 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Finally done (bb8c97a) Message-ID: <20181123173448.59FF73A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/bb8c97a9535961c8dde34f172b3ff0c9b0525bf9/ghc >--------------------------------------------------------------- commit bb8c97a9535961c8dde34f172b3ff0c9b0525bf9 Author: Simon Peyton Jones Date: Wed Nov 7 12:51:32 2018 +0000 Finally done >--------------------------------------------------------------- bb8c97a9535961c8dde34f172b3ff0c9b0525bf9 compiler/typecheck/TcHsType.hs | 128 +++----------- compiler/typecheck/TcMType.hs | 63 +++---- compiler/typecheck/TcTyClsDecls.hs | 188 ++++++++++++++++----- compiler/typecheck/TcValidity.hs | 77 ++++++--- .../dependent/should_fail/BadTelescope.stderr | 7 +- .../dependent/should_fail/BadTelescope3.stderr | 6 +- .../dependent/should_fail/BadTelescope4.stderr | 13 +- .../tests/dependent/should_fail/T13895.stderr | 37 +--- .../tests/dependent/should_fail/T14066f.stderr | 6 +- .../tests/dependent/should_fail/T14066g.stderr | 8 +- .../tests/dependent/should_fail/T15591b.stderr | 9 +- .../tests/dependent/should_fail/T15591c.stderr | 9 +- .../tests/dependent/should_fail/T15743c.stderr | 13 +- .../tests/dependent/should_fail/T15743d.stderr | 13 +- testsuite/tests/ghci/scripts/T15591.hs | 9 +- testsuite/tests/ghci/scripts/T15591.stdout | 6 +- 16 files changed, 312 insertions(+), 280 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 bb8c97a9535961c8dde34f172b3ff0c9b0525bf9 From git at git.haskell.org Fri Nov 23 17:34:51 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Nov 2018 17:34:51 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Further work on TyCon generalisation (1d39ab2) Message-ID: <20181123173451.6C4013A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/1d39ab284d24fbe840ddba5d343a22c53b6dbe63/ghc >--------------------------------------------------------------- commit 1d39ab284d24fbe840ddba5d343a22c53b6dbe63 Author: Simon Peyton Jones Date: Fri Nov 2 18:06:16 2018 +0000 Further work on TyCon generalisation >--------------------------------------------------------------- 1d39ab284d24fbe840ddba5d343a22c53b6dbe63 compiler/typecheck/TcHsType.hs | 109 +++++++++++---------- compiler/typecheck/TcMType.hs | 54 +++++++--- compiler/typecheck/TcRnTypes.hs | 8 +- compiler/typecheck/TcTyClsDecls.hs | 93 +++++------------- compiler/types/TyCoRep.hs | 16 ++- compiler/types/Type.hs | 2 +- testsuite/tests/dependent/should_compile/T14880.hs | 1 + .../tests/dependent/should_compile/T15743e.stderr | 6 +- .../tests/indexed-types/should_fail/T13972.stderr | 2 +- testsuite/tests/polykinds/T12593.stderr | 8 +- 10 files changed, 147 insertions(+), 152 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 1d39ab284d24fbe840ddba5d343a22c53b6dbe63 From git at git.haskell.org Fri Nov 23 17:34:54 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Nov 2018 17:34:54 +0000 (UTC) Subject: [commit: ghc] wip/T15809: More progress (ee11207) Message-ID: <20181123173454.77DD43A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/ee11207e0a29eade134c59633d3d40dbe85022de/ghc >--------------------------------------------------------------- commit ee11207e0a29eade134c59633d3d40dbe85022de Author: Simon Peyton Jones Date: Tue Nov 6 17:44:25 2018 +0000 More progress >--------------------------------------------------------------- ee11207e0a29eade134c59633d3d40dbe85022de compiler/typecheck/TcHsType.hs | 290 +++++++++------------ compiler/typecheck/TcMType.hs | 122 ++++----- compiler/typecheck/TcTyClsDecls.hs | 229 ++++++++-------- compiler/typecheck/TcValidity.hs | 19 +- testsuite/tests/dependent/should_compile/T14880.hs | 1 - .../tests/dependent/should_compile/T15743e.stderr | 2 +- testsuite/tests/ghci/scripts/T15591.hs | 5 + testsuite/tests/ghci/scripts/T15743b.stdout | 2 +- testsuite/tests/ghci/scripts/T7873.stderr | 2 +- .../tests/indexed-types/should_fail/T13972.stderr | 2 +- testsuite/tests/polykinds/T11203.stderr | 2 +- testsuite/tests/polykinds/T11821a.stderr | 2 +- testsuite/tests/polykinds/T15592b.stderr | 2 +- .../tests/typecheck/should_fail/T13983.stderr | 2 +- testsuite/tests/typecheck/should_fail/T2688.stderr | 6 +- 15 files changed, 318 insertions(+), 370 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 ee11207e0a29eade134c59633d3d40dbe85022de From git at git.haskell.org Fri Nov 23 17:34:57 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Nov 2018 17:34:57 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Get rid of kcLHsQTyVarBndrs (7a4f383) Message-ID: <20181123173457.845613A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/7a4f383dc55384d343e355e599754ecbca2df314/ghc >--------------------------------------------------------------- commit 7a4f383dc55384d343e355e599754ecbca2df314 Author: Simon Peyton Jones Date: Mon Nov 12 12:08:33 2018 +0000 Get rid of kcLHsQTyVarBndrs >--------------------------------------------------------------- 7a4f383dc55384d343e355e599754ecbca2df314 compiler/typecheck/TcHsType.hs | 289 +++++++++++++++++++-------------------- compiler/typecheck/TcMType.hs | 2 +- compiler/typecheck/TcValidity.hs | 21 --- 3 files changed, 138 insertions(+), 174 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 7a4f383dc55384d343e355e599754ecbca2df314 From git at git.haskell.org Fri Nov 23 17:35:00 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Nov 2018 17:35:00 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Further progress (1a7a425) Message-ID: <20181123173500.8D0773A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/1a7a42590b44b8f4357626a1410c2b09289ce15f/ghc >--------------------------------------------------------------- commit 1a7a42590b44b8f4357626a1410c2b09289ce15f Author: Simon Peyton Jones Date: Mon Nov 5 17:43:08 2018 +0000 Further progress >--------------------------------------------------------------- 1a7a42590b44b8f4357626a1410c2b09289ce15f compiler/typecheck/TcHsSyn.hs | 28 ++++++----- compiler/typecheck/TcHsType.hs | 7 ++- compiler/typecheck/TcMType.hs | 95 ++++++++++++++++++++++++-------------- compiler/typecheck/TcRules.hs | 2 +- compiler/typecheck/TcSimplify.hs | 6 +-- compiler/typecheck/TcTyClsDecls.hs | 43 +++++++++-------- 6 files changed, 111 insertions(+), 70 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 1a7a42590b44b8f4357626a1410c2b09289ce15f From git at git.haskell.org Fri Nov 23 17:35:04 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Nov 2018 17:35:04 +0000 (UTC) Subject: [commit: ghc] wip/T15809: More progress on tcFamTyPats (196b4a0) Message-ID: <20181123173504.87BA63A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/196b4a0b5713a1c32e3bff1ebc385062d1876dd5/ghc >--------------------------------------------------------------- commit 196b4a0b5713a1c32e3bff1ebc385062d1876dd5 Author: Simon Peyton Jones Date: Mon Nov 12 17:21:55 2018 +0000 More progress on tcFamTyPats This fixes Trac #15740 >--------------------------------------------------------------- 196b4a0b5713a1c32e3bff1ebc385062d1876dd5 compiler/typecheck/TcHsType.hs | 26 ++++++++++------- compiler/typecheck/TcMType.hs | 4 +-- compiler/typecheck/TcTyClsDecls.hs | 51 +++++++++++++++++++++++++++------ compiler/typecheck/TcValidity.hs | 23 ++++++++------- testsuite/tests/polykinds/T13985.stderr | 10 ++----- testsuite/tests/polykinds/T15740.hs | 15 ++++++++++ testsuite/tests/polykinds/T15740.stderr | 6 ++++ testsuite/tests/polykinds/T15740a.hs | 12 ++++++++ testsuite/tests/polykinds/all.T | 2 ++ 9 files changed, 109 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 196b4a0b5713a1c32e3bff1ebc385062d1876dd5 From git at git.haskell.org Fri Nov 23 17:35:07 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Nov 2018 17:35:07 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Data family instances working, I think (04ba8f9) Message-ID: <20181123173507.B8B613A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/04ba8f9cfd5674ecdd8306498ce20797455aa283/ghc >--------------------------------------------------------------- commit 04ba8f9cfd5674ecdd8306498ce20797455aa283 Author: Simon Peyton Jones Date: Wed Nov 14 11:36:22 2018 +0000 Data family instances working, I think >--------------------------------------------------------------- 04ba8f9cfd5674ecdd8306498ce20797455aa283 compiler/typecheck/TcInstDcls.hs | 154 +++++++++++++++++++++++++++++++++++++ compiler/typecheck/TcTyClsDecls.hs | 68 ++++++++-------- 2 files changed, 191 insertions(+), 31 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 04ba8f9cfd5674ecdd8306498ce20797455aa283 From git at git.haskell.org Fri Nov 23 17:35:10 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Nov 2018 17:35:10 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Much more progress on tcFamTyPats (08dba31) Message-ID: <20181123173510.BA52C3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/08dba31e8dcde98bafd6b8c6601a16d96aa832f7/ghc >--------------------------------------------------------------- commit 08dba31e8dcde98bafd6b8c6601a16d96aa832f7 Author: Simon Peyton Jones Date: Tue Nov 13 15:36:28 2018 +0000 Much more progress on tcFamTyPats Main thing left to do: data family instances A handful of validate failures Reporting unused binders correctly polykinds/T13985 indexed-types/should_fail/ExplicitForAllFams4a indexed-types/should_fail/ExplicitForAllFams4b extra error (ok) polykinds/T8616 polykinds/T14846 >--------------------------------------------------------------- 08dba31e8dcde98bafd6b8c6601a16d96aa832f7 compiler/prelude/TysPrim.hs | 19 +- compiler/typecheck/TcHsType.hs | 4 +- compiler/typecheck/TcInstDcls.hs | 14 +- compiler/typecheck/TcTyClsDecls.hs | 257 +++++++++------------ compiler/types/Type.hs | 32 ++- .../tests/th/TH_reifyExplicitForAllFams.stderr | 6 +- .../typecheck/should_fail/LevPolyBounded.stderr | 5 + testsuite/tests/typecheck/should_fail/T14607.hs | 2 +- .../tests/typecheck/should_fail/T14607.stderr | 17 +- .../tests/typecheck/should_fail/T6018fail.stderr | 2 +- testsuite/tests/typecheck/should_fail/all.T | 2 +- 11 files changed, 167 insertions(+), 193 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 08dba31e8dcde98bafd6b8c6601a16d96aa832f7 From git at git.haskell.org Fri Nov 23 17:35:13 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Nov 2018 17:35:13 +0000 (UTC) Subject: [commit: ghc] wip/T15809: More progress on reporting unbound variables (588e220) Message-ID: <20181123173513.BD0693A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/588e2203f0646a2f846454333e3f868a29fa76a8/ghc >--------------------------------------------------------------- commit 588e2203f0646a2f846454333e3f868a29fa76a8 Author: Simon Peyton Jones Date: Thu Nov 15 01:16:12 2018 +0000 More progress on reporting unbound variables >--------------------------------------------------------------- 588e2203f0646a2f846454333e3f868a29fa76a8 compiler/typecheck/TcHsType.hs | 16 +- compiler/typecheck/TcInstDcls.hs | 64 ++-- compiler/typecheck/TcTyClsDecls.hs | 352 +++++---------------- compiler/typecheck/TcValidity.hs | 19 +- .../should_fail/ExplicitForAllFams4a.stderr | 6 +- .../should_fail/ExplicitForAllFams4b.stderr | 30 +- testsuite/tests/polykinds/T13985.stderr | 25 +- 7 files changed, 164 insertions(+), 348 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 588e2203f0646a2f846454333e3f868a29fa76a8 From git at git.haskell.org Fri Nov 23 17:35:16 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Nov 2018 17:35:16 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Print tycon arity in -ddump-types (bf5a415) Message-ID: <20181123173516.C79123A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/bf5a415a9ad3719769613d9d46baf51abe995855/ghc >--------------------------------------------------------------- commit bf5a415a9ad3719769613d9d46baf51abe995855 Author: Simon Peyton Jones Date: Wed Nov 14 14:57:08 2018 +0000 Print tycon arity in -ddump-types >--------------------------------------------------------------- bf5a415a9ad3719769613d9d46baf51abe995855 compiler/typecheck/TcRnDriver.hs | 2 +- testsuite/tests/dependent/should_compile/T15743.stderr | 2 +- testsuite/tests/dependent/should_compile/T15743e.stderr | 4 ++-- .../tests/indexed-types/should_compile/T15711.stderr | 4 ++-- .../tests/indexed-types/should_compile/T3017.stderr | 6 +++--- testsuite/tests/partial-sigs/should_compile/ADT.stderr | 2 +- .../should_compile/DataFamilyInstanceLHS.stderr | 4 ++-- .../tests/partial-sigs/should_compile/Meltdown.stderr | 2 +- .../NamedWildcardInDataFamilyInstanceLHS.stderr | 4 ++-- .../NamedWildcardInTypeFamilyInstanceLHS.stderr | 2 +- .../tests/partial-sigs/should_compile/SkipMany.stderr | 2 +- .../should_compile/TypeFamilyInstanceLHS.stderr | 2 +- testsuite/tests/polykinds/T15592.stderr | 2 +- testsuite/tests/polykinds/T15592b.stderr | 4 ++-- testsuite/tests/roles/should_compile/Roles1.stderr | 14 +++++++------- testsuite/tests/roles/should_compile/Roles14.stderr | 2 +- testsuite/tests/roles/should_compile/Roles2.stderr | 4 ++-- testsuite/tests/roles/should_compile/Roles3.stderr | 16 ++++++++-------- testsuite/tests/roles/should_compile/Roles4.stderr | 6 +++--- testsuite/tests/roles/should_compile/T8958.stderr | 6 +++--- testsuite/tests/th/TH_Roles2.stderr | 2 +- testsuite/tests/typecheck/should_compile/T12763.stderr | 2 +- testsuite/tests/typecheck/should_compile/tc231.stderr | 6 +++--- 23 files changed, 50 insertions(+), 50 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc bf5a415a9ad3719769613d9d46baf51abe995855 From git at git.haskell.org Fri Nov 23 17:35:19 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Nov 2018 17:35:19 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Wibbles (49cdbf5) Message-ID: <20181123173519.CA4223A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/49cdbf52a7473fc04518045b1b121d28da3c1556/ghc >--------------------------------------------------------------- commit 49cdbf52a7473fc04518045b1b121d28da3c1556 Author: Simon Peyton Jones Date: Wed Nov 14 17:28:35 2018 +0000 Wibbles >--------------------------------------------------------------- 49cdbf52a7473fc04518045b1b121d28da3c1556 compiler/typecheck/TcHsType.hs | 2 +- compiler/typecheck/TcInstDcls.hs | 188 ++++++++------------------------------- 2 files changed, 36 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 49cdbf52a7473fc04518045b1b121d28da3c1556 From git at git.haskell.org Fri Nov 23 17:35:22 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Nov 2018 17:35:22 +0000 (UTC) Subject: [commit: ghc] wip/T15809: More progress with data instances (1a20fe9) Message-ID: <20181123173522.C025E3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/1a20fe917774d65fcffc5c410b65630ba6eb4977/ghc >--------------------------------------------------------------- commit 1a20fe917774d65fcffc5c410b65630ba6eb4977 Author: Simon Peyton Jones Date: Wed Nov 14 15:25:45 2018 +0000 More progress with data instances Slightly controversially, I adjusted T15725 to have data Sing :: k -> * rather than data Sing :: forall k. k -> * See a fc-call thread. We could revisit this if need be; it's not fundamental to the line of progress. >--------------------------------------------------------------- 1a20fe917774d65fcffc5c410b65630ba6eb4977 compiler/typecheck/TcDeriv.hs | 2 +- compiler/typecheck/TcInstDcls.hs | 1 - compiler/typecheck/TcTyClsDecls.hs | 17 +++++++++++------ testsuite/tests/dependent/should_compile/T15725.hs | 6 +++--- testsuite/tests/ghci/scripts/T10059.stdout | 6 +++--- testsuite/tests/ghci/scripts/ghci059.stdout | 2 +- 6 files changed, 19 insertions(+), 15 deletions(-) diff --git a/compiler/typecheck/TcDeriv.hs b/compiler/typecheck/TcDeriv.hs index 4ee0f23..05c7958 100644 --- a/compiler/typecheck/TcDeriv.hs +++ b/compiler/typecheck/TcDeriv.hs @@ -786,7 +786,7 @@ deriveTyData tvs tc tc_args mb_deriv_strat deriv_pred -- we want to drop type variables from T so that (C d (T a)) is well-kinded let (arg_kinds, _) = splitFunTys cls_arg_kind n_args_to_drop = length arg_kinds - n_args_to_keep = tyConArity tc - n_args_to_drop + n_args_to_keep = length tc_args - n_args_to_drop (tc_args_to_keep, args_to_drop) = splitAt n_args_to_keep tc_args inst_ty_kind = typeKind (mkTyConApp tc tc_args_to_keep) diff --git a/compiler/typecheck/TcInstDcls.hs b/compiler/typecheck/TcInstDcls.hs index 86ed84a..d1081a2 100644 --- a/compiler/typecheck/TcInstDcls.hs +++ b/compiler/typecheck/TcInstDcls.hs @@ -738,7 +738,6 @@ tcDataFamInstDecl mb_clsinfo -- Kind check type patterns ; let exp_bndrs = mb_bndrs `orElse` [] data_ctxt = DataKindCtxt (unLoc fam_name) - ; ; (_, (_, (pats, stupid_theta, res_kind))) <- pushTcLevelM_ $ diff --git a/compiler/typecheck/TcTyClsDecls.hs b/compiler/typecheck/TcTyClsDecls.hs index c8a182a..4de2238 100644 --- a/compiler/typecheck/TcTyClsDecls.hs +++ b/compiler/typecheck/TcTyClsDecls.hs @@ -1485,17 +1485,22 @@ tcFamDecl1 parent (FamilyDecl { fdInfo = fam_info, fdLName = tc_lname@(L _ tc_na { traceTc "data family:" (ppr tc_name) ; checkFamFlag tc_name - -- Check the kind signature, if any. - -- Data families might have a variable return kind. - -- See See Note [Arity of data families] in FamInstEnv. - ; (extra_binders, final_res_kind) <- tcDataKindSig binders res_kind + -- Check that the result kind is OK + -- We allow things like + -- data family T (a :: Type) :: forall k. k -> Type + -- We treat T as having arity 1, but result kind forall k. k -> Type + -- But we want to check that the result kind finishes in + -- Type or a kind-variable + -- For the latter, consider + -- data family D a :: forall k. Type -> k + ; let (_, final_res_kind) = splitPiTys res_kind ; checkTc (tcIsLiftedTypeKind final_res_kind || isJust (tcGetCastedTyVar_maybe final_res_kind)) (badKindSig False res_kind) ; tc_rep_name <- newTyConRepName tc_name - ; let tycon = mkFamilyTyCon tc_name (binders `chkAppend` extra_binders) - final_res_kind + ; let tycon = mkFamilyTyCon tc_name binders + res_kind (resultVariableName sig) (DataFamilyTyCon tc_rep_name) parent NotInjective diff --git a/testsuite/tests/dependent/should_compile/T15725.hs b/testsuite/tests/dependent/should_compile/T15725.hs index a5f259e..1e2e171 100644 --- a/testsuite/tests/dependent/should_compile/T15725.hs +++ b/testsuite/tests/dependent/should_compile/T15725.hs @@ -23,12 +23,12 @@ instance SC Identity ------------------------------------------------------------------------------- -data family Sing :: forall k. k -> Type -data instance Sing :: forall a. Identity a -> Type where +data family Sing :: k -> Type +data instance Sing :: Identity a -> Type where SIdentity :: Sing x -> Sing ('Identity x) newtype Par1 p = Par1 p -data instance Sing :: forall p. Par1 p -> Type where +data instance Sing :: Par1 p -> Type where SPar1 :: Sing x -> Sing ('Par1 x) type family Rep1 (f :: Type -> Type) :: Type -> Type diff --git a/testsuite/tests/ghci/scripts/T10059.stdout b/testsuite/tests/ghci/scripts/T10059.stdout index 92fbb45..955c95a 100644 --- a/testsuite/tests/ghci/scripts/T10059.stdout +++ b/testsuite/tests/ghci/scripts/T10059.stdout @@ -1,4 +1,4 @@ -class (a ~ b) => (~) (a :: k0) (b :: k0) -- Defined in ‘GHC.Types’ -(~) :: k0 -> k0 -> Constraint -class (a GHC.Prim.~# b) => (~) (a :: k0) (b :: k0) +class (a ~ b) => (~) (a :: k) (b :: k) -- Defined in ‘GHC.Types’ +(~) :: k -> k -> Constraint +class (a GHC.Prim.~# b) => (~) (a :: k) (b :: k) -- Defined in ‘GHC.Types’ diff --git a/testsuite/tests/ghci/scripts/ghci059.stdout b/testsuite/tests/ghci/scripts/ghci059.stdout index 9e9adb9..7e734f1 100644 --- a/testsuite/tests/ghci/scripts/ghci059.stdout +++ b/testsuite/tests/ghci/scripts/ghci059.stdout @@ -4,6 +4,6 @@ It is not a class. Please see section 9.14.4 of the user's guide for details. -} type role Coercible representational representational -class Coercible a b => Coercible (a :: k0) (b :: k0) +class Coercible a b => Coercible (a :: k) (b :: k) -- Defined in ‘GHC.Types’ coerce :: Coercible a b => a -> b -- Defined in ‘GHC.Prim’ From git at git.haskell.org Fri Nov 23 17:35:25 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Nov 2018 17:35:25 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Nearly there... (24db669) Message-ID: <20181123173525.C4FF43A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/24db669666e01de6bb52bd5cd8ace9f1602770cd/ghc >--------------------------------------------------------------- commit 24db669666e01de6bb52bd5cd8ace9f1602770cd Author: Simon Peyton Jones Date: Thu Nov 15 17:43:18 2018 +0000 Nearly there... >--------------------------------------------------------------- 24db669666e01de6bb52bd5cd8ace9f1602770cd compiler/typecheck/TcGenDeriv.hs | 8 +- compiler/typecheck/TcHsType.hs | 2 - compiler/typecheck/TcInstDcls.hs | 12 +- compiler/typecheck/TcTyClsDecls.hs | 100 ++-------------- compiler/typecheck/TcValidity.hs | 132 +++++++++++++++++---- testsuite/tests/ghci/scripts/T6018ghcifail.stderr | 2 +- .../should_fail/ExplicitForAllFams4a.stderr | 10 +- .../should_fail/ExplicitForAllFams4b.stderr | 20 ++-- .../indexed-types/should_fail/SimpleFail13.stderr | 2 +- .../indexed-types/should_fail/SimpleFail2a.hs | 12 +- .../indexed-types/should_fail/SimpleFail9.stderr | 4 +- .../tests/indexed-types/should_fail/T7536.stderr | 5 +- testsuite/tests/polykinds/T13985.stderr | 10 +- .../tests/th/TH_reifyExplicitForAllFams.stderr | 6 +- .../tests/typecheck/should_fail/T6018fail.stderr | 4 +- 15 files changed, 168 insertions(+), 161 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 24db669666e01de6bb52bd5cd8ace9f1602770cd From git at git.haskell.org Fri Nov 23 17:35:28 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Nov 2018 17:35:28 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Wibbles (b8b837f) Message-ID: <20181123173528.C2F7D3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/b8b837fe463e67a9bc225ce599564ac4222c159e/ghc >--------------------------------------------------------------- commit b8b837fe463e67a9bc225ce599564ac4222c159e Author: Simon Peyton Jones Date: Mon Nov 19 11:32:56 2018 +0000 Wibbles >--------------------------------------------------------------- b8b837fe463e67a9bc225ce599564ac4222c159e compiler/typecheck/TcTyClsDecls.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/typecheck/TcTyClsDecls.hs b/compiler/typecheck/TcTyClsDecls.hs index 0f8057d..e1c570d 100644 --- a/compiler/typecheck/TcTyClsDecls.hs +++ b/compiler/typecheck/TcTyClsDecls.hs @@ -1879,7 +1879,7 @@ tcFamTyPatsAndGen fam_tc mb_clsinfo imp_vars exp_bndrs hs_pats thing_inside tcFamTyPats :: TyCon -> Maybe ClsInstInfo -> HsTyPats GhcRn -- Patterns -> TcM ([TcType], TcKind) -- (pats, rhs_kind) -tcFamTyPats fam_tc mb_clsinfo hs_pats +tcFamTyPats fam_tc _mb_clsinfo hs_pats = do { traceTc "tcFamTyPats {" $ vcat [ ppr fam_tc <+> dcolon <+> ppr fun_kind , text "arity:" <+> ppr fam_arity @@ -1911,7 +1911,7 @@ tcFamTyPats fam_tc mb_clsinfo hs_pats fun_kind = tyConKind fam_tc lhs_fun = noLoc (HsTyVar noExt NotPromoted (noLoc fam_name)) (invis_bndrs, body_kind) = splitPiTysInvisibleN fam_arity fun_kind - mb_kind_env = thdOf3 <$> mb_clsinfo +-- mb_kind_env = thdOf3 <$> mb_clsinfo bad_lhs fam_app = hang (text "Ill-typed LHS of family instance") From git at git.haskell.org Fri Nov 23 17:35:31 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Nov 2018 17:35:31 +0000 (UTC) Subject: [commit: ghc] wip/T15809: More wibbles (613a4a8) Message-ID: <20181123173531.C27E83A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/613a4a8094de4f489496f342bdff0f3132ad7930/ghc >--------------------------------------------------------------- commit 613a4a8094de4f489496f342bdff0f3132ad7930 Author: Simon Peyton Jones Date: Mon Nov 19 20:45:09 2018 +0000 More wibbles >--------------------------------------------------------------- 613a4a8094de4f489496f342bdff0f3132ad7930 compiler/typecheck/TcTyClsDecls.hs | 62 +++++++++++++++----------------------- 1 file changed, 24 insertions(+), 38 deletions(-) diff --git a/compiler/typecheck/TcTyClsDecls.hs b/compiler/typecheck/TcTyClsDecls.hs index e1c570d..7427035 100644 --- a/compiler/typecheck/TcTyClsDecls.hs +++ b/compiler/typecheck/TcTyClsDecls.hs @@ -67,7 +67,6 @@ import SrcLoc import ListSetOps import DynFlags import Unique -import UniqFM( nonDetEltsUFM ) import ConLike( ConLike(..) ) import BasicTypes import qualified GHC.LanguageExtensions as LangExt @@ -3222,8 +3221,7 @@ checkConsistentFamInst :: Maybe ClsInstInfo checkConsistentFamInst Nothing _ _ = return () checkConsistentFamInst (Just (clas, inst_tvs, mini_env)) fam_tc at_arg_tys = do { traceTc "checkConsistentFamInst" (vcat [ ppr inst_tvs - , ppr kind_prs - , ppr type_prs + , ppr arg_triples , ppr mini_env ]) -- Check that the associated type indeed comes from this class -- See [Mismatched class methods and associated type families] @@ -3231,28 +3229,16 @@ checkConsistentFamInst (Just (clas, inst_tvs, mini_env)) fam_tc at_arg_tys ; checkTc (Just (classTyCon clas) == tyConAssoc_maybe fam_tc) (badATErr (className clas) (tyConName fam_tc)) - -- Check kind args first, suggesting -fprint-explicit-kiinds - -- if there is a mis-match here. - ; checkTc (isJust mb_kinds_match) (pp_wrong_at_arg $$ ppSuggestExplicitKinds) - - -- Then type args. If we do these first, then we'll fail to - -- suggest -fprint-explicit-kinds for (T @k vs T @Type) - ; checkTc (isJust mb_types_match) pp_wrong_at_arg + ; check_match arg_triples } where - kind_prs, type_prs :: [(Type,Type)] - (kind_prs, type_prs) = partitionInvisibles $ - [ ((cls_arg_ty, at_arg_ty), vis) - | (fam_tc_tv, vis, at_arg_ty) - <- zip3 (tyConTyVars fam_tc) - (tyConArgFlags fam_tc at_arg_tys) - at_arg_tys - , Just cls_arg_ty <- [lookupVarEnv mini_env fam_tc_tv] ] - - - mb_types_match = alphaMatchTysX emptyTCvSubst type_prs - Just subst1 = mb_types_match - mb_kinds_match = alphaMatchTysX subst1 kind_prs + arg_triples :: [(Type,Type, ArgFlag)] + arg_triples = [ (cls_arg_ty, at_arg_ty, vis) + | (fam_tc_tv, vis, at_arg_ty) + <- zip3 (tyConTyVars fam_tc) + (tyConArgFlags fam_tc at_arg_tys) + at_arg_tys + , Just cls_arg_ty <- [lookupVarEnv mini_env fam_tc_tv] ] pp_wrong_at_arg = vcat [ text "Type indexes must match class instance head" , text "Expected:" <+> ppr (mkTyConApp fam_tc expected_args) @@ -3263,22 +3249,22 @@ checkConsistentFamInst (Just (clas, inst_tvs, mini_env)) fam_tc at_arg_tys underscore at_tv = mkTyVarTy (mkTyVar tv_name (tyVarKind at_tv)) tv_name = mkInternalName (mkAlphaTyVarUnique 1) (mkTyVarOcc "_") noSrcSpan -alphaMatchTysX :: TCvSubst -> [(Type,Type)] -> Maybe TCvSubst -alphaMatchTysX subst pairs - | null pairs = Just subst - | otherwise = go subst pairs - where - go :: TCvSubst -> [(Type,Type)] -> Maybe TCvSubst - go subst [] - | allDistinctTyVars emptyVarSet $ - nonDetEltsUFM (getTvSubstEnv subst) - = Just subst + check_match :: [(Type,Type, ArgFlag)] -> TcM () + check_match triples = go emptyTCvSubst emptyTCvSubst triples + + go _ _ [] = return () + go lr_subst rl_subst ((ty1,ty2,vis):triples) + | Just lr_subst1 <- tcMatchTyX lr_subst ty1 ty2 + , Just rl_subst1 <- tcMatchTyX rl_subst ty2 ty1 + = go lr_subst1 rl_subst1 triples | otherwise - = Nothing - go subst ((ty1,ty2):prs) - = case tcMatchTyX subst ty1 ty2 of - Just subst' -> go subst' prs - Nothing -> Nothing + = addErrTc (pp_wrong_at_arg $$ + ppWhen (isInvisibleArgFlag vis) ppSuggestExplicitKinds) + -- NB: checks left-to-right, kinds first. + -- If we types first, we'll fail to + -- suggest -fprint-explicit-kinds for a mis-match with + -- T @k vs T @Type + -- somewhere deep inside the type badATErr :: Name -> Name -> SDoc badATErr clas op From git at git.haskell.org Fri Nov 23 17:35:34 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Nov 2018 17:35:34 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Simplify typing of associated family instances (6d3b5bd) Message-ID: <20181123173534.C51FA3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/6d3b5bd9992d579b1787f0ddf401d368fe943c4b/ghc >--------------------------------------------------------------- commit 6d3b5bd9992d579b1787f0ddf401d368fe943c4b Author: Simon Peyton Jones Date: Mon Nov 19 08:19:14 2018 +0000 Simplify typing of associated family instances This experimental patch simplifies the treatment of assocaited family instances, by - Treating them entirely independently from their enclosing class-instance declaration - Making a separate check (checkConsistentFamInst) that the instance(s) match the class-instance decl This makes two or three testsuite cases fail -- but I think that's a feature not bug! This is on my wip/T15809 branch >--------------------------------------------------------------- 6d3b5bd9992d579b1787f0ddf401d368fe943c4b compiler/typecheck/TcTyClsDecls.hs | 136 +++++++++++++++++-------------------- 1 file changed, 64 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 6d3b5bd9992d579b1787f0ddf401d368fe943c4b From git at git.haskell.org Fri Nov 23 17:35:37 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Nov 2018 17:35:37 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Wibble, to fix build (2d7a153) Message-ID: <20181123173537.BAEF63A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/2d7a1532cf0a36dc6dde9f05b3ad9ba4b762b3b1/ghc >--------------------------------------------------------------- commit 2d7a1532cf0a36dc6dde9f05b3ad9ba4b762b3b1 Author: Simon Peyton Jones Date: Wed Nov 21 13:55:54 2018 +0000 Wibble, to fix build >--------------------------------------------------------------- 2d7a1532cf0a36dc6dde9f05b3ad9ba4b762b3b1 compiler/typecheck/TcTyClsDecls.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/typecheck/TcTyClsDecls.hs b/compiler/typecheck/TcTyClsDecls.hs index 7a8bc9e..1fc675c 100644 --- a/compiler/typecheck/TcTyClsDecls.hs +++ b/compiler/typecheck/TcTyClsDecls.hs @@ -1769,7 +1769,7 @@ tcTyFamInstEqn fam_tc mb_clsinfo ; (qtvs, pats, rhs_ty) <- tcFamTyPatsAndGen fam_tc mb_clsinfo imp_vars (mb_expl_bndrs `orElse` []) hs_pats - (tcCheckLHsType rhs_hs_ty res_kind) + (tcCheckLHsType rhs_hs_ty) ; (ze, qtvs') <- zonkTyBndrs qtvs ; pats' <- zonkTcTypesToTypesX ze pats From git at git.haskell.org Fri Nov 23 17:35:40 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Nov 2018 17:35:40 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Finally, validate-clean (b24cdb3) Message-ID: <20181123173540.BFF183A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/b24cdb306acad4ade62ba78c3bbd172286990495/ghc >--------------------------------------------------------------- commit b24cdb306acad4ade62ba78c3bbd172286990495 Author: Simon Peyton Jones Date: Fri Nov 16 12:03:59 2018 +0000 Finally, validate-clean Except for polykinds/T14846, where there is an extra error message. I actually tnink it's correct, but have not checked yet. >--------------------------------------------------------------- b24cdb306acad4ade62ba78c3bbd172286990495 compiler/typecheck/TcBinds.hs | 24 ---- compiler/typecheck/TcClassDcl.hs | 3 - compiler/typecheck/TcDeriv.hs | 3 - compiler/typecheck/TcEnv.hs | 8 -- compiler/typecheck/TcHsType.hs | 87 +++++++++----- compiler/typecheck/TcInstDcls.hs | 81 ++++++------- compiler/typecheck/TcPat.hs | 2 +- compiler/typecheck/TcTyClsDecls.hs | 132 +++++++++++++-------- compiler/types/TyCoRep.hs | 7 +- .../indexed-types/should_fail/SimpleFail9.stderr | 2 +- .../tests/indexed-types/should_fail/T10817.stderr | 9 +- .../tests/indexed-types/should_fail/T10899.stderr | 3 +- testsuite/tests/polykinds/T8616.stderr | 9 ++ testsuite/tests/printer/Ppr040.hs | 10 +- 14 files changed, 202 insertions(+), 178 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 b24cdb306acad4ade62ba78c3bbd172286990495 From git at git.haskell.org Fri Nov 23 17:35:43 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Nov 2018 17:35:43 +0000 (UTC) Subject: [commit: ghc] wip/T15809: More progress in tcFamTyPats (ae4e5d9) Message-ID: <20181123173543.C3D343A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/ae4e5d9cebe70efda03fa03b963e0237b0aadb49/ghc >--------------------------------------------------------------- commit ae4e5d9cebe70efda03fa03b963e0237b0aadb49 Author: Simon Peyton Jones Date: Tue Nov 20 16:36:06 2018 +0000 More progress in tcFamTyPats In particular, revert to taking account of the class instance types in tcFamTyPats, but by unification rather than by messing with tcInferApps >--------------------------------------------------------------- ae4e5d9cebe70efda03fa03b963e0237b0aadb49 compiler/typecheck/Inst.hs | 31 ++++++++++++------ compiler/typecheck/TcHsType.hs | 54 +++++++------------------------- compiler/typecheck/TcTyClsDecls.hs | 64 +++++++++++++++++++++++++++----------- compiler/types/Type.hs | 15 ++++++++- 4 files changed, 92 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 ae4e5d9cebe70efda03fa03b963e0237b0aadb49 From git at git.haskell.org Fri Nov 23 17:35:46 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Nov 2018 17:35:46 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Better validity checks, simplification (3915172) Message-ID: <20181123173546.CB7723A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/39151721cab828343071460f3de8c8f170e0311f/ghc >--------------------------------------------------------------- commit 39151721cab828343071460f3de8c8f170e0311f Author: Simon Peyton Jones Date: Thu Nov 15 23:29:34 2018 +0000 Better validity checks, simplification >--------------------------------------------------------------- 39151721cab828343071460f3de8c8f170e0311f compiler/typecheck/TcGenDeriv.hs | 3 +- compiler/typecheck/TcHsType.hs | 66 +++--- compiler/typecheck/TcInstDcls.hs | 43 +++- compiler/typecheck/TcTyClsDecls.hs | 223 ++++++++++++++++++- compiler/typecheck/TcValidity.hs | 239 ++------------------- .../should_fail/ExplicitForAllFams4b.stderr | 63 ++++-- .../indexed-types/should_fail/SimpleFail2a.stderr | 2 +- .../tests/indexed-types/should_fail/T14045a.stderr | 2 +- testsuite/tests/polykinds/T13985.hs | 1 + testsuite/tests/polykinds/T13985.stderr | 10 +- 10 files changed, 338 insertions(+), 314 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 39151721cab828343071460f3de8c8f170e0311f From git at git.haskell.org Fri Nov 23 17:35:49 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Nov 2018 17:35:49 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Wibbles (bd34111) Message-ID: <20181123173549.C2D3C3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/bd34111a7b0a9168a442aaa4e8de6db4daffeeb6/ghc >--------------------------------------------------------------- commit bd34111a7b0a9168a442aaa4e8de6db4daffeeb6 Author: Simon Peyton Jones Date: Wed Nov 21 00:00:53 2018 +0000 Wibbles >--------------------------------------------------------------- bd34111a7b0a9168a442aaa4e8de6db4daffeeb6 compiler/typecheck/TcMType.hs | 15 +++++++++++++ compiler/typecheck/TcRnTypes.hs | 8 ++++++- compiler/typecheck/TcTyClsDecls.hs | 25 +++++++++++----------- .../tests/indexed-types/should_fail/SimpleFail9.hs | 4 +++- 4 files changed, 37 insertions(+), 15 deletions(-) diff --git a/compiler/typecheck/TcMType.hs b/compiler/typecheck/TcMType.hs index 886a894..769a312 100644 --- a/compiler/typecheck/TcMType.hs +++ b/compiler/typecheck/TcMType.hs @@ -41,6 +41,7 @@ module TcMType ( newEvVar, newEvVars, newDict, newWanted, newWanteds, newHoleCt, cloneWanted, cloneWC, emitWanted, emitWantedEq, emitWantedEvVar, emitWantedEvVars, + emitDerivedEqs, newTcEvBinds, newNoTcEvBinds, addTcEvBind, newCoercionHole, fillCoercionHole, isFilledCoercionHole, @@ -232,6 +233,20 @@ emitWanted origin pty ; emitSimple $ mkNonCanonical ev ; return $ ctEvTerm ev } +emitDerivedEqs :: CtOrigin -> [(TcType,TcType)] -> TcM () +-- Emit some new derived nominal equalities +emitDerivedEqs origin pairs + | null pairs + = return () + | otherwise + = do { loc <- getCtLocM origin Nothing + ; emitSimples (listToBag (map (mk_one loc) pairs)) } + where + mk_one loc (ty1, ty2) + = mkNonCanonical $ + CtDerived { ctev_pred = mkPrimEqPred ty1 ty2 + , ctev_loc = loc } + -- | Emits a new equality constraint emitWantedEq :: CtOrigin -> TypeOrKind -> Role -> TcType -> TcType -> TcM Coercion emitWantedEq origin t_or_k role ty1 ty2 diff --git a/compiler/typecheck/TcRnTypes.hs b/compiler/typecheck/TcRnTypes.hs index f7caacd..ad3122b 100644 --- a/compiler/typecheck/TcRnTypes.hs +++ b/compiler/typecheck/TcRnTypes.hs @@ -3511,8 +3511,10 @@ data CtOrigin | NegateOrigin -- Occurrence of syntactic negation | ArithSeqOrigin (ArithSeqInfo GhcRn) -- [x..], [x..y] etc + | AssocFamPatOrigin -- When matching the patterns of an associated + -- family instance with that of its parent class | SectionOrigin - | TupleOrigin -- (..,..) + | TupleOrigin -- (..,..) | ExprSigOrigin -- e :: ty | PatSigOrigin -- p :: ty | PatOrigin -- Instantiating a polytyped pattern at a constructor @@ -3730,6 +3732,9 @@ pprCtOrigin (KindEqOrigin t1 (Just t2) _ _) = hang (ctoHerald <+> text "a kind equality arising from") 2 (sep [ppr t1, char '~', ppr t2]) +pprCtOrigin AssocFamPatOrigin + = text "when matching a family LHS with its class instance head" + pprCtOrigin (KindEqOrigin t1 Nothing _ _) = hang (ctoHerald <+> text "a kind equality when matching") 2 (ppr t1) @@ -3801,6 +3806,7 @@ pprCtO IfOrigin = text "an if expression" pprCtO (LiteralOrigin lit) = hsep [text "the literal", quotes (ppr lit)] pprCtO (ArithSeqOrigin seq) = hsep [text "the arithmetic sequence", quotes (ppr seq)] pprCtO SectionOrigin = text "an operator section" +pprCtO AssocFamPatOrigin = text "the LHS of a famly instance" pprCtO TupleOrigin = text "a tuple" pprCtO NegateOrigin = text "a use of syntactic negation" pprCtO (ScOrigin n) = text "the superclasses of an instance declaration" diff --git a/compiler/typecheck/TcTyClsDecls.hs b/compiler/typecheck/TcTyClsDecls.hs index 92977fb..7a8bc9e 100644 --- a/compiler/typecheck/TcTyClsDecls.hs +++ b/compiler/typecheck/TcTyClsDecls.hs @@ -39,7 +39,6 @@ import TcDeriv (DerivInfo) import TcHsType import Inst( tcInstTyBinders ) import TcMType -import TcUnify( unifyType ) import TysWiredIn ( unitTy ) import TcType import RnEnv( lookupConstructorFields ) @@ -1770,9 +1769,7 @@ tcTyFamInstEqn fam_tc mb_clsinfo ; (qtvs, pats, rhs_ty) <- tcFamTyPatsAndGen fam_tc mb_clsinfo imp_vars (mb_expl_bndrs `orElse` []) hs_pats - (\ res_kind -> - do { traceTc "tcTyFasmInstEqn" (ppr fam_tc $$ ppr hs_pats $$ ppr res_kind) - ; tcCheckLHsType rhs_hs_ty res_kind }) + (tcCheckLHsType rhs_hs_ty res_kind) ; (ze, qtvs') <- zonkTyBndrs qtvs ; pats' <- zonkTcTypesToTypesX ze pats @@ -1932,16 +1929,19 @@ addConsistencyConstraints :: Maybe ClsInstInfo -> TyCon -> [Type] -> TcM () -- F c x y a :: Type -- Here the first arg of F should be the same as the third of C -- and the fourth arg of F should be the same as the first of C - +-- +-- We emit /Derived/ constraints (a bit like fundeps) to encourage +-- unification to happen, but without actually reporting errors. +-- If, despite the efforts, corresponding positions do not match, +-- checkConsistentFamInst will complain addConsistencyConstraints Nothing _ _ = return () addConsistencyConstraints (Just (_, _, inst_ty_env)) fam_tc pats - = mapM_ do_one (tyConTyVars fam_tc `zip` pats) - where - do_one (fam_tc_tv, pat) - | Just cls_arg_ty <- lookupVarEnv inst_ty_env fam_tc_tv - = discardResult (unifyType Nothing cls_arg_ty pat) - | otherwise - = return () + = emitDerivedEqs AssocFamPatOrigin + [ (cls_ty, pat) + | (fam_tc_tv, pat) <- tyConTyVars fam_tc `zip` pats + , Just cls_ty <- [lookupVarEnv inst_ty_env fam_tc_tv] ] + -- Improve inference + -- Any mis-match is reports by checkConsistentFamInst {- Note [Constraints in patterns] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -3237,7 +3237,6 @@ checkFamFlag tc_name -- types. type ClsInstInfo = (Class, [TyVar], VarEnv Type) - checkConsistentFamInst :: Maybe ClsInstInfo -> TyCon -- ^ Family tycon -> [Type] -- ^ Type patterns from instance diff --git a/testsuite/tests/indexed-types/should_fail/SimpleFail9.hs b/testsuite/tests/indexed-types/should_fail/SimpleFail9.hs index 9c1c4a8..0f20f78 100644 --- a/testsuite/tests/indexed-types/should_fail/SimpleFail9.hs +++ b/testsuite/tests/indexed-types/should_fail/SimpleFail9.hs @@ -2,8 +2,10 @@ module ShouldFail where +import Data.Kind + class C7 a b where - data S7 b :: * + data S7 b :: Type instance C7 Char (a, Bool) where data S7 (a, Bool) = S7_1 From git at git.haskell.org Fri Nov 23 17:35:52 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Nov 2018 17:35:52 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Yet more on family-instance checking (e584a5b) Message-ID: <20181123173552.D36923A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/e584a5bd5ed7260bc27c06e0365075e13eed8a5e/ghc >--------------------------------------------------------------- commit e584a5bd5ed7260bc27c06e0365075e13eed8a5e Author: Simon Peyton Jones Date: Thu Nov 22 14:24:28 2018 +0000 Yet more on family-instance checking Following conversation with Richard yesterday. Very close now. Comments to be written. >--------------------------------------------------------------- e584a5bd5ed7260bc27c06e0365075e13eed8a5e compiler/hsSyn/HsDecls.hs | 57 +++---- compiler/hsSyn/HsTypes.hs | 69 ++++---- compiler/nativeGen/CFG.hs | 1 - compiler/parser/RdrHsSyn.hs | 8 +- compiler/typecheck/Inst.hs | 2 +- compiler/typecheck/TcHsType.hs | 5 +- compiler/typecheck/TcInstDcls.hs | 125 ++++++++------- compiler/typecheck/TcMType.hs | 155 +++++++++--------- compiler/typecheck/TcSigs.hs | 21 +-- compiler/typecheck/TcTyClsDecls.hs | 173 +++++++++++++-------- compiler/types/Unify.hs | 43 +++-- .../should_fail/ExplicitForAllFams4b.hs | 1 + .../should_fail/ExplicitForAllFams4b.stderr | 54 +++++-- .../indexed-types/should_fail/SimpleFail9.stderr | 2 +- .../tests/indexed-types/should_fail/T12041.stderr | 11 +- .../tests/indexed-types/should_fail/T13972.hs | 6 + .../tests/indexed-types/should_fail/T13972.stderr | 7 - .../tests/indexed-types/should_fail/T14045a.hs | 5 + .../tests/indexed-types/should_fail/T14045a.stderr | 7 - testsuite/tests/indexed-types/should_fail/T9160.hs | 1 + .../tests/indexed-types/should_fail/T9160.stderr | 13 +- testsuite/tests/indexed-types/should_fail/all.T | 4 +- .../tests/partial-sigs/should_fail/T14040a.stderr | 8 +- testsuite/tests/polykinds/T14450.stderr | 12 +- testsuite/tests/polykinds/T14846.stderr | 36 +++-- 25 files changed, 446 insertions(+), 380 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 e584a5bd5ed7260bc27c06e0365075e13eed8a5e From git at git.haskell.org Fri Nov 23 17:35:55 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Nov 2018 17:35:55 +0000 (UTC) Subject: [commit: ghc] wip/T15809: More wibbles on checkConsistentFamInst (2280651) Message-ID: <20181123173555.DD4F23A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/2280651d3bff0e90ecf4151776a1447531179091/ghc >--------------------------------------------------------------- commit 2280651d3bff0e90ecf4151776a1447531179091 Author: Simon Peyton Jones Date: Fri Nov 23 11:55:48 2018 +0000 More wibbles on checkConsistentFamInst >--------------------------------------------------------------- 2280651d3bff0e90ecf4151776a1447531179091 compiler/typecheck/TcDeriv.hs | 28 ++++++------- compiler/typecheck/TcHsType.hs | 80 ++++++++++++++++++++++++-------------- compiler/typecheck/TcInstDcls.hs | 18 +++++---- compiler/typecheck/TcTyClsDecls.hs | 9 ++--- compiler/typecheck/TcValidity.hs | 7 ++-- compiler/types/TyCoRep.hs | 2 +- compiler/types/Type.hs | 15 ++----- compiler/utils/Util.hs | 8 +++- 8 files changed, 94 insertions(+), 73 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 2280651d3bff0e90ecf4151776a1447531179091 From git at git.haskell.org Fri Nov 23 17:35:58 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Nov 2018 17:35:58 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Wibbles to checkConsistentFamInst (a8e101f) Message-ID: <20181123173558.DBC243A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/a8e101f2678a0a97179a624ae9d077c11d8e17d2/ghc >--------------------------------------------------------------- commit a8e101f2678a0a97179a624ae9d077c11d8e17d2 Author: Simon Peyton Jones Date: Fri Nov 23 08:31:22 2018 +0000 Wibbles to checkConsistentFamInst >--------------------------------------------------------------- a8e101f2678a0a97179a624ae9d077c11d8e17d2 compiler/typecheck/TcInstDcls.hs | 27 +++++++++-------- compiler/typecheck/TcTyClsDecls.hs | 62 +++++++++++++++++++++++++------------- 2 files changed, 55 insertions(+), 34 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc a8e101f2678a0a97179a624ae9d077c11d8e17d2 From git at git.haskell.org Fri Nov 23 17:36:01 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Nov 2018 17:36:01 +0000 (UTC) Subject: [commit: ghc] wip/T15809: More wibbles (9d91611) Message-ID: <20181123173601.E63DB3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/9d91611a5736a312d7b22fb4b91a1b99d9682b14/ghc >--------------------------------------------------------------- commit 9d91611a5736a312d7b22fb4b91a1b99d9682b14 Author: Simon Peyton Jones Date: Fri Nov 23 17:33:19 2018 +0000 More wibbles Plus rebased onto master >--------------------------------------------------------------- 9d91611a5736a312d7b22fb4b91a1b99d9682b14 compiler/hsSyn/HsTypes.hs | 1 - compiler/typecheck/TcDeriv.hs | 23 ++++++++++++++-- compiler/typecheck/TcHsType.hs | 6 ++--- compiler/typecheck/TcInstDcls.hs | 40 ++++++++++++++++++++------- compiler/typecheck/TcTyClsDecls.hs | 55 ++++++++++++++++++++------------------ compiler/types/TyCoRep.hs | 6 ++++- compiler/types/Type.hs | 3 ++- 7 files changed, 90 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 9d91611a5736a312d7b22fb4b91a1b99d9682b14 From git at git.haskell.org Fri Nov 23 17:36:04 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Nov 2018 17:36:04 +0000 (UTC) Subject: [commit: ghc] wip/T15809's head updated: More wibbles (9d91611) Message-ID: <20181123173604.757D03A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/T15809' now includes: 7e57067 eventlog: Log the current stack size when stack overflows cc615c6 hadrian: make it possible to run the testsuite with quickest and quick 47bbc70 Don't track free variables in STG syntax by default d13b7d6 Remove redundant check in cgCase 691aa71 Fix heap corruption during stable name allocation 4343d5a another minor refactoring 8707911 Minor performance optimisation f5fbecc users guide: We no longer build libraries with -split-objs 13bb4bf Rename literal constructors 011e39d Fix GhostScript detection (Trac #15856) 4ba3fa3 base: Mention openFile throwing does-not-exist-errors on FIFOs ea01517 Add test for #15437 86f6890 rts/M32Alloc: Abort if m32 linker mmap fails 06a09a5 rts: Fix bss initialization on Windows 67277e7 testuite: update more windows tests outputs 6c26b3f Fixup the new code layout patch for SplitObjs. 7cba71f Don't reverse explicit export lists during renaming 676f1f2 rts: fix Windows megablock allocator 19ffddc Hadrian: work around Cabal's/GHC's different Arch/OS strings 561748c rts.cabal.in: force inclusion of findPtr/_findPtr symbol only with debug flag 1f74f7d plugins10 no longer broken f088c2d Fix deadlock bug when mkFastStringWith is duplicated 599eaad Load plugins in interactive session 390df8b Fix uninformative hp2ps error when the cmdline contains double quotes 66f0056 Refactor TcRnMonad.mapAndRecoverM 014d6c1 Fix #15852 by eta expanding data family instance RHSes, too f2d9fb0 Calling gcc: Pass optc flags as last options (#14452) 699e507 Remove warnings-silencing flags for code generated by Alex ff61955 Hadrian: Misc. fixes in Haddock rules f5d2083 Overhaul -fprint-explicit-kinds to use VKA 35a8977 UNREG: PprC: Add support for adjacent floats d0fc761 llvmGen: Eliminate duplicate definition 3584bd4 circleci: Actually build with in-tree GMP on Darwin 9e0a23b rts/MachO: Add a bit more debugging output to getNames b2f6f89 rts/MachO: A bit of refactoring in ocGetNames 2548908 rts/MachO: Iterate through N (all) symbols, not M external symbols 9f3e22b LLVM: Use generic code for small size quot-rem ops a1bbb56 Doc-only fixes 5aa2923 'DynFlag'-free version of 'mkParserFlags' d2fbc33 Simplify 'ExtBits' in the lexer 8d008b7 Don't pass -no-pie when -pgmc is supplied 6353efc Fix unused-import warnings 9b0d033 Use handy shortcut llvm_ways 7856676 Typofix in help text 4e42a78 Tc-tracing, and order of arguments only 2828e18 WIP on using level numbers for generalisation 5b84cbf More progress on using level numbers for gen 1d39ab2 Further work on TyCon generalisation 1a7a425 Further progress 1a1e6c8 More progress ee11207 More progress 8a932d0 More progress 1eddbc2 Comemnts only bb8c97a Finally done 8be7e73 Comments and alpha-renaming 2f86a8d Comments only 9c02610 Progress f2fe11a Combine kcImplicitTKBndrs and tcImplicitTKBndrs 7a4f383 Get rid of kcLHsQTyVarBndrs 584cdfc Start to eliminate tcFamTyPats 196b4a0 More progress on tcFamTyPats d5b27c7 Wibbles 08dba31 Much more progress on tcFamTyPats 04ba8f9 Data family instances working, I think bf5a415 Print tycon arity in -ddump-types 1a20fe9 More progress with data instances 49cdbf5 Wibbles 588e220 More progress on reporting unbound variables 24db669 Nearly there... 3915172 Better validity checks, simplification b24cdb3 Finally, validate-clean 6d3b5bd Simplify typing of associated family instances b8b837f Wibbles 613a4a8 More wibbles ae4e5d9 More progress in tcFamTyPats bd34111 Wibbles 2d7a153 Wibble, to fix build e584a5b Yet more on family-instance checking a8e101f Wibbles to checkConsistentFamInst 2280651 More wibbles on checkConsistentFamInst 9d91611 More wibbles From git at git.haskell.org Fri Nov 23 19:38:50 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Nov 2018 19:38:50 +0000 (UTC) Subject: [commit: ghc] master: configure: Use LLVM 7.0 (929363b) Message-ID: <20181123193850.45C593A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/929363b7454f8ec843908514f7e3c3da1666b000/ghc >--------------------------------------------------------------- commit 929363b7454f8ec843908514f7e3c3da1666b000 Author: Ben Gamari Date: Thu Nov 22 16:07:49 2018 -0500 configure: Use LLVM 7.0 >--------------------------------------------------------------- 929363b7454f8ec843908514f7e3c3da1666b000 configure.ac | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/configure.ac b/configure.ac index 0b65770..5ae1c6a 100644 --- a/configure.ac +++ b/configure.ac @@ -643,7 +643,7 @@ AC_SUBST([LibtoolCmd]) # tools we are looking for. In the past, GHC supported a number of # versions of LLVM simultaneously, but that stopped working around # 3.5/3.6 release of LLVM. -LlvmVersion=6.0 +LlvmVersion=7.0 AC_SUBST([LlvmVersion]) sUPPORTED_LLVM_VERSION=$(echo \($LlvmVersion\) | sed 's/\./,/') AC_DEFINE_UNQUOTED([sUPPORTED_LLVM_VERSION], ${sUPPORTED_LLVM_VERSION}, [The supported LLVM version number]) From git at git.haskell.org Fri Nov 23 19:39:05 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Nov 2018 19:39:05 +0000 (UTC) Subject: [commit: ghc] master: distrib/configure: Set RanlibCmd (0a126a3) Message-ID: <20181123193905.74B7F3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/0a126a32d1bbdb3bb70030a77e01415e19ea8b6e/ghc >--------------------------------------------------------------- commit 0a126a32d1bbdb3bb70030a77e01415e19ea8b6e Author: Ben Gamari Date: Wed Nov 7 21:02:19 2018 -0500 distrib/configure: Set RanlibCmd This fixes #15875. >--------------------------------------------------------------- 0a126a32d1bbdb3bb70030a77e01415e19ea8b6e distrib/configure.ac.in | 2 ++ 1 file changed, 2 insertions(+) diff --git a/distrib/configure.ac.in b/distrib/configure.ac.in index ed1c296..e064a5d 100644 --- a/distrib/configure.ac.in +++ b/distrib/configure.ac.in @@ -187,6 +187,8 @@ dnl ** how to invoke `ar' and `ranlib' # FP_PROG_AR_SUPPORTS_ATFILE FP_PROG_AR_NEEDS_RANLIB +RanlibCmd="$RANLIB" +AC_SUBST([RanlibCmd]) dnl ** Have libdw? dnl -------------------------------------------------------------- From git at git.haskell.org Fri Nov 23 19:39:20 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Nov 2018 19:39:20 +0000 (UTC) Subject: [commit: ghc] master: users guide: Clarify meanings of -g flags (937d484) Message-ID: <20181123193920.A799E3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/937d4847400ab70248b12f644a06d14726048c52/ghc >--------------------------------------------------------------- commit 937d4847400ab70248b12f644a06d14726048c52 Author: Ben Gamari Date: Thu Nov 22 17:20:40 2018 -0500 users guide: Clarify meanings of -g flags >--------------------------------------------------------------- 937d4847400ab70248b12f644a06d14726048c52 docs/users_guide/debug-info.rst | 12 +++++++++--- 1 file changed, 9 insertions(+), 3 deletions(-) diff --git a/docs/users_guide/debug-info.rst b/docs/users_guide/debug-info.rst index ecda4af..91ea073 100644 --- a/docs/users_guide/debug-info.rst +++ b/docs/users_guide/debug-info.rst @@ -17,9 +17,15 @@ useable by most UNIX debugging tools. Emit debug information in object code. Currently only DWARF debug information is supported on x86-64 and i386. Currently debug levels 0 - through 3 are accepted, with 0 disabling debug information production - and higher numbers producing richer output. If ⟨n⟩ is omitted, level 2 - is assumed. + through 3 are accepted: + + * ``-g0``: no debug information produced + * ``-g1``: produces stack unwinding records for top-level functions (sufficient for basic backtraces) + * ``-g2``: produces stack unwinding records for top-level functions as well + as inner blocks (allowing more precise backtraces than with ``-g1``). + * ``-g3``: same as ``-g2``. + + If ⟨n⟩ is omitted, level 2 is assumed. Tutorial From git at git.haskell.org Fri Nov 23 19:39:35 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Nov 2018 19:39:35 +0000 (UTC) Subject: [commit: ghc] master: Bump containers submodule (ee03ac4) Message-ID: <20181123193935.878663A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ee03ac4cd6cefd562453ff43dd1311a3ce7e73fe/ghc >--------------------------------------------------------------- commit ee03ac4cd6cefd562453ff43dd1311a3ce7e73fe Author: Ben Gamari Date: Fri Nov 23 12:30:13 2018 -0500 Bump containers submodule >--------------------------------------------------------------- ee03ac4cd6cefd562453ff43dd1311a3ce7e73fe libraries/containers | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/containers b/libraries/containers index e5b3bba..03dcb28 160000 --- a/libraries/containers +++ b/libraries/containers @@ -1 +1 @@ -Subproject commit e5b3bbaeb79cbf3a2c99bd14257d4199cc651b73 +Subproject commit 03dcb287c96613ceb1f64d5d5a82f7b94b879268 From git at git.haskell.org Fri Nov 23 19:39:50 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Nov 2018 19:39:50 +0000 (UTC) Subject: [commit: ghc] master: Bump text submodule (c2be6d5) Message-ID: <20181123193950.8EFE03A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/c2be6d5e9a7137aa480874fe0929f12264860c6e/ghc >--------------------------------------------------------------- commit c2be6d5e9a7137aa480874fe0929f12264860c6e Author: Ben Gamari Date: Fri Nov 23 12:32:09 2018 -0500 Bump text submodule >--------------------------------------------------------------- c2be6d5e9a7137aa480874fe0929f12264860c6e libraries/text | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/libraries/text b/libraries/text index 44ec2ce..69d625b 160000 --- a/libraries/text +++ b/libraries/text @@ -1 +1 @@ -Subproject commit 44ec2cee65e5326ed943370e424f60d4ae6206d1 +Subproject commit 69d625b9caa34fd8b384a4599ee98f5f53f20fbb From git at git.haskell.org Fri Nov 23 19:40:06 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Nov 2018 19:40:06 +0000 (UTC) Subject: [commit: ghc] master: Revert "Simplify 'ExtBits' in the lexer" (f61f71c) Message-ID: <20181123194006.6DA7B3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f61f71c48e2f1aec8999b632bc5722391a42d036/ghc >--------------------------------------------------------------- commit f61f71c48e2f1aec8999b632bc5722391a42d036 Author: Ben Gamari Date: Fri Nov 23 14:09:28 2018 -0500 Revert "Simplify 'ExtBits' in the lexer" This reverts commit d2fbc33c4ff3074126ab71654af8bbf8a46e4e11. >--------------------------------------------------------------- f61f71c48e2f1aec8999b632bc5722391a42d036 compiler/parser/Lexer.x | 498 +++++++++++++++++++++++++------------------- compiler/parser/Parser.y | 14 +- compiler/parser/RdrHsSyn.hs | 32 +-- 3 files changed, 306 insertions(+), 238 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 f61f71c48e2f1aec8999b632bc5722391a42d036 From git at git.haskell.org Fri Nov 23 19:40:22 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 23 Nov 2018 19:40:22 +0000 (UTC) Subject: [commit: ghc] master: Revert "'DynFlag'-free version of 'mkParserFlags'" (7e7e846) Message-ID: <20181123194022.0B7B13A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/7e7e846b8c86dbf7ba98933a346442416d17c784/ghc >--------------------------------------------------------------- commit 7e7e846b8c86dbf7ba98933a346442416d17c784 Author: Ben Gamari Date: Fri Nov 23 14:09:30 2018 -0500 Revert "'DynFlag'-free version of 'mkParserFlags'" This reverts commit 5aa29231ab7603537284eff5e4caff3a73dba6d2. >--------------------------------------------------------------- 7e7e846b8c86dbf7ba98933a346442416d17c784 compiler/parser/Lexer.x | 106 ++++++++++++++++---------------------------- compiler/parser/Parser.y | 10 +++-- compiler/parser/RdrHsSyn.hs | 22 ++++----- 3 files changed, 55 insertions(+), 83 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 7e7e846b8c86dbf7ba98933a346442416d17c784 From git at git.haskell.org Sat Nov 24 09:09:43 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 24 Nov 2018 09:09:43 +0000 (UTC) Subject: [commit: ghc] master: Fix unused import warning (ad2d761) Message-ID: <20181124090943.AC97B3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/ad2d7612dbdf0e928318394ec0606da3b85a8837/ghc >--------------------------------------------------------------- commit ad2d7612dbdf0e928318394ec0606da3b85a8837 Author: = <=> Date: Sat Nov 24 11:08:36 2018 +0200 Fix unused import warning Presumably introduced by new unused import checker. >--------------------------------------------------------------- ad2d7612dbdf0e928318394ec0606da3b85a8837 compiler/simplStg/StgLiftLams/LiftM.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/compiler/simplStg/StgLiftLams/LiftM.hs b/compiler/simplStg/StgLiftLams/LiftM.hs index c9e520a..c024956 100644 --- a/compiler/simplStg/StgLiftLams/LiftM.hs +++ b/compiler/simplStg/StgLiftLams/LiftM.hs @@ -47,7 +47,6 @@ import Control.Monad.Trans.RWS.Strict ( RWST, runRWST ) import qualified Control.Monad.Trans.RWS.Strict as RWS import Control.Monad.Trans.Cont ( ContT (..) ) import Data.ByteString ( ByteString ) -import Data.List ( foldl' ) -- | @uncurry 'mkStgBinding' . 'decomposeStgBinding' = id@ decomposeStgBinding :: GenStgBinding pass -> (RecFlag, [(BinderP pass, GenStgRhs pass)]) From git at git.haskell.org Sat Nov 24 10:30:47 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 24 Nov 2018 10:30:47 +0000 (UTC) Subject: [commit: ghc] master: [TTG: Handling Source Locations] Foundation and Pat (509d5be) Message-ID: <20181124103047.7B3853A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/509d5be69c7507ba5d0a5f39ffd1613a59e73eea/ghc >--------------------------------------------------------------- commit 509d5be69c7507ba5d0a5f39ffd1613a59e73eea Author: Shayan-Najd Date: Thu Nov 22 01:23:29 2018 +0000 [TTG: Handling Source Locations] Foundation and Pat This patch removes the ping-pong style from HsPat (only, for now), using the plan laid out at https://ghc.haskell.org/trac/ghc/wiki/ImplementingTreesThatGrow/HandlingSourceLocations (solution A). - the class `HasSrcSpan`, and its functions (e.g., `cL` and `dL`), are introduced - some instances of `HasSrcSpan` are introduced - some constructors `L` are replaced with `cL` - some patterns `L` are replaced with `dL->L` view pattern - some type annotation are necessarily updated (e.g., `Pat p` --> `Pat (GhcPass p)`) Phab diff: D5036 Trac Issues #15495 Updates haddock submodule >--------------------------------------------------------------- 509d5be69c7507ba5d0a5f39ffd1613a59e73eea compiler/basicTypes/Name.hs | 11 +- compiler/basicTypes/SrcLoc.hs | 132 ++++- compiler/deSugar/Check.hs | 34 +- compiler/deSugar/Coverage.hs | 149 ++--- compiler/deSugar/Desugar.hs | 17 +- compiler/deSugar/DsArrows.hs | 123 ++-- compiler/deSugar/DsBinds.hs | 16 +- compiler/deSugar/DsExpr.hs | 69 +-- compiler/deSugar/DsForeign.hs | 9 +- compiler/deSugar/DsGRHSs.hs | 6 +- compiler/deSugar/DsListComp.hs | 7 +- compiler/deSugar/DsMeta.hs | 391 ++++++------ compiler/deSugar/DsMonad.hs | 1 + compiler/deSugar/DsUsage.hs | 1 + compiler/deSugar/DsUtils.hs | 55 +- compiler/deSugar/ExtractDocs.hs | 42 +- compiler/deSugar/Match.hs | 60 +- compiler/deSugar/MatchCon.hs | 8 +- compiler/deSugar/MatchLit.hs | 16 +- compiler/deSugar/PmExpr.hs | 9 +- compiler/hsSyn/Convert.hs | 157 ++--- compiler/hsSyn/HsPat.hs | 203 ++++--- compiler/hsSyn/HsPat.hs-boot | 3 +- compiler/hsSyn/HsTypes.hs | 4 +- compiler/hsSyn/HsUtils.hs | 186 +++--- compiler/main/GHC.hs | 10 +- compiler/main/HeaderInfo.hs | 107 ++-- compiler/main/HscStats.hs | 27 +- compiler/main/HscTypes.hs | 3 +- compiler/parser/Lexer.x | 32 +- compiler/parser/Parser.y | 378 ++++++------ compiler/parser/RdrHsSyn.hs | 658 +++++++++++---------- compiler/rename/RnBinds.hs | 10 +- compiler/rename/RnExpr.hs | 9 +- compiler/rename/RnFixity.hs | 14 +- compiler/rename/RnHsDoc.hs | 6 +- compiler/rename/RnPat.hs | 133 +++-- compiler/rename/RnSource.hs | 205 ++++--- compiler/rename/RnSplice.hs | 31 +- compiler/rename/RnTypes.hs | 152 ++--- compiler/rename/RnUtils.hs | 7 +- compiler/typecheck/TcBinds.hs | 59 +- compiler/typecheck/TcErrors.hs | 8 +- compiler/typecheck/TcGenDeriv.hs | 30 +- compiler/typecheck/TcHsSyn.hs | 144 +++-- compiler/typecheck/TcHsType.hs | 1 + compiler/typecheck/TcPat.hs | 45 +- compiler/typecheck/TcPatSyn.hs | 62 +- compiler/typecheck/TcRnDriver.hs | 260 ++++---- compiler/typecheck/TcRnExports.hs | 39 +- compiler/typecheck/TcRnMonad.hs | 39 +- compiler/typecheck/TcTyClsDecls.hs | 169 +++--- compiler/typecheck/TcTyDecls.hs | 35 +- compiler/utils/Binary.hs | 2 +- ghc/GHCi/UI/Info.hs | 17 +- testsuite/tests/ghc-api/T6145.hs | 13 +- .../tests/parser/should_compile/KindSigs.stderr | 12 +- utils/ghctags/Main.hs | 2 +- utils/haddock | 2 +- 59 files changed, 2479 insertions(+), 1951 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 509d5be69c7507ba5d0a5f39ffd1613a59e73eea From git at git.haskell.org Sat Nov 24 17:35:53 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 24 Nov 2018 17:35:53 +0000 (UTC) Subject: [commit: ghc] master: CircleCI: Clean up docker image (6a70acf) Message-ID: <20181124173553.170E23A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6a70acfa0b8757b9a6a56cffedc4b16a39dad510/ghc >--------------------------------------------------------------- commit 6a70acfa0b8757b9a6a56cffedc4b16a39dad510 Author: Ben Gamari Date: Sat Nov 24 12:34:57 2018 -0500 CircleCI: Clean up docker image >--------------------------------------------------------------- 6a70acfa0b8757b9a6a56cffedc4b16a39dad510 .circleci/config.yml | 12 ++++++------ .circleci/images/x86_64-linux-fedora/Dockerfile | 3 +-- .circleci/images/x86_64-linux/Dockerfile | 22 +++++++++------------- .circleci/prepare-system.sh | 13 ------------- 4 files changed, 16 insertions(+), 34 deletions(-) diff --git a/.circleci/config.yml b/.circleci/config.yml index 5e49cde..ebf5737 100644 --- a/.circleci/config.yml +++ b/.circleci/config.yml @@ -110,7 +110,7 @@ jobs: "validate-x86_64-linux": resource_class: xlarge docker: - - image: ghcci/x86_64-linux:0.0.4 + - image: ghcci/x86_64-linux:0.0.5 environment: <<: *buildenv GHC_COLLECTOR_FLAVOR: x86_64-linux @@ -181,7 +181,7 @@ jobs: "validate-hadrian-x86_64-linux": resource_class: xlarge docker: - - image: ghcci/x86_64-linux:0.0.4 + - image: ghcci/x86_64-linux:0.0.5 environment: <<: *buildenv steps: @@ -196,7 +196,7 @@ jobs: "validate-x86_64-linux-unreg": resource_class: xlarge docker: - - image: ghcci/x86_64-linux:0.0.4 + - image: ghcci/x86_64-linux:0.0.5 environment: <<: *buildenv TEST_ENV: x86_64-linux-unreg @@ -215,7 +215,7 @@ jobs: "validate-x86_64-linux-llvm": resource_class: xlarge docker: - - image: ghcci/x86_64-linux:0.0.4 + - image: ghcci/x86_64-linux:0.0.5 environment: <<: *buildenv BUILD_FLAVOUR: perf-llvm @@ -243,7 +243,7 @@ jobs: "validate-x86_64-linux-debug": resource_class: xlarge docker: - - image: ghcci/x86_64-linux:0.0.4 + - image: ghcci/x86_64-linux:0.0.5 environment: BUILD_FLAVOUR: devel2 <<: *buildenv @@ -308,7 +308,7 @@ jobs: "slow-validate-x86_64-linux": resource_class: xlarge docker: - - image: ghcci/x86_64-linux:0.0.4 + - image: ghcci/x86_64-linux:0.0.5 environment: <<: *buildenv GHC_COLLECTOR_FLAVOR: x86_64-linux diff --git a/.circleci/images/x86_64-linux-fedora/Dockerfile b/.circleci/images/x86_64-linux-fedora/Dockerfile index f60398d..959231b 100644 --- a/.circleci/images/x86_64-linux-fedora/Dockerfile +++ b/.circleci/images/x86_64-linux-fedora/Dockerfile @@ -42,8 +42,7 @@ USER ghc WORKDIR /home/ghc/ # Install Alex, Happy, and HsColor with Cabal -RUN cabal update -RUN cabal install alex happy hscolour +RUN cabal update && cabal install alex happy hscolour ENV PATH /home/ghc/.cabal/bin:$PATH CMD ["bash"] diff --git a/.circleci/images/x86_64-linux/Dockerfile b/.circleci/images/x86_64-linux/Dockerfile index f68c7e6..9fe713e 100644 --- a/.circleci/images/x86_64-linux/Dockerfile +++ b/.circleci/images/x86_64-linux/Dockerfile @@ -7,23 +7,15 @@ RUN apt-key adv --keyserver keyserver.ubuntu.com --recv-keys F6F88286 RUN apt-get update -qq # Core build utilities -RUN apt-get install -qy cabal-install-2.2 ghc-8.4.2 happy alex zlib1g-dev \ - libtinfo-dev libsqlite3-0 libsqlite3-dev ca-certificates g++ git curl \ - git make automake autoconf gcc perl python3 texinfo xz-utils lbzip2 \ - patch openssh-client sudo +RUN apt-get install -qy zlib1g-dev libtinfo-dev libsqlite3-0 libsqlite3-dev + ca-certificates g++ git curl make automake autoconf gcc + perl python3 texinfo xz-utils lbzip2 patch openssh-client sudo # Documentation tools RUN apt-get install -qy python3-sphinx texlive-xetex texlive-latex-extra -# Stack intallation -RUN curl -fSL https://github.com/commercialhaskell/stack/releases/download/v1.6.5/stack-1.6.5-linux-x86_64-static.tar.gz -o stack.tar.gz -RUN curl -fSL https://github.com/commercialhaskell/stack/releases/download/v1.6.5/stack-1.6.5-linux-x86_64-static.tar.gz.asc -o stack.tar.gz.asc -RUN export GNUPGHOME="$(mktemp -d)" -RUN gpg --keyserver ha.pool.sks-keyservers.net --recv-keys C5705533DA4F78D8664B5DC0575159689BEFB442 -RUN gpg --batch --verify stack.tar.gz.asc stack.tar.gz -RUN tar -xf stack.tar.gz -C /usr/local/bin --strip-components=1 -RUN /usr/local/bin/stack config set system-ghc --global true -RUN rm -rf "$GNUPGHOME" /var/lib/apt/lists/* /stack.tar.gz.asc /stack.tar.gz +# Basic Haskell toolchain +RUN apt-get install -qy cabal-install-2.2 ghc-8.4.2 ENV PATH /home/ghc/.cabal/bin:/home/ghc/.local/bin:/opt/cabal/2.2/bin:/opt/ghc/8.4.2/bin:$PATH @@ -32,6 +24,10 @@ RUN adduser ghc --gecos "GHC builds" --disabled-password RUN echo "ghc ALL = NOPASSWD : ALL" > /etc/sudoers.d/ghc USER ghc +# Build Haskell tools +RUN cabal update && \ + cabal install hscolour happy alex + WORKDIR /home/ghc/ CMD ["bash"] diff --git a/.circleci/prepare-system.sh b/.circleci/prepare-system.sh index 4be1b64..9a16c01 100755 --- a/.circleci/prepare-system.sh +++ b/.circleci/prepare-system.sh @@ -27,15 +27,6 @@ case "$(uname)" in if [[ -n ${TARGET:-} ]]; then if [[ $TARGET = FreeBSD ]]; then # cross-compiling to FreeBSD - add-apt-repository -y ppa:hvr/ghc - apt-get update -qq - apt-get install -qy ghc-8.0.2 cabal-install-1.24 alex happy \ - ncurses-dev git make automake autoconf gcc perl \ - python3 texinfo xz-utils lbzip2 patch - cabal update - cabal install --reinstall hscolour --index-state=$hackage_index_state - ln -s $HOME/.cabal/bin/HsColour /usr/local/bin/HsColour - echo 'HADDOCK_DOCS = NO' >> mk/build.mk echo 'WERROR=' >> mk/build.mk # https://circleci.com/docs/2.0/env-vars/#interpolating-environment-variables-to-set-other-environment-variables @@ -43,10 +34,6 @@ case "$(uname)" in else fail "TARGET=$target not supported" fi - else - cabal update - cabal install --reinstall hscolour - sudo ln -s /home/ghc/.cabal/bin/HsColour /usr/local/bin/HsColour || true fi ;; From git at git.haskell.org Sat Nov 24 19:13:56 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 24 Nov 2018 19:13:56 +0000 (UTC) Subject: [commit: ghc] master: CircleCI: More cleanup (4ac7a94) Message-ID: <20181124191356.7454C3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4ac7a947d1de79223d03cc44ccb99d44307ba23b/ghc >--------------------------------------------------------------- commit 4ac7a947d1de79223d03cc44ccb99d44307ba23b Author: Ben Gamari Date: Sat Nov 24 13:08:06 2018 -0500 CircleCI: More cleanup >--------------------------------------------------------------- 4ac7a947d1de79223d03cc44ccb99d44307ba23b .circleci/config.yml | 16 ++++++++-------- .circleci/images/i386-linux/Dockerfile | 17 +++++++++++++++-- .circleci/images/x86_64-linux-fedora/Dockerfile | 3 ++- .circleci/images/x86_64-linux/Dockerfile | 7 ++++--- 4 files changed, 29 insertions(+), 14 deletions(-) diff --git a/.circleci/config.yml b/.circleci/config.yml index ebf5737..8bb9306 100644 --- a/.circleci/config.yml +++ b/.circleci/config.yml @@ -110,7 +110,7 @@ jobs: "validate-x86_64-linux": resource_class: xlarge docker: - - image: ghcci/x86_64-linux:0.0.5 + - image: ghcci/x86_64-linux:0.0.7 environment: <<: *buildenv GHC_COLLECTOR_FLAVOR: x86_64-linux @@ -181,7 +181,7 @@ jobs: "validate-hadrian-x86_64-linux": resource_class: xlarge docker: - - image: ghcci/x86_64-linux:0.0.5 + - image: ghcci/x86_64-linux:0.0.7 environment: <<: *buildenv steps: @@ -196,7 +196,7 @@ jobs: "validate-x86_64-linux-unreg": resource_class: xlarge docker: - - image: ghcci/x86_64-linux:0.0.5 + - image: ghcci/x86_64-linux:0.0.7 environment: <<: *buildenv TEST_ENV: x86_64-linux-unreg @@ -215,7 +215,7 @@ jobs: "validate-x86_64-linux-llvm": resource_class: xlarge docker: - - image: ghcci/x86_64-linux:0.0.5 + - image: ghcci/x86_64-linux:0.0.7 environment: <<: *buildenv BUILD_FLAVOUR: perf-llvm @@ -243,7 +243,7 @@ jobs: "validate-x86_64-linux-debug": resource_class: xlarge docker: - - image: ghcci/x86_64-linux:0.0.5 + - image: ghcci/x86_64-linux:0.0.7 environment: BUILD_FLAVOUR: devel2 <<: *buildenv @@ -264,7 +264,7 @@ jobs: "validate-i386-linux": resource_class: xlarge docker: - - image: ghcci/i386-linux:0.0.5 + - image: ghcci/i386-linux:0.0.6 environment: <<: *buildenv GHC_COLLECTOR_FLAVOR: i386-linux @@ -286,7 +286,7 @@ jobs: "validate-x86_64-fedora": resource_class: xlarge docker: - - image: ghcci/x86_64-linux-fedora:0.0.15 + - image: ghcci/x86_64-linux-fedora:0.0.16 environment: <<: *buildenv GHC_COLLECTOR_FLAVOR: x86_64-fedora @@ -308,7 +308,7 @@ jobs: "slow-validate-x86_64-linux": resource_class: xlarge docker: - - image: ghcci/x86_64-linux:0.0.5 + - image: ghcci/x86_64-linux:0.0.7 environment: <<: *buildenv GHC_COLLECTOR_FLAVOR: x86_64-linux diff --git a/.circleci/images/i386-linux/Dockerfile b/.circleci/images/i386-linux/Dockerfile index 13a5721..47d19cc 100644 --- a/.circleci/images/i386-linux/Dockerfile +++ b/.circleci/images/i386-linux/Dockerfile @@ -7,12 +7,15 @@ RUN apt-key adv --keyserver keyserver.ubuntu.com --recv-keys F6F88286 RUN apt-get update -qq # Core build utilities -RUN apt-get install -qy git make automake autoconf gcc perl python3 texinfo xz-utils lbzip2 bzip2 patch openssh-client sudo curl zlib1g-dev libtinfo-dev libsqlite3-0 libsqlite3-dev ca-certificates g++ cabal-install-2.2 ghc-8.4.2 happy alex +RUN apt-get install -qy zlib1g-dev libtinfo-dev libsqlite3-0 libsqlite3-dev \ + ca-certificates g++ git curl make automake autoconf gcc \ + perl python3 texinfo xz-utils lbzip2 patch openssh-client sudo # Documentation tools RUN apt-get install -qy python3-sphinx texlive-xetex texlive-latex-extra -ENV PATH /home/ghc/.cabal/bin:/home/ghc/.local/bin:/opt/cabal/2.2/bin:/opt/ghc/8.4.2/bin:$PATH +# Core build utilities +RUN apt-get install -qy libgmp-dev:i386 # Get i386 GHC bindist for 32 bit CI builds. RUN cd /tmp && curl https://downloads.haskell.org/~ghc/8.4.2/ghc-8.4.2-i386-deb8-linux.tar.xz | tar -Jx @@ -21,11 +24,21 @@ RUN cd /tmp/ghc-8.4.2 && make install RUN rm -rf /tmp/ghc-8.4.2 ENV PATH /opt/ghc-i386/8.4.2/bin:$PATH +# Get Cabal +RUN cd /tmp && \ + curl https://www.haskell.org/cabal/release/cabal-install-2.2.0.0/cabal-install-2.2.0.0-i386-unknown-linux.tar.gz | tar -zx && \ + mv cabal /usr/local/bin/cabal + # Create a normal user. RUN adduser ghc --gecos "GHC builds" --disabled-password RUN echo "ghc ALL = NOPASSWD : ALL" > /etc/sudoers.d/ghc USER ghc +# Build Haskell tools +RUN cabal update && \ + cabal install hscolour happy alex +ENV PATH /home/ghc/.cabal/bin:$PATH + WORKDIR /home/ghc/ CMD ["bash"] diff --git a/.circleci/images/x86_64-linux-fedora/Dockerfile b/.circleci/images/x86_64-linux-fedora/Dockerfile index 959231b..0ed546c 100644 --- a/.circleci/images/x86_64-linux-fedora/Dockerfile +++ b/.circleci/images/x86_64-linux-fedora/Dockerfile @@ -42,7 +42,8 @@ USER ghc WORKDIR /home/ghc/ # Install Alex, Happy, and HsColor with Cabal -RUN cabal update && cabal install alex happy hscolour +RUN cabal update && \ + cabal install hscolour happy alex ENV PATH /home/ghc/.cabal/bin:$PATH CMD ["bash"] diff --git a/.circleci/images/x86_64-linux/Dockerfile b/.circleci/images/x86_64-linux/Dockerfile index 9fe713e..5360645 100644 --- a/.circleci/images/x86_64-linux/Dockerfile +++ b/.circleci/images/x86_64-linux/Dockerfile @@ -7,8 +7,8 @@ RUN apt-key adv --keyserver keyserver.ubuntu.com --recv-keys F6F88286 RUN apt-get update -qq # Core build utilities -RUN apt-get install -qy zlib1g-dev libtinfo-dev libsqlite3-0 libsqlite3-dev - ca-certificates g++ git curl make automake autoconf gcc +RUN apt-get install -qy zlib1g-dev libtinfo-dev libsqlite3-0 libsqlite3-dev \ + ca-certificates g++ git curl make automake autoconf gcc \ perl python3 texinfo xz-utils lbzip2 patch openssh-client sudo # Documentation tools @@ -17,7 +17,7 @@ RUN apt-get install -qy python3-sphinx texlive-xetex texlive-latex-extra # Basic Haskell toolchain RUN apt-get install -qy cabal-install-2.2 ghc-8.4.2 -ENV PATH /home/ghc/.cabal/bin:/home/ghc/.local/bin:/opt/cabal/2.2/bin:/opt/ghc/8.4.2/bin:$PATH +ENV PATH /home/ghc/.local/bin:/opt/cabal/2.2/bin:/opt/ghc/8.4.2/bin:$PATH # Create a normal user. RUN adduser ghc --gecos "GHC builds" --disabled-password @@ -27,6 +27,7 @@ USER ghc # Build Haskell tools RUN cabal update && \ cabal install hscolour happy alex +ENV PATH /home/ghc/.cabal/bin:$PATH WORKDIR /home/ghc/ From git at git.haskell.org Sat Nov 24 19:13:59 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sat, 24 Nov 2018 19:13:59 +0000 (UTC) Subject: [commit: ghc] master: Revert "Fix uninformative hp2ps error when the cmdline contains double quotes" (bba2b9b) Message-ID: <20181124191359.773B73A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/bba2b9bf2d69700dc114118658507aaac34c5e62/ghc >--------------------------------------------------------------- commit bba2b9bf2d69700dc114118658507aaac34c5e62 Author: Ben Gamari Date: Sat Nov 24 14:01:40 2018 -0500 Revert "Fix uninformative hp2ps error when the cmdline contains double quotes" This reverts commit 390df8b51b917fb6409cbde8e73fe838d61d8832. >--------------------------------------------------------------- bba2b9bf2d69700dc114118658507aaac34c5e62 rts/ProfHeap.c | 30 +-- testsuite/tests/hp2ps/Makefile | 9 - testsuite/tests/hp2ps/T15904.hs | 8 - testsuite/tests/hp2ps/T15904.stdout | 7 - testsuite/tests/hp2ps/all.T | 1 - utils/hp2ps/HpFile.c | 351 ++++++++++++++++++------------------ 6 files changed, 185 insertions(+), 221 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 bba2b9bf2d69700dc114118658507aaac34c5e62 From git at git.haskell.org Sun Nov 25 14:32:57 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Sun, 25 Nov 2018 14:32:57 +0000 (UTC) Subject: [commit: ghc] master: Remove unused declarations in MarkWeak.h (9e47dd3) Message-ID: <20181125143257.BE9F73A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9e47dd32e238ed0c4c39035f47e0843ddccb5175/ghc >--------------------------------------------------------------- commit 9e47dd32e238ed0c4c39035f47e0843ddccb5175 Author: Ömer Sinan Ağacan Date: Sun Nov 25 17:03:39 2018 +0300 Remove unused declarations in MarkWeak.h >--------------------------------------------------------------- 9e47dd32e238ed0c4c39035f47e0843ddccb5175 rts/sm/MarkWeak.h | 2 -- 1 file changed, 2 deletions(-) diff --git a/rts/sm/MarkWeak.h b/rts/sm/MarkWeak.h index eba1f21..cd58ec9 100644 --- a/rts/sm/MarkWeak.h +++ b/rts/sm/MarkWeak.h @@ -15,9 +15,7 @@ #include "BeginPrivate.h" -extern StgWeak *old_weak_ptr_list; extern StgTSO *resurrected_threads; -extern StgTSO *exception_threads; void collectFreshWeakPtrs ( void ); void initWeakForGC ( void ); From git at git.haskell.org Mon Nov 26 09:00:39 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Nov 2018 09:00:39 +0000 (UTC) Subject: [commit: ghc] master: Revert "Remove redundant check in cgCase" (8a6aa87) Message-ID: <20181126090039.2E8573A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8a6aa87766a47f7f2f11642f770a52c0a91fc554/ghc >--------------------------------------------------------------- commit 8a6aa87766a47f7f2f11642f770a52c0a91fc554 Author: Ömer Sinan Ağacan Date: Mon Nov 26 12:00:02 2018 +0300 Revert "Remove redundant check in cgCase" This reverts commit d13b7d60650cb84af11ee15b3f51c3511548cfdb. (See discussion in D5358) >--------------------------------------------------------------- 8a6aa87766a47f7f2f11642f770a52c0a91fc554 compiler/codeGen/StgCmmExpr.hs | 11 +++++++---- 1 file changed, 7 insertions(+), 4 deletions(-) diff --git a/compiler/codeGen/StgCmmExpr.hs b/compiler/codeGen/StgCmmExpr.hs index 5844161..ea64e45 100644 --- a/compiler/codeGen/StgCmmExpr.hs +++ b/compiler/codeGen/StgCmmExpr.hs @@ -304,10 +304,13 @@ cgCase (StgOpApp (StgPrimOp op) args _) bndr (AlgAlt tycon) alts | isEnumerationTyCon tycon -- Note [case on bool] = do { tag_expr <- do_enum_primop op args - ; dflags <- getDynFlags - ; tmp_reg <- bindArgToReg (NonVoid bndr) - ; emitAssign (CmmLocal tmp_reg) - (tagToClosure dflags tycon tag_expr) + -- If the binder is not dead, convert the tag to a constructor + -- and assign it. + ; unless (isDeadBinder bndr) $ do + { dflags <- getDynFlags + ; tmp_reg <- bindArgToReg (NonVoid bndr) + ; emitAssign (CmmLocal tmp_reg) + (tagToClosure dflags tycon tag_expr) } ; (mb_deflt, branches) <- cgAlgAltRhss (NoGcInAlts,AssignedDirectly) (NonVoid bndr) alts From git at git.haskell.org Mon Nov 26 09:28:44 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Nov 2018 09:28:44 +0000 (UTC) Subject: [commit: ghc] master: Fix build on darwin (df570d9) Message-ID: <20181126092844.9CD433A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/df570d920fa66db631f936fa377e598fe92bd2a1/ghc >--------------------------------------------------------------- commit df570d920fa66db631f936fa377e598fe92bd2a1 Author: Ömer Sinan Ağacan Date: Mon Nov 26 12:27:59 2018 +0300 Fix build on darwin CPP error introduced with b2950e0 >--------------------------------------------------------------- df570d920fa66db631f936fa377e598fe92bd2a1 compiler/simplStg/StgLiftLams/Transformation.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/simplStg/StgLiftLams/Transformation.hs b/compiler/simplStg/StgLiftLams/Transformation.hs index 8c4d616..7b37bac 100644 --- a/compiler/simplStg/StgLiftLams/Transformation.hs +++ b/compiler/simplStg/StgLiftLams/Transformation.hs @@ -102,7 +102,7 @@ liftRhs -> LlStgRhs -> LiftM OutStgRhs liftRhs mb_former_fvs rhs@(StgRhsCon ccs con args) - = ASSERT2 ( isNothing mb_former_fvs, text "Should never lift a constructor" $$ ppr rhs) + = ASSERT2(isNothing mb_former_fvs, text "Should never lift a constructor" $$ ppr rhs) StgRhsCon ccs con <$> traverse liftArgs args liftRhs Nothing (StgRhsClosure _ ccs upd infos body) = do -- This RHS wasn't lifted. From git at git.haskell.org Mon Nov 26 09:41:13 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Nov 2018 09:41:13 +0000 (UTC) Subject: [commit: ghc] wip/T15809: More wibbles to data families (f5fa9cd) Message-ID: <20181126094113.1BEB93A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/f5fa9cd3c944aad0d09555c3d0f1472c2036ddf5/ghc >--------------------------------------------------------------- commit f5fa9cd3c944aad0d09555c3d0f1472c2036ddf5 Author: Simon Peyton Jones Date: Mon Nov 26 09:39:31 2018 +0000 More wibbles to data families Including fixing Trac #15817 >--------------------------------------------------------------- f5fa9cd3c944aad0d09555c3d0f1472c2036ddf5 compiler/basicTypes/DataCon.hs | 3 +- compiler/typecheck/TcHsType.hs | 119 +++++++++--------- compiler/typecheck/TcInstDcls.hs | 247 ++++++++++++++++++++++++++----------- compiler/typecheck/TcMType.hs | 4 +- compiler/typecheck/TcTyClsDecls.hs | 65 +++++++--- compiler/types/TyCon.hs | 15 ++- compiler/types/Type.hs | 8 +- 7 files changed, 298 insertions(+), 163 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 f5fa9cd3c944aad0d09555c3d0f1472c2036ddf5 From git at git.haskell.org Mon Nov 26 13:09:32 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Nov 2018 13:09:32 +0000 (UTC) Subject: [commit: ghc] branch 'wip/tdammers/T14375' created Message-ID: <20181126130932.47B393A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New branch : wip/tdammers/T14375 Referencing: 7099d2dbe6121a549dc6da8ed95b54959154d40c From git at git.haskell.org Mon Nov 26 13:09:35 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Nov 2018 13:09:35 +0000 (UTC) Subject: [commit: ghc] wip/tdammers/T14375: D4110, manually rebased onto master (7099d2d) Message-ID: <20181126130935.5D9563A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tdammers/T14375 Link : http://ghc.haskell.org/trac/ghc/changeset/7099d2dbe6121a549dc6da8ed95b54959154d40c/ghc >--------------------------------------------------------------- commit 7099d2dbe6121a549dc6da8ed95b54959154d40c Author: Tobias Dammers Date: Mon Nov 26 14:08:35 2018 +0100 D4110, manually rebased onto master >--------------------------------------------------------------- 7099d2dbe6121a549dc6da8ed95b54959154d40c compiler/cmm/CmmMachOp.hs | 1 + compiler/cmm/PprC.hs | 1 + compiler/llvmGen/LlvmCodeGen/CodeGen.hs | 1 + compiler/nativeGen/PPC/CodeGen.hs | 1 + compiler/nativeGen/SPARC/CodeGen.hs | 1 + compiler/nativeGen/X86/CodeGen.hs | 1 + compiler/prelude/primops.txt.pp | 46 +++++++++++++++++++++++++ includes/rts/storage/ClosureTypes.h | 3 +- includes/rts/storage/Closures.h | 5 +++ includes/stg/MiscClosures.h | 1 + libraries/base/Foreign/Marshal/Alloc.hs | 14 +++----- libraries/ghc-compact/GHC/Compact/Serialized.hs | 5 ++- rts/ClosureFlags.c | 13 +++---- rts/PrimOps.cmm | 21 +++++++++++ rts/Printer.c | 5 +-- rts/RetainerProfile.c | 6 ++++ rts/RtsSymbols.c | 1 + rts/sm/Compact.c | 1 + rts/sm/Evac.c | 1 + rts/sm/Sanity.c | 1 + rts/sm/Scav.c | 1 + utils/genprimopcode/Main.hs | 2 ++ 22 files changed, 111 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 7099d2dbe6121a549dc6da8ed95b54959154d40c From git at git.haskell.org Mon Nov 26 17:48:28 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Nov 2018 17:48:28 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Tc-tracing, and order of arguments only (c216a13) Message-ID: <20181126174828.26C053A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/c216a13c549908337ed7c7e3dc7825cc216c5ef2/ghc >--------------------------------------------------------------- commit c216a13c549908337ed7c7e3dc7825cc216c5ef2 Author: Simon Peyton Jones Date: Wed Oct 31 08:31:38 2018 +0000 Tc-tracing, and order of arguments only I changed the order of arguments to reportAllUnsolved, and the tc-tracing that surrounds it. No change in behaviour >--------------------------------------------------------------- c216a13c549908337ed7c7e3dc7825cc216c5ef2 compiler/typecheck/TcErrors.hs | 29 ++++++++++++++++------------- compiler/typecheck/TcRnMonad.hs | 2 ++ compiler/typecheck/TcSimplify.hs | 4 ---- 3 files changed, 18 insertions(+), 17 deletions(-) diff --git a/compiler/typecheck/TcErrors.hs b/compiler/typecheck/TcErrors.hs index 7c33834..0ad6706 100644 --- a/compiler/typecheck/TcErrors.hs +++ b/compiler/typecheck/TcErrors.hs @@ -148,8 +148,9 @@ reportUnsolved wanted | warn_out_of_scope = HoleWarn | otherwise = HoleDefer - ; report_unsolved binds_var type_errors expr_holes - type_holes out_of_scope_holes wanted + ; report_unsolved type_errors expr_holes + type_holes out_of_scope_holes + binds_var wanted ; ev_binds <- getTcEvBindsMap binds_var ; return (evBindMapBinds ev_binds)} @@ -164,8 +165,8 @@ reportUnsolved wanted reportAllUnsolved :: WantedConstraints -> TcM () reportAllUnsolved wanted = do { ev_binds <- newNoTcEvBinds - ; report_unsolved ev_binds TypeError - HoleError HoleError HoleError wanted } + ; report_unsolved TypeError HoleError HoleError HoleError + ev_binds wanted } -- | Report all unsolved goals as warnings (but without deferring any errors to -- run-time). See Note [Safe Haskell Overlapping Instances Implementation] in @@ -173,22 +174,23 @@ reportAllUnsolved wanted warnAllUnsolved :: WantedConstraints -> TcM () warnAllUnsolved wanted = do { ev_binds <- newTcEvBinds - ; report_unsolved ev_binds (TypeWarn NoReason) - HoleWarn HoleWarn HoleWarn wanted } + ; report_unsolved (TypeWarn NoReason) HoleWarn HoleWarn HoleWarn + ev_binds wanted } -- | Report unsolved goals as errors or warnings. -report_unsolved :: EvBindsVar -- cec_binds - -> TypeErrorChoice -- Deferred type errors +report_unsolved :: TypeErrorChoice -- Deferred type errors -> HoleChoice -- Expression holes -> HoleChoice -- Type holes -> HoleChoice -- Out of scope holes + -> EvBindsVar -- cec_binds -> WantedConstraints -> TcM () -report_unsolved mb_binds_var type_errors expr_holes - type_holes out_of_scope_holes wanted +report_unsolved type_errors expr_holes + type_holes out_of_scope_holes binds_var wanted | isEmptyWC wanted = return () | otherwise - = do { traceTc "reportUnsolved warning/error settings:" $ + = do { traceTc "reportUnsolved {" empty + ; traceTc "reportUnsolved warning/error settings:" $ vcat [ text "type errors:" <+> ppr type_errors , text "expr holes:" <+> ppr expr_holes , text "type holes:" <+> ppr type_holes @@ -221,10 +223,11 @@ report_unsolved mb_binds_var type_errors expr_holes -- See Trac #15539 and c.f. setting ic_status -- in TcSimplify.setImplicationStatus , cec_warn_redundant = warn_redundant - , cec_binds = mb_binds_var } + , cec_binds = binds_var } ; tc_lvl <- getTcLevel - ; reportWanteds err_ctxt tc_lvl wanted } + ; reportWanteds err_ctxt tc_lvl wanted + ; traceTc "reportUnsolved }" empty } -------------------------------------------- -- Internal functions diff --git a/compiler/typecheck/TcRnMonad.hs b/compiler/typecheck/TcRnMonad.hs index 667d866..453f699 100644 --- a/compiler/typecheck/TcRnMonad.hs +++ b/compiler/typecheck/TcRnMonad.hs @@ -1542,8 +1542,10 @@ pushLevelAndCaptureConstraints :: TcM a -> TcM (TcLevel, WantedConstraints, a) pushLevelAndCaptureConstraints thing_inside = do { env <- getLclEnv ; let tclvl' = pushTcLevel (tcl_tclvl env) + ; traceTc "pushLevelAndCaptureConstraints {" (ppr tclvl') ; (res, lie) <- setLclEnv (env { tcl_tclvl = tclvl' }) $ captureConstraints thing_inside + ; traceTc "pushLevelAndCaptureConstraints }" (ppr tclvl') ; return (tclvl', lie, res) } pushTcLevelM_ :: TcM a -> TcM a diff --git a/compiler/typecheck/TcSimplify.hs b/compiler/typecheck/TcSimplify.hs index 6ef62c8..c424a02 100644 --- a/compiler/typecheck/TcSimplify.hs +++ b/compiler/typecheck/TcSimplify.hs @@ -178,9 +178,7 @@ solveEqualities thing_inside -- vars to LiftedRep. This is needed to avoid #14991. ; traceTc "End solveEqualities }" empty - ; traceTc "reportAllUnsolved {" empty ; reportAllUnsolved final_wc - ; traceTc "reportAllUnsolved }" empty ; return result } -- | Simplify top-level constraints, but without reporting any unsolved @@ -514,9 +512,7 @@ simplifyDefault theta = do { traceTc "simplifyDefault" empty ; wanteds <- newWanteds DefaultOrigin theta ; unsolved <- runTcSDeriveds (solveWantedsAndDrop (mkSimpleWC wanteds)) - ; traceTc "reportUnsolved {" empty ; reportAllUnsolved unsolved - ; traceTc "reportUnsolved }" empty ; return () } ------------------ From git at git.haskell.org Mon Nov 26 17:48:31 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Nov 2018 17:48:31 +0000 (UTC) Subject: [commit: ghc] wip/T15809: WIP on using level numbers for generalisation (ec716ec) Message-ID: <20181126174831.2DC3E3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/ec716ec4ddbcd74eafa3d9ba87be3e4facc23bdc/ghc >--------------------------------------------------------------- commit ec716ec4ddbcd74eafa3d9ba87be3e4facc23bdc Author: Simon Peyton Jones Date: Wed Oct 31 08:40:40 2018 +0000 WIP on using level numbers for generalisation This mostly works. So far I simply have a WARNING in quantifyTyVars which fires if the two methods (old "global-tyvars" and new "level-numbers") give different answers. Some modest but important refactoring along the way. Main thing that is still wrong: in instance declarations we are not skoelmising. Here's a partial patch to TcInstDcls, that /doesn't/ yet work -- Next, process any associated types. ; traceTc "tcLocalInstDecl" (ppr poly_ty) - ; tyfam_insts0 <- scopeTyVars InstSkol tyvars $ - mapAndRecoverM (tcTyFamInstDecl mb_info) ats - ; datafam_stuff <- scopeTyVars InstSkol tyvars $ - mapAndRecoverM (tcDataFamInstDecl mb_info) adts + ; (_subst, skol_tvs) <- tcInstSkolTyVars tyvars + ; (tyfam_insts0, datafam_stuff) + <- tcExtendNameTyVarEnv (map tyVarName tyvars `zip` skol_tvs) $ + do { tfs <- mapAndRecoverM (tcTyFamInstDecl mb_info) ats + ; dfs <- mapAndRecoverM (tcDataFamInstDecl mb_info) adts + ; return (tfs, dfs) } ; let (datafam_insts, m_deriv_infos) = unzip datafam_stuff >--------------------------------------------------------------- ec716ec4ddbcd74eafa3d9ba87be3e4facc23bdc compiler/typecheck/TcHsType.hs | 95 ++++++++++++++++++++++++------------ compiler/typecheck/TcMType.hs | 99 ++++++++++++++++++++++++++------------ compiler/typecheck/TcSimplify.hs | 19 +++++--- compiler/typecheck/TcTyClsDecls.hs | 90 +++++++++++++++++----------------- compiler/typecheck/TcValidity.hs | 12 ++--- 5 files changed, 194 insertions(+), 121 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 ec716ec4ddbcd74eafa3d9ba87be3e4facc23bdc From git at git.haskell.org Mon Nov 26 17:48:34 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Nov 2018 17:48:34 +0000 (UTC) Subject: [commit: ghc] wip/T15809: More progress (ea20832) Message-ID: <20181126174834.329503A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/ea20832022d6cbcfe0d1b764fbcb91094fd8601a/ghc >--------------------------------------------------------------- commit ea20832022d6cbcfe0d1b764fbcb91094fd8601a Author: Simon Peyton Jones Date: Tue Nov 6 08:55:37 2018 +0000 More progress >--------------------------------------------------------------- ea20832022d6cbcfe0d1b764fbcb91094fd8601a compiler/typecheck/TcEnv.hs | 2 +- compiler/typecheck/TcHsSyn.hs | 7 ++++- compiler/typecheck/TcHsType.hs | 4 --- compiler/typecheck/TcMType.hs | 14 ++++----- compiler/typecheck/TcRnDriver.hs | 2 +- compiler/typecheck/TcSimplify.hs | 2 +- compiler/typecheck/TcTyClsDecls.hs | 61 +++++++++++++++++++++++++------------- 7 files changed, 57 insertions(+), 35 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc ea20832022d6cbcfe0d1b764fbcb91094fd8601a From git at git.haskell.org Mon Nov 26 17:48:37 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Nov 2018 17:48:37 +0000 (UTC) Subject: [commit: ghc] wip/T15809: More progress on using level numbers for gen (7cc4706) Message-ID: <20181126174837.356A03A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/7cc4706feda2241d1904ac73e31912273109aa28/ghc >--------------------------------------------------------------- commit 7cc4706feda2241d1904ac73e31912273109aa28 Author: Simon Peyton Jones Date: Wed Oct 31 15:00:16 2018 +0000 More progress on using level numbers for gen >--------------------------------------------------------------- 7cc4706feda2241d1904ac73e31912273109aa28 compiler/typecheck/TcHsType.hs | 196 ++++++++++++++++++------------------- compiler/typecheck/TcInstDcls.hs | 11 +-- compiler/typecheck/TcMType.hs | 5 +- compiler/typecheck/TcSimplify.hs | 11 ++- compiler/typecheck/TcTyClsDecls.hs | 8 +- 5 files changed, 112 insertions(+), 119 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 7cc4706feda2241d1904ac73e31912273109aa28 From git at git.haskell.org Mon Nov 26 17:48:40 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Nov 2018 17:48:40 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Further work on TyCon generalisation (1394ef8) Message-ID: <20181126174840.54BF43A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/1394ef8df027f880f2fd39538b05bc937e70e307/ghc >--------------------------------------------------------------- commit 1394ef8df027f880f2fd39538b05bc937e70e307 Author: Simon Peyton Jones Date: Fri Nov 2 18:06:16 2018 +0000 Further work on TyCon generalisation >--------------------------------------------------------------- 1394ef8df027f880f2fd39538b05bc937e70e307 compiler/typecheck/TcHsType.hs | 109 +++++++++++---------- compiler/typecheck/TcMType.hs | 54 +++++++--- compiler/typecheck/TcRnTypes.hs | 8 +- compiler/typecheck/TcTyClsDecls.hs | 93 +++++------------- compiler/types/TyCoRep.hs | 16 ++- compiler/types/Type.hs | 2 +- testsuite/tests/dependent/should_compile/T14880.hs | 1 + .../tests/dependent/should_compile/T15743e.stderr | 6 +- .../tests/indexed-types/should_fail/T13972.stderr | 2 +- testsuite/tests/polykinds/T12593.stderr | 8 +- 10 files changed, 147 insertions(+), 152 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 1394ef8df027f880f2fd39538b05bc937e70e307 From git at git.haskell.org Mon Nov 26 17:48:43 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Nov 2018 17:48:43 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Further progress (ccdcb58) Message-ID: <20181126174843.6A1F73A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/ccdcb5801fb58589a4cf7163f6c19505e1d71f8d/ghc >--------------------------------------------------------------- commit ccdcb5801fb58589a4cf7163f6c19505e1d71f8d Author: Simon Peyton Jones Date: Mon Nov 5 17:43:08 2018 +0000 Further progress >--------------------------------------------------------------- ccdcb5801fb58589a4cf7163f6c19505e1d71f8d compiler/typecheck/TcHsSyn.hs | 28 ++++++----- compiler/typecheck/TcHsType.hs | 7 ++- compiler/typecheck/TcMType.hs | 95 ++++++++++++++++++++++++-------------- compiler/typecheck/TcRules.hs | 2 +- compiler/typecheck/TcSimplify.hs | 6 +-- compiler/typecheck/TcTyClsDecls.hs | 43 +++++++++-------- 6 files changed, 111 insertions(+), 70 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 ccdcb5801fb58589a4cf7163f6c19505e1d71f8d From git at git.haskell.org Mon Nov 26 17:48:46 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Nov 2018 17:48:46 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Comemnts only (e5492e6) Message-ID: <20181126174846.6B1A53A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/e5492e65c83baf0dc1a7bed3288435af8fd72496/ghc >--------------------------------------------------------------- commit e5492e65c83baf0dc1a7bed3288435af8fd72496 Author: Simon Peyton Jones Date: Wed Nov 7 11:40:50 2018 +0000 Comemnts only >--------------------------------------------------------------- e5492e65c83baf0dc1a7bed3288435af8fd72496 compiler/typecheck/TcTyClsDecls.hs | 74 +++++++++++++++++++++++--------------- 1 file changed, 46 insertions(+), 28 deletions(-) diff --git a/compiler/typecheck/TcTyClsDecls.hs b/compiler/typecheck/TcTyClsDecls.hs index 968a153..d8c8db1 100644 --- a/compiler/typecheck/TcTyClsDecls.hs +++ b/compiler/typecheck/TcTyClsDecls.hs @@ -638,37 +638,55 @@ generaliseTcTyCon tc {- Note [Required, Specified, and Inferred for types] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -We have some design choices in how we classify the tyvars bound -in a type declaration. (Here, I use "type" to refer to any TyClDecl.) -Much of the debate is memorialized in #15743. This Note documents -the final conclusion. - -First, a reminder: - * a Required argument is one that must be provided at every call site - * a Specified argument is one that can be inferred at call sites, but - may be instantiated with visible type application - * an Inferred argument is one that must be inferred at call sites; it - is unavailable for use with visible type application. - -Why have Inferred at all? Because we just can't make user-facing promises -about the ordering of some variables. These might swizzle around even between -minor released. By forbidding visible type application, we ensure users -aren't caught unawares. See also -Note [VarBndrs, TyCoVarBinders, TyConBinders, and visibility] in TyCoRep. - -When inferring the ordering of variables (that is, for those -variables that he user has not specified the order with an explicit `forall`) -we use the following order: - - 1. Inferred variables from an enclosing class (associated types only) - 2. Specified variables from an enclosing class (associated types only) - 3. Inferred variables not from an enclosing class - 4. Specified variables not from an enclosing class - 5. Required variables before a top-level :: - 6. All variables after a top-level :: +Each forall'd type variable in a type or kind is one of + + * Required: an argument must be provided at every call site + + * Specified: the argument can be inferred at call sites, but + may be instantiated with visible type/kind application + + * Inferred: the must be inferred at call sites; it + is unavailable for use with visible type/kind application. + +Why have Inferred at all? Because we just can't make user-facing +promises about the ordering of some variables. These might swizzle +around even between minor released. By forbidding visible type +application, we ensure users aren't caught unawares. + +Go read Note [VarBndrs, TyCoVarBinders, TyConBinders, and visibility] in TyCoRep. + +The question for this Note is this: + given a TyClDecl, how are its quantified type variables classified? +Much of the debate is memorialized in #15743. + +Here is our design choice. When inferring the ordering of variables +for a TyCl declaration (that is, for those variables that he user +has not specified the order with an explicit `forall`), we use the +following order: + + 1. Inferred variables + 2. Specified variables; in the left-to-right order in which + the user wrote them, modified by scopedSort (see below) + to put them in depdendency order. + 3. Required variables before a top-level :: + 4. All variables after a top-level :: If this ordering does not make a valid telescope, we reject the definition. +Example: + data SameKind :: k -> k -> * + data X a (b :: SameKind a b) (c :: k) d + +For X: + - a, b, c, d are Required; they are explicitly listed by the user + as the positional arguments of X + - k is Specified; it appears explicitly in a kind signature + - k2, the kind of d, is Inferred; it is not mentioned explicitly at all + +Putting variables in the order Inferred, Specified, Required gives us + Inferred: k2 + Specified: k (a ::kb + This idea is implemented in the generalise function within kcTyClGroup (for declarations without CUSKs), and in kcLHsQTyVars (for declarations with CUSKs). Note that neither definition worries about point (6) above, as this From git at git.haskell.org Mon Nov 26 17:48:49 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Nov 2018 17:48:49 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Progress (326f87a) Message-ID: <20181126174849.6602E3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/326f87a2028b6254dd0fd0f722564740e99cf108/ghc >--------------------------------------------------------------- commit 326f87a2028b6254dd0fd0f722564740e99cf108 Author: Simon Peyton Jones Date: Fri Nov 9 18:11:25 2018 +0000 Progress Allocate result kind outside tcImplicit in tc_hs_sig_type_and_gen Plus comments In flight.. may not build (but it's a wip/ branch) >--------------------------------------------------------------- 326f87a2028b6254dd0fd0f722564740e99cf108 compiler/typecheck/TcHsType.hs | 49 +++++++++++++++++++++--------------------- compiler/typecheck/TcMType.hs | 18 ++++------------ 2 files changed, 29 insertions(+), 38 deletions(-) diff --git a/compiler/typecheck/TcHsType.hs b/compiler/typecheck/TcHsType.hs index 99bc57e..7b1e414 100644 --- a/compiler/typecheck/TcHsType.hs +++ b/compiler/typecheck/TcHsType.hs @@ -230,19 +230,15 @@ tc_hs_sig_type_and_gen skol_info hs_sig_type ctxt_kind | HsIB { hsib_ext = sig_vars, hsib_body = hs_ty } <- hs_sig_type = do { (_inner_lvl, wanted, (tkvs, ty)) <- pushLevelAndCaptureConstraints $ - tcImplicitTKBndrs skol_info sig_vars $ - -- tcImplicitTKBndrs does a solveLocalEqualities - do { kind <- case ctxt_kind of + do { -- See Note [Levels and generalisation] + res_kind <- case ctxt_kind of TheKind k -> return k AnyKind -> newMetaKindVar OpenKind -> newOpenTypeKind - -- The kind is checked by checkValidType, and isn't necessarily - -- of kind * in a Template Haskell quote eg [t| Maybe |] - ; tc_lhs_type typeLevelMode hs_ty kind } - -- Any remaining variables (unsolved in the solveLocalEqualities - -- in the tcImplicitTKBndrs) should be in the global tyvars, - -- and therefore won't be quantified over + ; tcImplicitTKBndrs skol_info sig_vars $ + -- tcImplicitTKBndrs does a solveLocalEqualities + tc_lhs_type typeLevelMode hs_ty res_kind } ; let ty1 = mkSpecForAllTys tkvs ty ; kvs <- kindGeneralizeLocal wanted ty1 @@ -1468,20 +1464,6 @@ To avoid the double-zonk, we do two things: 2. When we are generalizing: kindGeneralize does not require a zonked type -- it zonks as it gathers free variables. So this way effectively sidesteps step 3. - -Note [TcLevel for CUSKs] -~~~~~~~~~~~~~~~~~~~~~~~~ -In getInitialKinds we are at level 1, busy making unification -variables over which we will subsequently generalise. - -But when we find a CUSK we want to jump back to top level (0) -because that's the right starting point for a completee, -stand-alone kind signature. - -More precisely, we want to make level-1 skolems, because -the end up as the TyConBinders of the TyCon, and are brought -into scope when we type-check the body of the type declaration -(in tcTyClDecl). -} tcWildCardBinders :: [Name] @@ -2004,7 +1986,26 @@ kindGeneralizeLocal wanted kind_or_type ; quantifyTyVars mono_tvs dvs } -{- +{- Note [Levels and generalisation] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Consider + f x = e +with no type signature. We are currently at level i. +We must + * Push the level to level (i+1) + * Allocate a fresh alpha[i+1] for the result type + * Check that e :: alpha[i+1], gathering constraint WC + * Solve WC as far as possible + * Zonking the result type alpha[i+1], say to beta[i-1] -> gamma[i] + * Find the free variables with level > i, in this case gamma[i] + * Skolemise those free variables and quantify over them, giving + f :: forall g. beta[i-1] -> g + * Emit the residiual constraint wrapped in an implication for g, + thus forall g. WC + +All of this happens for types too. Consider + f :: Int -> (forall a. Proxy a -> Int) + Note [Kind generalisation] ~~~~~~~~~~~~~~~~~~~~~~~~~~ We do kind generalisation only at the outer level of a type signature. diff --git a/compiler/typecheck/TcMType.hs b/compiler/typecheck/TcMType.hs index 6d9f3ca..a1cdf24 100644 --- a/compiler/typecheck/TcMType.hs +++ b/compiler/typecheck/TcMType.hs @@ -1342,16 +1342,6 @@ to be later converted to a list in a deterministic order. For more information about deterministic sets see Note [Deterministic UniqFM] in UniqDFM. - - ---------------- Note to tidy up -------- -Can we quantify over a non-unification variable? Sadly yes (Trac #15991b) - class C2 (a :: Type) (b :: Proxy a) (c :: Proxy b) where - type T4 a c - -When we come to T4 we have in Inferred b; but it is a skolem -from the (fully settled) C2. - -} quantifyTyVars @@ -1444,10 +1434,10 @@ quantifyTyVars gbl_tvs = return Nothing -- this can happen for a covar that's associated with -- a coercion hole. Test case: typecheck/should_compile/T2494 - | not (isTcTyVar tkv) - = WARN( True, text "quantifying over a TyVar" <+> ppr tkv) - return (Just tkv) -- For associated types, we have the class variables - -- in scope, and they are TyVars not TcTyVars + | not (isTcTyVar tkv) -- I don't think this can ever happen. + -- Hence the assert + = ASSERT2( False, text "quantifying over a TyVar" <+> ppr tkv) + return (Just tkv) | otherwise = do { deflt_done <- defaultTyVar default_kind tkv From git at git.haskell.org Mon Nov 26 17:48:52 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Nov 2018 17:48:52 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Comments only (9980257) Message-ID: <20181126174852.75B2C3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/99802578f8a900a102bf20c1e812c4b899dc556a/ghc >--------------------------------------------------------------- commit 99802578f8a900a102bf20c1e812c4b899dc556a Author: Simon Peyton Jones Date: Fri Nov 9 17:46:05 2018 +0000 Comments only >--------------------------------------------------------------- 99802578f8a900a102bf20c1e812c4b899dc556a compiler/typecheck/TcMType.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/compiler/typecheck/TcMType.hs b/compiler/typecheck/TcMType.hs index 9edad0f..6d9f3ca 100644 --- a/compiler/typecheck/TcMType.hs +++ b/compiler/typecheck/TcMType.hs @@ -662,7 +662,8 @@ but this restriction was dropped, and ScopedTypeVariables can now refer to full types (GHC Proposal 29). The remaining uses of newTyVarTyVars are -* in kind signatures, see Note [Kind generalisation and TyVarTvs] +* In kind signatures, see + TcTyClsDecls Note [Inferring kinds for type declarations] and Note [Use TyVarTvs in kind-checking pass] * in partial type signatures, see Note [Quantified variables in partial type signatures] -} From git at git.haskell.org Mon Nov 26 17:48:55 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Nov 2018 17:48:55 +0000 (UTC) Subject: [commit: ghc] wip/T15809: More progress (fbb64e4) Message-ID: <20181126174855.8F8553A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/fbb64e47001b1d376441a6321a727654cde3ae01/ghc >--------------------------------------------------------------- commit fbb64e47001b1d376441a6321a727654cde3ae01 Author: Simon Peyton Jones Date: Tue Nov 6 17:44:25 2018 +0000 More progress >--------------------------------------------------------------- fbb64e47001b1d376441a6321a727654cde3ae01 compiler/typecheck/TcHsType.hs | 290 +++++++++------------ compiler/typecheck/TcMType.hs | 122 ++++----- compiler/typecheck/TcTyClsDecls.hs | 228 ++++++++-------- compiler/typecheck/TcValidity.hs | 19 +- testsuite/tests/dependent/should_compile/T14880.hs | 1 - .../tests/dependent/should_compile/T15743e.stderr | 2 +- testsuite/tests/ghci/scripts/T15591.hs | 5 + testsuite/tests/ghci/scripts/T15743b.stdout | 2 +- testsuite/tests/ghci/scripts/T7873.stderr | 2 +- .../tests/indexed-types/should_fail/T13972.stderr | 2 +- testsuite/tests/polykinds/T11203.stderr | 2 +- testsuite/tests/polykinds/T11821a.stderr | 2 +- testsuite/tests/polykinds/T15592b.stderr | 2 +- .../tests/typecheck/should_fail/T13983.stderr | 2 +- testsuite/tests/typecheck/should_fail/T2688.stderr | 6 +- 15 files changed, 317 insertions(+), 370 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 fbb64e47001b1d376441a6321a727654cde3ae01 From git at git.haskell.org Mon Nov 26 17:48:58 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Nov 2018 17:48:58 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Finally done (2f02df6) Message-ID: <20181126174858.926983A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/2f02df69987a2682420ea4361d72c0d582cbdea2/ghc >--------------------------------------------------------------- commit 2f02df69987a2682420ea4361d72c0d582cbdea2 Author: Simon Peyton Jones Date: Wed Nov 7 12:51:32 2018 +0000 Finally done >--------------------------------------------------------------- 2f02df69987a2682420ea4361d72c0d582cbdea2 compiler/typecheck/TcHsType.hs | 128 +++----------- compiler/typecheck/TcMType.hs | 63 +++---- compiler/typecheck/TcTyClsDecls.hs | 188 ++++++++++++++++----- compiler/typecheck/TcValidity.hs | 77 ++++++--- .../dependent/should_fail/BadTelescope.stderr | 7 +- .../dependent/should_fail/BadTelescope3.stderr | 6 +- .../dependent/should_fail/BadTelescope4.stderr | 13 +- .../tests/dependent/should_fail/T13895.stderr | 37 +--- .../tests/dependent/should_fail/T14066f.stderr | 6 +- .../tests/dependent/should_fail/T14066g.stderr | 8 +- .../tests/dependent/should_fail/T15591b.stderr | 9 +- .../tests/dependent/should_fail/T15591c.stderr | 9 +- .../tests/dependent/should_fail/T15743c.stderr | 13 +- .../tests/dependent/should_fail/T15743d.stderr | 13 +- testsuite/tests/ghci/scripts/T15591.hs | 9 +- testsuite/tests/ghci/scripts/T15591.stdout | 6 +- 16 files changed, 312 insertions(+), 280 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 2f02df69987a2682420ea4361d72c0d582cbdea2 From git at git.haskell.org Mon Nov 26 17:49:01 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Nov 2018 17:49:01 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Comments and alpha-renaming (5104ded) Message-ID: <20181126174901.939523A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/5104ded3055d2fe1eab1c38d11055e125df88227/ghc >--------------------------------------------------------------- commit 5104ded3055d2fe1eab1c38d11055e125df88227 Author: Simon Peyton Jones Date: Wed Nov 7 23:26:05 2018 +0000 Comments and alpha-renaming >--------------------------------------------------------------- 5104ded3055d2fe1eab1c38d11055e125df88227 compiler/typecheck/TcHsType.hs | 2 -- compiler/typecheck/TcInstDcls.hs | 10 +++++----- compiler/typecheck/TcMType.hs | 2 +- compiler/typecheck/TcSimplify.hs | 7 ++++--- 4 files changed, 10 insertions(+), 11 deletions(-) diff --git a/compiler/typecheck/TcHsType.hs b/compiler/typecheck/TcHsType.hs index 06cf0db..99bc57e 100644 --- a/compiler/typecheck/TcHsType.hs +++ b/compiler/typecheck/TcHsType.hs @@ -1745,7 +1745,6 @@ kcImplicitTKBndrs = kcImplicitTKBndrsX newFlexiKindedTyVarTyVar -- | Bring implicitly quantified type/kind variables into scope during -- kind checking. The returned TcTyVars are in 1-1 correspondence --- with the names passed in. --- Note [Use TyVarTvs in kind-checking pass] in TcTyClsDecls. kcImplicitTKBndrsX :: (Name -> TcM TcTyVar) -- new_tv function -> [Name] -- of the vars -> TcM a @@ -2066,7 +2065,6 @@ kcLookupTcTyCon nm -- Never emits constraints, though the thing_inside might. kcTyClTyVars :: Name -> TcM a -> TcM a kcTyClTyVars tycon_name thing_inside - -- See Note [Use TyVarTvs in kind-checking pass] in TcTyClsDecls = do { tycon <- kcLookupTcTyCon tycon_name ; tcExtendNameTyVarEnv (tcTyConScopedTyVars tycon) $ thing_inside } diff --git a/compiler/typecheck/TcInstDcls.hs b/compiler/typecheck/TcInstDcls.hs index 84f43e9..63c565d 100644 --- a/compiler/typecheck/TcInstDcls.hs +++ b/compiler/typecheck/TcInstDcls.hs @@ -465,14 +465,14 @@ tcLocalInstDecl (L _ (XInstDecl _)) = panic "tcLocalInstDecl" tcClsInstDecl :: LClsInstDecl GhcRn -> TcM ([InstInfo GhcRn], [FamInst], [DerivInfo]) -- The returned DerivInfos are for any associated data families -tcClsInstDecl (L loc (ClsInstDecl { cid_poly_ty = poly_ty, cid_binds = binds +tcClsInstDecl (L loc (ClsInstDecl { cid_poly_ty = hs_ty, cid_binds = binds , cid_sigs = uprags, cid_tyfam_insts = ats , cid_overlap_mode = overlap_mode , cid_datafam_insts = adts })) = setSrcSpan loc $ - addErrCtxt (instDeclCtxt1 poly_ty) $ + addErrCtxt (instDeclCtxt1 hs_ty) $ do { (tyvars, theta, clas, inst_tys) - <- tcHsClsInstType (InstDeclCtxt False) poly_ty + <- tcHsClsInstType (InstDeclCtxt False) hs_ty -- NB: tcHsClsInstType does checkValidInstance ; tcExtendTyVarEnv tyvars $ @@ -481,7 +481,7 @@ tcClsInstDecl (L loc (ClsInstDecl { cid_poly_ty = poly_ty, cid_binds = binds mb_info = Just (clas, tyvars, mini_env) -- Next, process any associated types. - ; traceTc "tcLocalInstDecl" (ppr poly_ty) + ; traceTc "tcLocalInstDecl" (ppr hs_ty) ; tyfam_insts0 <- mapAndRecoverM (tcTyFamInstDecl mb_info) ats ; datafam_stuff <- mapAndRecoverM (tcDataFamInstDecl mb_info) adts ; let (datafam_insts, m_deriv_infos) = unzip datafam_stuff @@ -500,7 +500,7 @@ tcClsInstDecl (L loc (ClsInstDecl { cid_poly_ty = poly_ty, cid_binds = binds -- Finally, construct the Core representation of the instance. -- (This no longer includes the associated types.) - ; dfun_name <- newDFunName clas inst_tys (getLoc (hsSigType poly_ty)) + ; dfun_name <- newDFunName clas inst_tys (getLoc (hsSigType hs_ty)) -- Dfun location is that of instance *header* ; ispec <- newClsInst (fmap unLoc overlap_mode) dfun_name tyvars theta diff --git a/compiler/typecheck/TcMType.hs b/compiler/typecheck/TcMType.hs index 8192f75..9edad0f 100644 --- a/compiler/typecheck/TcMType.hs +++ b/compiler/typecheck/TcMType.hs @@ -1499,7 +1499,7 @@ defaultTyVar default_kind tv -- Do not default TyVarTvs. Doing so would violate the invariants -- on TyVarTvs; see Note [Signature skolems] in TcType. -- Trac #13343 is an example; #14555 is another - -- See Note [Kind generalisation and TyVarTvs] + -- See Note [Inferring kinds for type declarations] in TcTyClsDecls = return False diff --git a/compiler/typecheck/TcSimplify.hs b/compiler/typecheck/TcSimplify.hs index 750b621..e1a3532 100644 --- a/compiler/typecheck/TcSimplify.hs +++ b/compiler/typecheck/TcSimplify.hs @@ -2008,9 +2008,10 @@ promoteTyVarTcS tv defaultTyVarTcS :: TcTyVar -> TcS Bool defaultTyVarTcS the_tv | isRuntimeRepVar the_tv - , not (isTyVarTyVar the_tv) -- TyVarTvs should only be unified with a tyvar - -- never with a type; c.f. TcMType.defaultTyVar - -- See Note [Kind generalisation and TyVarTvs] + , not (isTyVarTyVar the_tv) + -- TyVarTvs should only be unified with a tyvar + -- never with a type; c.f. TcMType.defaultTyVar + -- and Note [Inferring kinds for type declarations] in TcTyClsDecls = do { traceTcS "defaultTyVarTcS RuntimeRep" (ppr the_tv) ; unifyTyVar the_tv liftedRepTy ; return True } From git at git.haskell.org Mon Nov 26 17:49:04 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Nov 2018 17:49:04 +0000 (UTC) Subject: [commit: ghc] wip/T15809: More progress (069307d) Message-ID: <20181126174904.A19A93A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/069307d2291faafb2d978cb54dbc85e69c00a7bb/ghc >--------------------------------------------------------------- commit 069307d2291faafb2d978cb54dbc85e69c00a7bb Author: Simon Peyton Jones Date: Wed Nov 7 07:52:16 2018 +0000 More progress A fixup in TcPatSyn >--------------------------------------------------------------- 069307d2291faafb2d978cb54dbc85e69c00a7bb compiler/typecheck/TcMType.hs | 48 ++++++++++++++++---------------- compiler/typecheck/TcPatSyn.hs | 56 +++++++++++++++++++++++++++++++------- compiler/typecheck/TcSimplify.hs | 7 +++-- compiler/typecheck/TcTyClsDecls.hs | 1 + 4 files changed, 75 insertions(+), 37 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 069307d2291faafb2d978cb54dbc85e69c00a7bb From git at git.haskell.org Mon Nov 26 17:49:07 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Nov 2018 17:49:07 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Combine kcImplicitTKBndrs and tcImplicitTKBndrs (7c61052) Message-ID: <20181126174907.AF3B43A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/7c61052d1162626382f234612541da187cce694f/ghc >--------------------------------------------------------------- commit 7c61052d1162626382f234612541da187cce694f Author: Simon Peyton Jones Date: Mon Nov 12 08:30:33 2018 +0000 Combine kcImplicitTKBndrs and tcImplicitTKBndrs Based on a conversation with Richard on Friday, this patch * Abolishes the distinction between kcImplicitTKBndrs and tcImplicitTKBndrs; now it is bindImplicitTKBndrs * Same for kc/tcExplicitTKBndrs * tcImplicitTKBndrs no longer does a solveLocalEqualities and sort; the caller does that Much nicer. Not quite working yet though >--------------------------------------------------------------- 7c61052d1162626382f234612541da187cce694f compiler/typecheck/TcBackpack.hs | 2 +- compiler/typecheck/TcDerivInfer.hs | 2 +- compiler/typecheck/TcHsType.hs | 238 +++++++++------------ compiler/typecheck/TcInstDcls.hs | 2 +- compiler/typecheck/TcRnMonad.hs | 4 +- compiler/typecheck/TcRules.hs | 34 ++- compiler/typecheck/TcSMonad.hs | 4 +- compiler/typecheck/TcSigs.hs | 46 ++-- compiler/typecheck/TcSimplify.hs | 18 +- compiler/typecheck/TcSplice.hs | 4 +- compiler/typecheck/TcTyClsDecls.hs | 169 ++++++++------- compiler/typecheck/TcUnify.hs | 33 +-- testsuite/tests/dependent/should_compile/T13910.hs | 10 +- .../tests/indexed-types/should_compile/T12369.hs | 10 + testsuite/tests/indexed-types/should_fail/T7938.hs | 6 +- 15 files changed, 290 insertions(+), 292 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 7c61052d1162626382f234612541da187cce694f From git at git.haskell.org Mon Nov 26 17:49:10 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Nov 2018 17:49:10 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Get rid of kcLHsQTyVarBndrs (0ba23e8) Message-ID: <20181126174910.B1A0C3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/0ba23e868b4e45a42e2214bef50304020423d6e5/ghc >--------------------------------------------------------------- commit 0ba23e868b4e45a42e2214bef50304020423d6e5 Author: Simon Peyton Jones Date: Mon Nov 12 12:08:33 2018 +0000 Get rid of kcLHsQTyVarBndrs >--------------------------------------------------------------- 0ba23e868b4e45a42e2214bef50304020423d6e5 compiler/typecheck/TcHsType.hs | 289 +++++++++++++++++++-------------------- compiler/typecheck/TcMType.hs | 2 +- compiler/typecheck/TcValidity.hs | 21 --- 3 files changed, 138 insertions(+), 174 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 0ba23e868b4e45a42e2214bef50304020423d6e5 From git at git.haskell.org Mon Nov 26 17:49:13 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Nov 2018 17:49:13 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Start to eliminate tcFamTyPats (a787fbb) Message-ID: <20181126174913.AE61D3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/a787fbb80837884171fef369eed5a4f6a4a9622e/ghc >--------------------------------------------------------------- commit a787fbb80837884171fef369eed5a4f6a4a9622e Author: Simon Peyton Jones Date: Mon Nov 12 13:41:33 2018 +0000 Start to eliminate tcFamTyPats >--------------------------------------------------------------- a787fbb80837884171fef369eed5a4f6a4a9622e compiler/typecheck/TcHsType.hs | 1 + compiler/typecheck/TcTyClsDecls.hs | 43 ++++++++++++++++++++++++++------------ 2 files changed, 31 insertions(+), 13 deletions(-) diff --git a/compiler/typecheck/TcHsType.hs b/compiler/typecheck/TcHsType.hs index 5a8dbb5..ac6355c 100644 --- a/compiler/typecheck/TcHsType.hs +++ b/compiler/typecheck/TcHsType.hs @@ -22,6 +22,7 @@ module TcHsType ( UserTypeCtxt(..), bindImplicitTKBndrs_Skol, bindImplicitTKBndrs_Q_Skol, bindExplicitTKBndrs_Skol, bindExplicitTKBndrs_Q_Skol, + ContextKind(..), -- Type checking type and class decls kcLookupTcTyCon, kcTyClTyVars, tcTyClTyVars, diff --git a/compiler/typecheck/TcTyClsDecls.hs b/compiler/typecheck/TcTyClsDecls.hs index 6edf469..e773da7 100644 --- a/compiler/typecheck/TcTyClsDecls.hs +++ b/compiler/typecheck/TcTyClsDecls.hs @@ -1777,29 +1777,46 @@ tcTyFamInstEqn :: TcTyCon -> Maybe ClsInstInfo -> LTyFamInstEqn GhcRn -- Needs to be here, not in TcInstDcls, because closed families -- (typechecked here) have TyFamInstEqns - tcTyFamInstEqn fam_tc mb_clsinfo - (dL->L loc (HsIB { hsib_ext = imp_vars - , hsib_body = FamEqn { feqn_tycon = (dL->L _ eqn_tc_name) - , feqn_bndrs = mb_expl_bndrs - , feqn_pats = pats - , feqn_rhs = hs_ty }})) + eqn@(dl->L loc (HsIB { hsib_ext = imp_vars + , hsib_body = FamEqn { feqn_tycon = L _ eqn_tc_name + , feqn_bndrs = mb_expl_bndrs + , feqn_pats = hs_pats + , feqn_rhs = hs_ty }})) = ASSERT( getName fam_tc == eqn_tc_name ) setSrcSpan loc $ - tcFamTyPats fam_tc mb_clsinfo imp_vars mb_expl_bndrs pats - (kcTyFamEqnRhs mb_clsinfo hs_ty) $ - \tvs pats res_kind -> - do { traceTc "tcTyFamInstEqn {" (ppr eqn_tc_name <+> ppr pats) - ; rhs_ty <- solveEqualities $ tcCheckLHsType hs_ty res_kind - ; (ze, tvs') <- zonkTyBndrs tvs + do { traceTc "tcTyFamInstEqn {" (ppr eqn_tc_name <+> ppr hs_pats) + ; (_imp_tvs, (_exp_tvs, ((pats, rhs_ty)))) + <- pushTcLevelM_ $ + solveEqualities $ + bindImplicitTKBndrs_Q_Skol imp_vars $ + bindExplicitTKBndrs_Q_Skol AnyKind (mb_expl_bndrs `orElse` []) $ + do { let fam_name = tyConName fam_tc + lhs_fun = L loc (HsTyVar noExt NotPromoted + (L loc fam_name)) + fun_ty = mkTyConApp fam_tc [] + fun_kind = tyConKind fam_tc + + ; (_, pats, res_kind) <- tcInferApps typeLevelMode Nothing + lhs_fun fun_ty fun_kind hs_pats + + ; rhs_ty <- tcCheckLHsType hs_ty res_kind + ; return (pats, rhs_ty) } + + ; dvs <- candidateQTyVarsOfTypes (rhs_ty : pats) + ; qtkvs <- quantifyTyVars emptyVarSet dvs + + ; (ze, tvs') <- zonkTyBndrs qtkvs ; pats' <- zonkTcTypesToTypesX ze pats ; rhs_ty' <- zonkTcTypeToTypeX ze rhs_ty ; traceTc "tcTyFamInstEqn }" (ppr fam_tc <+> pprTyVars tvs') ; return (mkCoAxBranch tvs' [] pats' rhs_ty' (map (const Nominal) tvs') loc) } + + tcTyFamInstEqn _ _ (dl->L _ (XHsImplicitBndrs _)) = panic "tcTyFamInstEqn" -tcTyFamInstEqn _ _ (dL->L _ (HsIB _ (XFamEqn _))) = panic "tcTyFamInstEqn" +tcTyFamInstEqn _ _ (dl->L _ (HsIB _ (XFamEqn _))) = panic "tcTyFamInstEqn" kcDataDefn :: Maybe (VarEnv Kind) -- ^ Possibly, instantiations for vars -- (associated types only) From git at git.haskell.org Mon Nov 26 17:49:17 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Nov 2018 17:49:17 +0000 (UTC) Subject: [commit: ghc] wip/T15809: More progress on tcFamTyPats (74f5b0e) Message-ID: <20181126174917.9DCBA3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/74f5b0e4265de2c70c4a2186c393dec2419b1686/ghc >--------------------------------------------------------------- commit 74f5b0e4265de2c70c4a2186c393dec2419b1686 Author: Simon Peyton Jones Date: Mon Nov 12 17:21:55 2018 +0000 More progress on tcFamTyPats This fixes Trac #15740 >--------------------------------------------------------------- 74f5b0e4265de2c70c4a2186c393dec2419b1686 compiler/typecheck/TcHsType.hs | 26 ++++++++++------- compiler/typecheck/TcMType.hs | 4 +-- compiler/typecheck/TcTyClsDecls.hs | 51 +++++++++++++++++++++++++++------ compiler/typecheck/TcValidity.hs | 23 ++++++++------- testsuite/tests/polykinds/T13985.stderr | 10 ++----- testsuite/tests/polykinds/T15740.hs | 15 ++++++++++ testsuite/tests/polykinds/T15740.stderr | 6 ++++ testsuite/tests/polykinds/T15740a.hs | 12 ++++++++ testsuite/tests/polykinds/all.T | 2 ++ 9 files changed, 109 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 74f5b0e4265de2c70c4a2186c393dec2419b1686 From git at git.haskell.org Mon Nov 26 17:49:20 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Nov 2018 17:49:20 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Wibbles (1651c0a) Message-ID: <20181126174920.93FFE3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/1651c0adf42896cca41ce7b3ecf0d09f55fd23fc/ghc >--------------------------------------------------------------- commit 1651c0adf42896cca41ce7b3ecf0d09f55fd23fc Author: Simon Peyton Jones Date: Mon Nov 12 17:43:48 2018 +0000 Wibbles >--------------------------------------------------------------- 1651c0adf42896cca41ce7b3ecf0d09f55fd23fc testsuite/tests/indexed-types/should_fail/T7536.stderr | 8 ++++---- testsuite/tests/indexed-types/should_fail/T7938.hs | 6 ++---- testsuite/tests/indexed-types/should_fail/T7938.stderr | 2 +- 3 files changed, 7 insertions(+), 9 deletions(-) diff --git a/testsuite/tests/indexed-types/should_fail/T7536.stderr b/testsuite/tests/indexed-types/should_fail/T7536.stderr index 9e7ed30..34a393e 100644 --- a/testsuite/tests/indexed-types/should_fail/T7536.stderr +++ b/testsuite/tests/indexed-types/should_fail/T7536.stderr @@ -1,5 +1,5 @@ -T7536.hs:8:15: - Family instance purports to bind type variable ‘a’ - but the real LHS (expanding synonyms) is: TF Int = ... - In the type instance declaration for ‘TF’ +T7536.hs:8:15: error: + • LHS of family instance fails to bind type variable ‘a’ + The real LHS (expanding synonyms) is: TF Int + • In the type instance declaration for ‘TF’ diff --git a/testsuite/tests/indexed-types/should_fail/T7938.hs b/testsuite/tests/indexed-types/should_fail/T7938.hs index f1e8266..246015d 100644 --- a/testsuite/tests/indexed-types/should_fail/T7938.hs +++ b/testsuite/tests/indexed-types/should_fail/T7938.hs @@ -8,7 +8,5 @@ data KProxy (a :: *) = KP class Foo (a :: k1) (b :: k2) where type Bar a --- instance Foo (a :: k1) (b :: k2) where --- type Bar a = (KP :: KProxy k2) - --- \ No newline at end of file +instance Foo (a :: k1) (b :: k2) where + type Bar a = (KP :: KProxy k2) diff --git a/testsuite/tests/indexed-types/should_fail/T7938.stderr b/testsuite/tests/indexed-types/should_fail/T7938.stderr index 890be7b..5751c4e 100644 --- a/testsuite/tests/indexed-types/should_fail/T7938.stderr +++ b/testsuite/tests/indexed-types/should_fail/T7938.stderr @@ -1,6 +1,6 @@ T7938.hs:12:17: error: - • Expected a type, but ‘KP :: KProxy k2’ has kind ‘KProxy k4’ + • Expected a type, but ‘KP :: KProxy k2’ has kind ‘KProxy k2’ • In the type ‘(KP :: KProxy k2)’ In the type instance declaration for ‘Bar’ In the instance declaration for ‘Foo (a :: k1) (b :: k2)’ From git at git.haskell.org Mon Nov 26 17:49:23 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Nov 2018 17:49:23 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Much more progress on tcFamTyPats (f147f82) Message-ID: <20181126174923.A86F83A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/f147f82f5b71b70d36eacb02ffe62279dd93fee5/ghc >--------------------------------------------------------------- commit f147f82f5b71b70d36eacb02ffe62279dd93fee5 Author: Simon Peyton Jones Date: Tue Nov 13 15:36:28 2018 +0000 Much more progress on tcFamTyPats Main thing left to do: data family instances A handful of validate failures Reporting unused binders correctly polykinds/T13985 indexed-types/should_fail/ExplicitForAllFams4a indexed-types/should_fail/ExplicitForAllFams4b extra error (ok) polykinds/T8616 polykinds/T14846 >--------------------------------------------------------------- f147f82f5b71b70d36eacb02ffe62279dd93fee5 compiler/prelude/TysPrim.hs | 19 +- compiler/typecheck/TcHsType.hs | 4 +- compiler/typecheck/TcInstDcls.hs | 14 +- compiler/typecheck/TcTyClsDecls.hs | 236 ++++++++++----------- compiler/types/Type.hs | 32 ++- .../tests/th/TH_reifyExplicitForAllFams.stderr | 6 +- .../typecheck/should_fail/LevPolyBounded.stderr | 5 + testsuite/tests/typecheck/should_fail/T14607.hs | 2 +- .../tests/typecheck/should_fail/T14607.stderr | 17 +- .../tests/typecheck/should_fail/T6018fail.stderr | 2 +- testsuite/tests/typecheck/should_fail/all.T | 2 +- 11 files changed, 168 insertions(+), 171 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 f147f82f5b71b70d36eacb02ffe62279dd93fee5 From git at git.haskell.org Mon Nov 26 17:49:26 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Nov 2018 17:49:26 +0000 (UTC) Subject: [commit: ghc] wip/T15809: More progress with data instances (412a735) Message-ID: <20181126174926.A3C7F3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/412a735dc804e0f79639dba30cfd62577038b1a0/ghc >--------------------------------------------------------------- commit 412a735dc804e0f79639dba30cfd62577038b1a0 Author: Simon Peyton Jones Date: Wed Nov 14 15:25:45 2018 +0000 More progress with data instances Slightly controversially, I adjusted T15725 to have data Sing :: k -> * rather than data Sing :: forall k. k -> * See a fc-call thread. We could revisit this if need be; it's not fundamental to the line of progress. >--------------------------------------------------------------- 412a735dc804e0f79639dba30cfd62577038b1a0 compiler/typecheck/TcDeriv.hs | 2 +- compiler/typecheck/TcInstDcls.hs | 1 - compiler/typecheck/TcTyClsDecls.hs | 17 +++++++++++------ testsuite/tests/dependent/should_compile/T15725.hs | 6 +++--- testsuite/tests/ghci/scripts/T10059.stdout | 6 +++--- testsuite/tests/ghci/scripts/ghci059.stdout | 2 +- 6 files changed, 19 insertions(+), 15 deletions(-) diff --git a/compiler/typecheck/TcDeriv.hs b/compiler/typecheck/TcDeriv.hs index 4ee0f23..05c7958 100644 --- a/compiler/typecheck/TcDeriv.hs +++ b/compiler/typecheck/TcDeriv.hs @@ -786,7 +786,7 @@ deriveTyData tvs tc tc_args mb_deriv_strat deriv_pred -- we want to drop type variables from T so that (C d (T a)) is well-kinded let (arg_kinds, _) = splitFunTys cls_arg_kind n_args_to_drop = length arg_kinds - n_args_to_keep = tyConArity tc - n_args_to_drop + n_args_to_keep = length tc_args - n_args_to_drop (tc_args_to_keep, args_to_drop) = splitAt n_args_to_keep tc_args inst_ty_kind = typeKind (mkTyConApp tc tc_args_to_keep) diff --git a/compiler/typecheck/TcInstDcls.hs b/compiler/typecheck/TcInstDcls.hs index 86ed84a..d1081a2 100644 --- a/compiler/typecheck/TcInstDcls.hs +++ b/compiler/typecheck/TcInstDcls.hs @@ -738,7 +738,6 @@ tcDataFamInstDecl mb_clsinfo -- Kind check type patterns ; let exp_bndrs = mb_bndrs `orElse` [] data_ctxt = DataKindCtxt (unLoc fam_name) - ; ; (_, (_, (pats, stupid_theta, res_kind))) <- pushTcLevelM_ $ diff --git a/compiler/typecheck/TcTyClsDecls.hs b/compiler/typecheck/TcTyClsDecls.hs index 2adc1fd..ea3c067 100644 --- a/compiler/typecheck/TcTyClsDecls.hs +++ b/compiler/typecheck/TcTyClsDecls.hs @@ -1501,17 +1501,22 @@ tcFamDecl1 parent (FamilyDecl { fdInfo = fam_info { traceTc "data family:" (ppr tc_name) ; checkFamFlag tc_name - -- Check the kind signature, if any. - -- Data families might have a variable return kind. - -- See See Note [Arity of data families] in FamInstEnv. - ; (extra_binders, final_res_kind) <- tcDataKindSig binders res_kind + -- Check that the result kind is OK + -- We allow things like + -- data family T (a :: Type) :: forall k. k -> Type + -- We treat T as having arity 1, but result kind forall k. k -> Type + -- But we want to check that the result kind finishes in + -- Type or a kind-variable + -- For the latter, consider + -- data family D a :: forall k. Type -> k + ; let (_, final_res_kind) = splitPiTys res_kind ; checkTc (tcIsLiftedTypeKind final_res_kind || isJust (tcGetCastedTyVar_maybe final_res_kind)) (badKindSig False res_kind) ; tc_rep_name <- newTyConRepName tc_name - ; let tycon = mkFamilyTyCon tc_name (binders `chkAppend` extra_binders) - final_res_kind + ; let tycon = mkFamilyTyCon tc_name binders + res_kind (resultVariableName sig) (DataFamilyTyCon tc_rep_name) parent NotInjective diff --git a/testsuite/tests/dependent/should_compile/T15725.hs b/testsuite/tests/dependent/should_compile/T15725.hs index a5f259e..1e2e171 100644 --- a/testsuite/tests/dependent/should_compile/T15725.hs +++ b/testsuite/tests/dependent/should_compile/T15725.hs @@ -23,12 +23,12 @@ instance SC Identity ------------------------------------------------------------------------------- -data family Sing :: forall k. k -> Type -data instance Sing :: forall a. Identity a -> Type where +data family Sing :: k -> Type +data instance Sing :: Identity a -> Type where SIdentity :: Sing x -> Sing ('Identity x) newtype Par1 p = Par1 p -data instance Sing :: forall p. Par1 p -> Type where +data instance Sing :: Par1 p -> Type where SPar1 :: Sing x -> Sing ('Par1 x) type family Rep1 (f :: Type -> Type) :: Type -> Type diff --git a/testsuite/tests/ghci/scripts/T10059.stdout b/testsuite/tests/ghci/scripts/T10059.stdout index 92fbb45..955c95a 100644 --- a/testsuite/tests/ghci/scripts/T10059.stdout +++ b/testsuite/tests/ghci/scripts/T10059.stdout @@ -1,4 +1,4 @@ -class (a ~ b) => (~) (a :: k0) (b :: k0) -- Defined in ‘GHC.Types’ -(~) :: k0 -> k0 -> Constraint -class (a GHC.Prim.~# b) => (~) (a :: k0) (b :: k0) +class (a ~ b) => (~) (a :: k) (b :: k) -- Defined in ‘GHC.Types’ +(~) :: k -> k -> Constraint +class (a GHC.Prim.~# b) => (~) (a :: k) (b :: k) -- Defined in ‘GHC.Types’ diff --git a/testsuite/tests/ghci/scripts/ghci059.stdout b/testsuite/tests/ghci/scripts/ghci059.stdout index 9e9adb9..7e734f1 100644 --- a/testsuite/tests/ghci/scripts/ghci059.stdout +++ b/testsuite/tests/ghci/scripts/ghci059.stdout @@ -4,6 +4,6 @@ It is not a class. Please see section 9.14.4 of the user's guide for details. -} type role Coercible representational representational -class Coercible a b => Coercible (a :: k0) (b :: k0) +class Coercible a b => Coercible (a :: k) (b :: k) -- Defined in ‘GHC.Types’ coerce :: Coercible a b => a -> b -- Defined in ‘GHC.Prim’ From git at git.haskell.org Mon Nov 26 17:49:29 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Nov 2018 17:49:29 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Data family instances working, I think (98331d5) Message-ID: <20181126174929.A81A13A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/98331d5472fd5612195c11d359f0f3b0e1eea04b/ghc >--------------------------------------------------------------- commit 98331d5472fd5612195c11d359f0f3b0e1eea04b Author: Simon Peyton Jones Date: Wed Nov 14 11:36:22 2018 +0000 Data family instances working, I think >--------------------------------------------------------------- 98331d5472fd5612195c11d359f0f3b0e1eea04b compiler/typecheck/TcInstDcls.hs | 154 +++++++++++++++++++++++++++++++++++++ compiler/typecheck/TcTyClsDecls.hs | 69 +++++++++-------- 2 files changed, 191 insertions(+), 32 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 98331d5472fd5612195c11d359f0f3b0e1eea04b From git at git.haskell.org Mon Nov 26 17:49:32 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Nov 2018 17:49:32 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Wibbles (95544de) Message-ID: <20181126174932.A93F93A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/95544de8f4d6679e8e12f871593d32143d2255d4/ghc >--------------------------------------------------------------- commit 95544de8f4d6679e8e12f871593d32143d2255d4 Author: Simon Peyton Jones Date: Wed Nov 14 17:28:35 2018 +0000 Wibbles >--------------------------------------------------------------- 95544de8f4d6679e8e12f871593d32143d2255d4 compiler/typecheck/TcHsType.hs | 2 +- compiler/typecheck/TcInstDcls.hs | 188 ++++++++------------------------------- 2 files changed, 36 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 95544de8f4d6679e8e12f871593d32143d2255d4 From git at git.haskell.org Mon Nov 26 17:49:35 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Nov 2018 17:49:35 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Print tycon arity in -ddump-types (1288a96) Message-ID: <20181126174935.AD9B33A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/1288a96dc1fdd75f9cf40967d09e0f42269b6716/ghc >--------------------------------------------------------------- commit 1288a96dc1fdd75f9cf40967d09e0f42269b6716 Author: Simon Peyton Jones Date: Wed Nov 14 14:57:08 2018 +0000 Print tycon arity in -ddump-types >--------------------------------------------------------------- 1288a96dc1fdd75f9cf40967d09e0f42269b6716 compiler/typecheck/TcRnDriver.hs | 2 +- testsuite/tests/dependent/should_compile/T15743.stderr | 2 +- testsuite/tests/dependent/should_compile/T15743e.stderr | 4 ++-- .../tests/indexed-types/should_compile/T15711.stderr | 4 ++-- .../tests/indexed-types/should_compile/T3017.stderr | 6 +++--- testsuite/tests/partial-sigs/should_compile/ADT.stderr | 2 +- .../should_compile/DataFamilyInstanceLHS.stderr | 4 ++-- .../tests/partial-sigs/should_compile/Meltdown.stderr | 2 +- .../NamedWildcardInDataFamilyInstanceLHS.stderr | 4 ++-- .../NamedWildcardInTypeFamilyInstanceLHS.stderr | 2 +- .../tests/partial-sigs/should_compile/SkipMany.stderr | 2 +- .../should_compile/TypeFamilyInstanceLHS.stderr | 2 +- testsuite/tests/polykinds/T15592.stderr | 2 +- testsuite/tests/polykinds/T15592b.stderr | 4 ++-- testsuite/tests/roles/should_compile/Roles1.stderr | 14 +++++++------- testsuite/tests/roles/should_compile/Roles14.stderr | 2 +- testsuite/tests/roles/should_compile/Roles2.stderr | 4 ++-- testsuite/tests/roles/should_compile/Roles3.stderr | 16 ++++++++-------- testsuite/tests/roles/should_compile/Roles4.stderr | 6 +++--- testsuite/tests/roles/should_compile/T8958.stderr | 6 +++--- testsuite/tests/th/TH_Roles2.stderr | 2 +- testsuite/tests/typecheck/should_compile/T12763.stderr | 2 +- testsuite/tests/typecheck/should_compile/tc231.stderr | 6 +++--- 23 files changed, 50 insertions(+), 50 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 1288a96dc1fdd75f9cf40967d09e0f42269b6716 From git at git.haskell.org Mon Nov 26 17:49:38 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Nov 2018 17:49:38 +0000 (UTC) Subject: [commit: ghc] wip/T15809: More progress on reporting unbound variables (3ff0120) Message-ID: <20181126174938.AF61F3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/3ff012021d87b76651399effbe26ec1c0c5cd235/ghc >--------------------------------------------------------------- commit 3ff012021d87b76651399effbe26ec1c0c5cd235 Author: Simon Peyton Jones Date: Thu Nov 15 01:16:12 2018 +0000 More progress on reporting unbound variables >--------------------------------------------------------------- 3ff012021d87b76651399effbe26ec1c0c5cd235 compiler/typecheck/TcHsType.hs | 16 +- compiler/typecheck/TcInstDcls.hs | 64 ++-- compiler/typecheck/TcTyClsDecls.hs | 357 +++++---------------- compiler/typecheck/TcValidity.hs | 19 +- .../should_fail/ExplicitForAllFams4a.stderr | 6 +- .../should_fail/ExplicitForAllFams4b.stderr | 30 +- testsuite/tests/polykinds/T13985.stderr | 25 +- 7 files changed, 166 insertions(+), 351 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 3ff012021d87b76651399effbe26ec1c0c5cd235 From git at git.haskell.org Mon Nov 26 17:49:41 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Nov 2018 17:49:41 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Better validity checks, simplification (e49adfb) Message-ID: <20181126174941.BA1353A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/e49adfb7cfb2737c422af7b4ce76ab10eb4be0a1/ghc >--------------------------------------------------------------- commit e49adfb7cfb2737c422af7b4ce76ab10eb4be0a1 Author: Simon Peyton Jones Date: Thu Nov 15 23:29:34 2018 +0000 Better validity checks, simplification >--------------------------------------------------------------- e49adfb7cfb2737c422af7b4ce76ab10eb4be0a1 compiler/typecheck/TcGenDeriv.hs | 3 +- compiler/typecheck/TcHsType.hs | 66 +++--- compiler/typecheck/TcInstDcls.hs | 43 +++- compiler/typecheck/TcTyClsDecls.hs | 223 ++++++++++++++++++- compiler/typecheck/TcValidity.hs | 239 ++------------------- .../should_fail/ExplicitForAllFams4b.stderr | 63 ++++-- .../indexed-types/should_fail/SimpleFail2a.stderr | 2 +- .../tests/indexed-types/should_fail/T14045a.stderr | 2 +- testsuite/tests/polykinds/T13985.hs | 1 + testsuite/tests/polykinds/T13985.stderr | 10 +- 10 files changed, 338 insertions(+), 314 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 e49adfb7cfb2737c422af7b4ce76ab10eb4be0a1 From git at git.haskell.org Mon Nov 26 17:49:44 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Nov 2018 17:49:44 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Nearly there... (df8140d) Message-ID: <20181126174944.C3D5E3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/df8140dff1cbcb9826e42495479ad1817dff3525/ghc >--------------------------------------------------------------- commit df8140dff1cbcb9826e42495479ad1817dff3525 Author: Simon Peyton Jones Date: Thu Nov 15 17:43:18 2018 +0000 Nearly there... >--------------------------------------------------------------- df8140dff1cbcb9826e42495479ad1817dff3525 compiler/typecheck/TcGenDeriv.hs | 8 +- compiler/typecheck/TcHsType.hs | 2 - compiler/typecheck/TcInstDcls.hs | 12 +- compiler/typecheck/TcTyClsDecls.hs | 101 ++-------------- compiler/typecheck/TcValidity.hs | 132 +++++++++++++++++---- testsuite/tests/ghci/scripts/T6018ghcifail.stderr | 2 +- .../should_fail/ExplicitForAllFams4a.stderr | 10 +- .../should_fail/ExplicitForAllFams4b.stderr | 20 ++-- .../indexed-types/should_fail/SimpleFail13.stderr | 2 +- .../indexed-types/should_fail/SimpleFail2a.hs | 12 +- .../indexed-types/should_fail/SimpleFail9.stderr | 4 +- .../tests/indexed-types/should_fail/T7536.stderr | 5 +- testsuite/tests/polykinds/T13985.stderr | 10 +- .../tests/th/TH_reifyExplicitForAllFams.stderr | 6 +- .../tests/typecheck/should_fail/T6018fail.stderr | 4 +- 15 files changed, 168 insertions(+), 162 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 df8140dff1cbcb9826e42495479ad1817dff3525 From git at git.haskell.org Mon Nov 26 17:49:47 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Nov 2018 17:49:47 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Simplify typing of associated family instances (82dfe01) Message-ID: <20181126174947.C6CF53A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/82dfe01ad39800dc2426d7ba6b5942a9ed9b348b/ghc >--------------------------------------------------------------- commit 82dfe01ad39800dc2426d7ba6b5942a9ed9b348b Author: Simon Peyton Jones Date: Mon Nov 19 08:19:14 2018 +0000 Simplify typing of associated family instances This experimental patch simplifies the treatment of assocaited family instances, by - Treating them entirely independently from their enclosing class-instance declaration - Making a separate check (checkConsistentFamInst) that the instance(s) match the class-instance decl This makes two or three testsuite cases fail -- but I think that's a feature not bug! This is on my wip/T15809 branch >--------------------------------------------------------------- 82dfe01ad39800dc2426d7ba6b5942a9ed9b348b compiler/typecheck/TcTyClsDecls.hs | 136 +++++++++++++++++-------------------- 1 file changed, 64 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 82dfe01ad39800dc2426d7ba6b5942a9ed9b348b From git at git.haskell.org Mon Nov 26 17:49:50 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Nov 2018 17:49:50 +0000 (UTC) Subject: [commit: ghc] wip/T15809: More wibbles (7b20763) Message-ID: <20181126174950.BFA8A3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/7b2076396138b7db289d8887ac5e526f3c55c03c/ghc >--------------------------------------------------------------- commit 7b2076396138b7db289d8887ac5e526f3c55c03c Author: Simon Peyton Jones Date: Mon Nov 19 20:45:09 2018 +0000 More wibbles >--------------------------------------------------------------- 7b2076396138b7db289d8887ac5e526f3c55c03c compiler/typecheck/TcTyClsDecls.hs | 62 +++++++++++++++----------------------- 1 file changed, 24 insertions(+), 38 deletions(-) diff --git a/compiler/typecheck/TcTyClsDecls.hs b/compiler/typecheck/TcTyClsDecls.hs index d74ecb5..8c6133e 100644 --- a/compiler/typecheck/TcTyClsDecls.hs +++ b/compiler/typecheck/TcTyClsDecls.hs @@ -68,7 +68,6 @@ import SrcLoc import ListSetOps import DynFlags import Unique -import UniqFM( nonDetEltsUFM ) import ConLike( ConLike(..) ) import BasicTypes import qualified GHC.LanguageExtensions as LangExt @@ -3240,8 +3239,7 @@ checkConsistentFamInst :: Maybe ClsInstInfo checkConsistentFamInst Nothing _ _ = return () checkConsistentFamInst (Just (clas, inst_tvs, mini_env)) fam_tc at_arg_tys = do { traceTc "checkConsistentFamInst" (vcat [ ppr inst_tvs - , ppr kind_prs - , ppr type_prs + , ppr arg_triples , ppr mini_env ]) -- Check that the associated type indeed comes from this class -- See [Mismatched class methods and associated type families] @@ -3249,28 +3247,16 @@ checkConsistentFamInst (Just (clas, inst_tvs, mini_env)) fam_tc at_arg_tys ; checkTc (Just (classTyCon clas) == tyConAssoc_maybe fam_tc) (badATErr (className clas) (tyConName fam_tc)) - -- Check kind args first, suggesting -fprint-explicit-kiinds - -- if there is a mis-match here. - ; checkTc (isJust mb_kinds_match) (pp_wrong_at_arg $$ ppSuggestExplicitKinds) - - -- Then type args. If we do these first, then we'll fail to - -- suggest -fprint-explicit-kinds for (T @k vs T @Type) - ; checkTc (isJust mb_types_match) pp_wrong_at_arg + ; check_match arg_triples } where - kind_prs, type_prs :: [(Type,Type)] - (kind_prs, type_prs) = partitionInvisibles $ - [ ((cls_arg_ty, at_arg_ty), vis) - | (fam_tc_tv, vis, at_arg_ty) - <- zip3 (tyConTyVars fam_tc) - (tyConArgFlags fam_tc at_arg_tys) - at_arg_tys - , Just cls_arg_ty <- [lookupVarEnv mini_env fam_tc_tv] ] - - - mb_types_match = alphaMatchTysX emptyTCvSubst type_prs - Just subst1 = mb_types_match - mb_kinds_match = alphaMatchTysX subst1 kind_prs + arg_triples :: [(Type,Type, ArgFlag)] + arg_triples = [ (cls_arg_ty, at_arg_ty, vis) + | (fam_tc_tv, vis, at_arg_ty) + <- zip3 (tyConTyVars fam_tc) + (tyConArgFlags fam_tc at_arg_tys) + at_arg_tys + , Just cls_arg_ty <- [lookupVarEnv mini_env fam_tc_tv] ] pp_wrong_at_arg = vcat [ text "Type indexes must match class instance head" , text "Expected:" <+> ppr (mkTyConApp fam_tc expected_args) @@ -3281,22 +3267,22 @@ checkConsistentFamInst (Just (clas, inst_tvs, mini_env)) fam_tc at_arg_tys underscore at_tv = mkTyVarTy (mkTyVar tv_name (tyVarKind at_tv)) tv_name = mkInternalName (mkAlphaTyVarUnique 1) (mkTyVarOcc "_") noSrcSpan -alphaMatchTysX :: TCvSubst -> [(Type,Type)] -> Maybe TCvSubst -alphaMatchTysX subst pairs - | null pairs = Just subst - | otherwise = go subst pairs - where - go :: TCvSubst -> [(Type,Type)] -> Maybe TCvSubst - go subst [] - | allDistinctTyVars emptyVarSet $ - nonDetEltsUFM (getTvSubstEnv subst) - = Just subst + check_match :: [(Type,Type, ArgFlag)] -> TcM () + check_match triples = go emptyTCvSubst emptyTCvSubst triples + + go _ _ [] = return () + go lr_subst rl_subst ((ty1,ty2,vis):triples) + | Just lr_subst1 <- tcMatchTyX lr_subst ty1 ty2 + , Just rl_subst1 <- tcMatchTyX rl_subst ty2 ty1 + = go lr_subst1 rl_subst1 triples | otherwise - = Nothing - go subst ((ty1,ty2):prs) - = case tcMatchTyX subst ty1 ty2 of - Just subst' -> go subst' prs - Nothing -> Nothing + = addErrTc (pp_wrong_at_arg $$ + ppWhen (isInvisibleArgFlag vis) ppSuggestExplicitKinds) + -- NB: checks left-to-right, kinds first. + -- If we types first, we'll fail to + -- suggest -fprint-explicit-kinds for a mis-match with + -- T @k vs T @Type + -- somewhere deep inside the type badATErr :: Name -> Name -> SDoc badATErr clas op From git at git.haskell.org Mon Nov 26 17:49:53 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Nov 2018 17:49:53 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Wibbles (a2b8905) Message-ID: <20181126174953.C05EC3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/a2b8905015519e83eddc7e3637d30ada5f63d7c9/ghc >--------------------------------------------------------------- commit a2b8905015519e83eddc7e3637d30ada5f63d7c9 Author: Simon Peyton Jones Date: Mon Nov 19 11:32:56 2018 +0000 Wibbles >--------------------------------------------------------------- a2b8905015519e83eddc7e3637d30ada5f63d7c9 compiler/typecheck/TcTyClsDecls.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/compiler/typecheck/TcTyClsDecls.hs b/compiler/typecheck/TcTyClsDecls.hs index 07a6320..d74ecb5 100644 --- a/compiler/typecheck/TcTyClsDecls.hs +++ b/compiler/typecheck/TcTyClsDecls.hs @@ -1897,7 +1897,7 @@ tcFamTyPatsAndGen fam_tc mb_clsinfo imp_vars exp_bndrs hs_pats thing_inside tcFamTyPats :: TyCon -> Maybe ClsInstInfo -> HsTyPats GhcRn -- Patterns -> TcM ([TcType], TcKind) -- (pats, rhs_kind) -tcFamTyPats fam_tc mb_clsinfo hs_pats +tcFamTyPats fam_tc _mb_clsinfo hs_pats = do { traceTc "tcFamTyPats {" $ vcat [ ppr fam_tc <+> dcolon <+> ppr fun_kind , text "arity:" <+> ppr fam_arity @@ -1929,7 +1929,7 @@ tcFamTyPats fam_tc mb_clsinfo hs_pats fun_kind = tyConKind fam_tc lhs_fun = noLoc (HsTyVar noExt NotPromoted (noLoc fam_name)) (invis_bndrs, body_kind) = splitPiTysInvisibleN fam_arity fun_kind - mb_kind_env = thdOf3 <$> mb_clsinfo +-- mb_kind_env = thdOf3 <$> mb_clsinfo bad_lhs fam_app = hang (text "Ill-typed LHS of family instance") From git at git.haskell.org Mon Nov 26 17:49:56 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Nov 2018 17:49:56 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Finally, validate-clean (dc1457c) Message-ID: <20181126174956.CC2BE3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/dc1457c42cad4e19bb0ce0eb85f68f1c02cf27a7/ghc >--------------------------------------------------------------- commit dc1457c42cad4e19bb0ce0eb85f68f1c02cf27a7 Author: Simon Peyton Jones Date: Fri Nov 16 12:03:59 2018 +0000 Finally, validate-clean Except for polykinds/T14846, where there is an extra error message. I actually tnink it's correct, but have not checked yet. >--------------------------------------------------------------- dc1457c42cad4e19bb0ce0eb85f68f1c02cf27a7 compiler/typecheck/TcBinds.hs | 24 ---- compiler/typecheck/TcClassDcl.hs | 3 - compiler/typecheck/TcDeriv.hs | 3 - compiler/typecheck/TcEnv.hs | 8 -- compiler/typecheck/TcHsType.hs | 87 +++++++++----- compiler/typecheck/TcInstDcls.hs | 81 ++++++------- compiler/typecheck/TcPat.hs | 2 +- compiler/typecheck/TcTyClsDecls.hs | 133 +++++++++++++-------- compiler/types/TyCoRep.hs | 7 +- .../indexed-types/should_fail/SimpleFail9.stderr | 2 +- .../tests/indexed-types/should_fail/T10817.stderr | 9 +- .../tests/indexed-types/should_fail/T10899.stderr | 3 +- testsuite/tests/polykinds/T8616.stderr | 9 ++ testsuite/tests/printer/Ppr040.hs | 10 +- 14 files changed, 203 insertions(+), 178 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 dc1457c42cad4e19bb0ce0eb85f68f1c02cf27a7 From git at git.haskell.org Mon Nov 26 17:49:59 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Nov 2018 17:49:59 +0000 (UTC) Subject: [commit: ghc] wip/T15809: More progress in tcFamTyPats (3baf793) Message-ID: <20181126174959.DA1FA3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/3baf7933cef5bdc7be5e996f37938b7e54e01c7b/ghc >--------------------------------------------------------------- commit 3baf7933cef5bdc7be5e996f37938b7e54e01c7b Author: Simon Peyton Jones Date: Tue Nov 20 16:36:06 2018 +0000 More progress in tcFamTyPats In particular, revert to taking account of the class instance types in tcFamTyPats, but by unification rather than by messing with tcInferApps >--------------------------------------------------------------- 3baf7933cef5bdc7be5e996f37938b7e54e01c7b compiler/typecheck/Inst.hs | 31 ++++++++++++------ compiler/typecheck/TcHsType.hs | 54 +++++++------------------------ compiler/typecheck/TcTyClsDecls.hs | 65 +++++++++++++++++++++++++++----------- compiler/types/Type.hs | 15 ++++++++- 4 files changed, 93 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 3baf7933cef5bdc7be5e996f37938b7e54e01c7b From git at git.haskell.org Mon Nov 26 17:50:02 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Nov 2018 17:50:02 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Wibble, to fix build (b728b32) Message-ID: <20181126175002.D04EE3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/b728b32059be8600b198337198eddae11208f459/ghc >--------------------------------------------------------------- commit b728b32059be8600b198337198eddae11208f459 Author: Simon Peyton Jones Date: Wed Nov 21 13:55:54 2018 +0000 Wibble, to fix build >--------------------------------------------------------------- b728b32059be8600b198337198eddae11208f459 compiler/typecheck/TcTyClsDecls.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/compiler/typecheck/TcTyClsDecls.hs b/compiler/typecheck/TcTyClsDecls.hs index fa22b33..2bce354 100644 --- a/compiler/typecheck/TcTyClsDecls.hs +++ b/compiler/typecheck/TcTyClsDecls.hs @@ -1787,7 +1787,7 @@ tcTyFamInstEqn fam_tc mb_clsinfo ; (qtvs, pats, rhs_ty) <- tcFamTyPatsAndGen fam_tc mb_clsinfo imp_vars (mb_expl_bndrs `orElse` []) hs_pats - (tcCheckLHsType rhs_hs_ty res_kind) + (tcCheckLHsType rhs_hs_ty) ; (ze, qtvs') <- zonkTyBndrs qtvs ; pats' <- zonkTcTypesToTypesX ze pats From git at git.haskell.org Mon Nov 26 17:50:05 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Nov 2018 17:50:05 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Wibbles (517805d) Message-ID: <20181126175005.CDD703A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/517805dda1377f7a42768e9770fa2c53412d21a5/ghc >--------------------------------------------------------------- commit 517805dda1377f7a42768e9770fa2c53412d21a5 Author: Simon Peyton Jones Date: Wed Nov 21 00:00:53 2018 +0000 Wibbles >--------------------------------------------------------------- 517805dda1377f7a42768e9770fa2c53412d21a5 compiler/typecheck/TcMType.hs | 15 +++++++++++++ compiler/typecheck/TcRnTypes.hs | 8 ++++++- compiler/typecheck/TcTyClsDecls.hs | 25 +++++++++++----------- .../tests/indexed-types/should_fail/SimpleFail9.hs | 4 +++- 4 files changed, 37 insertions(+), 15 deletions(-) diff --git a/compiler/typecheck/TcMType.hs b/compiler/typecheck/TcMType.hs index 886a894..769a312 100644 --- a/compiler/typecheck/TcMType.hs +++ b/compiler/typecheck/TcMType.hs @@ -41,6 +41,7 @@ module TcMType ( newEvVar, newEvVars, newDict, newWanted, newWanteds, newHoleCt, cloneWanted, cloneWC, emitWanted, emitWantedEq, emitWantedEvVar, emitWantedEvVars, + emitDerivedEqs, newTcEvBinds, newNoTcEvBinds, addTcEvBind, newCoercionHole, fillCoercionHole, isFilledCoercionHole, @@ -232,6 +233,20 @@ emitWanted origin pty ; emitSimple $ mkNonCanonical ev ; return $ ctEvTerm ev } +emitDerivedEqs :: CtOrigin -> [(TcType,TcType)] -> TcM () +-- Emit some new derived nominal equalities +emitDerivedEqs origin pairs + | null pairs + = return () + | otherwise + = do { loc <- getCtLocM origin Nothing + ; emitSimples (listToBag (map (mk_one loc) pairs)) } + where + mk_one loc (ty1, ty2) + = mkNonCanonical $ + CtDerived { ctev_pred = mkPrimEqPred ty1 ty2 + , ctev_loc = loc } + -- | Emits a new equality constraint emitWantedEq :: CtOrigin -> TypeOrKind -> Role -> TcType -> TcType -> TcM Coercion emitWantedEq origin t_or_k role ty1 ty2 diff --git a/compiler/typecheck/TcRnTypes.hs b/compiler/typecheck/TcRnTypes.hs index f7caacd..ad3122b 100644 --- a/compiler/typecheck/TcRnTypes.hs +++ b/compiler/typecheck/TcRnTypes.hs @@ -3511,8 +3511,10 @@ data CtOrigin | NegateOrigin -- Occurrence of syntactic negation | ArithSeqOrigin (ArithSeqInfo GhcRn) -- [x..], [x..y] etc + | AssocFamPatOrigin -- When matching the patterns of an associated + -- family instance with that of its parent class | SectionOrigin - | TupleOrigin -- (..,..) + | TupleOrigin -- (..,..) | ExprSigOrigin -- e :: ty | PatSigOrigin -- p :: ty | PatOrigin -- Instantiating a polytyped pattern at a constructor @@ -3730,6 +3732,9 @@ pprCtOrigin (KindEqOrigin t1 (Just t2) _ _) = hang (ctoHerald <+> text "a kind equality arising from") 2 (sep [ppr t1, char '~', ppr t2]) +pprCtOrigin AssocFamPatOrigin + = text "when matching a family LHS with its class instance head" + pprCtOrigin (KindEqOrigin t1 Nothing _ _) = hang (ctoHerald <+> text "a kind equality when matching") 2 (ppr t1) @@ -3801,6 +3806,7 @@ pprCtO IfOrigin = text "an if expression" pprCtO (LiteralOrigin lit) = hsep [text "the literal", quotes (ppr lit)] pprCtO (ArithSeqOrigin seq) = hsep [text "the arithmetic sequence", quotes (ppr seq)] pprCtO SectionOrigin = text "an operator section" +pprCtO AssocFamPatOrigin = text "the LHS of a famly instance" pprCtO TupleOrigin = text "a tuple" pprCtO NegateOrigin = text "a use of syntactic negation" pprCtO (ScOrigin n) = text "the superclasses of an instance declaration" diff --git a/compiler/typecheck/TcTyClsDecls.hs b/compiler/typecheck/TcTyClsDecls.hs index a5f3295..fa22b33 100644 --- a/compiler/typecheck/TcTyClsDecls.hs +++ b/compiler/typecheck/TcTyClsDecls.hs @@ -40,7 +40,6 @@ import TcDeriv (DerivInfo) import TcHsType import Inst( tcInstTyBinders ) import TcMType -import TcUnify( unifyType ) import TysWiredIn ( unitTy ) import TcType import RnEnv( lookupConstructorFields ) @@ -1788,9 +1787,7 @@ tcTyFamInstEqn fam_tc mb_clsinfo ; (qtvs, pats, rhs_ty) <- tcFamTyPatsAndGen fam_tc mb_clsinfo imp_vars (mb_expl_bndrs `orElse` []) hs_pats - (\ res_kind -> - do { traceTc "tcTyFasmInstEqn" (ppr fam_tc $$ ppr hs_pats $$ ppr res_kind) - ; tcCheckLHsType rhs_hs_ty res_kind }) + (tcCheckLHsType rhs_hs_ty res_kind) ; (ze, qtvs') <- zonkTyBndrs qtvs ; pats' <- zonkTcTypesToTypesX ze pats @@ -1950,16 +1947,19 @@ addConsistencyConstraints :: Maybe ClsInstInfo -> TyCon -> [Type] -> TcM () -- F c x y a :: Type -- Here the first arg of F should be the same as the third of C -- and the fourth arg of F should be the same as the first of C - +-- +-- We emit /Derived/ constraints (a bit like fundeps) to encourage +-- unification to happen, but without actually reporting errors. +-- If, despite the efforts, corresponding positions do not match, +-- checkConsistentFamInst will complain addConsistencyConstraints Nothing _ _ = return () addConsistencyConstraints (Just (_, _, inst_ty_env)) fam_tc pats - = mapM_ do_one (tyConTyVars fam_tc `zip` pats) - where - do_one (fam_tc_tv, pat) - | Just cls_arg_ty <- lookupVarEnv inst_ty_env fam_tc_tv - = discardResult (unifyType Nothing cls_arg_ty pat) - | otherwise - = return () + = emitDerivedEqs AssocFamPatOrigin + [ (cls_ty, pat) + | (fam_tc_tv, pat) <- tyConTyVars fam_tc `zip` pats + , Just cls_ty <- [lookupVarEnv inst_ty_env fam_tc_tv] ] + -- Improve inference + -- Any mis-match is reports by checkConsistentFamInst {- Note [Constraints in patterns] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -3256,7 +3256,6 @@ checkFamFlag tc_name -- types. type ClsInstInfo = (Class, [TyVar], VarEnv Type) - checkConsistentFamInst :: Maybe ClsInstInfo -> TyCon -- ^ Family tycon -> [Type] -- ^ Type patterns from instance diff --git a/testsuite/tests/indexed-types/should_fail/SimpleFail9.hs b/testsuite/tests/indexed-types/should_fail/SimpleFail9.hs index 9c1c4a8..0f20f78 100644 --- a/testsuite/tests/indexed-types/should_fail/SimpleFail9.hs +++ b/testsuite/tests/indexed-types/should_fail/SimpleFail9.hs @@ -2,8 +2,10 @@ module ShouldFail where +import Data.Kind + class C7 a b where - data S7 b :: * + data S7 b :: Type instance C7 Char (a, Bool) where data S7 (a, Bool) = S7_1 From git at git.haskell.org Mon Nov 26 17:50:08 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Nov 2018 17:50:08 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Wibbles to checkConsistentFamInst (df516f2) Message-ID: <20181126175008.D4F843A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/df516f20ee8ef1effb2f83aa3b6f7472486f6802/ghc >--------------------------------------------------------------- commit df516f20ee8ef1effb2f83aa3b6f7472486f6802 Author: Simon Peyton Jones Date: Fri Nov 23 08:31:22 2018 +0000 Wibbles to checkConsistentFamInst >--------------------------------------------------------------- df516f20ee8ef1effb2f83aa3b6f7472486f6802 compiler/typecheck/TcInstDcls.hs | 27 +++++++++-------- compiler/typecheck/TcTyClsDecls.hs | 62 +++++++++++++++++++++++++------------- 2 files changed, 55 insertions(+), 34 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc df516f20ee8ef1effb2f83aa3b6f7472486f6802 From git at git.haskell.org Mon Nov 26 17:50:11 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Nov 2018 17:50:11 +0000 (UTC) Subject: [commit: ghc] wip/T15809: More wibbles on checkConsistentFamInst (1c686e6) Message-ID: <20181126175011.DE6AD3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/1c686e6ca79b9ac2f1ba19d1abc215937fb562fc/ghc >--------------------------------------------------------------- commit 1c686e6ca79b9ac2f1ba19d1abc215937fb562fc Author: Simon Peyton Jones Date: Fri Nov 23 11:55:48 2018 +0000 More wibbles on checkConsistentFamInst >--------------------------------------------------------------- 1c686e6ca79b9ac2f1ba19d1abc215937fb562fc compiler/typecheck/TcDeriv.hs | 28 ++++++------- compiler/typecheck/TcHsType.hs | 80 ++++++++++++++++++++++++-------------- compiler/typecheck/TcInstDcls.hs | 18 +++++---- compiler/typecheck/TcTyClsDecls.hs | 9 ++--- compiler/typecheck/TcValidity.hs | 7 ++-- compiler/types/TyCoRep.hs | 2 +- compiler/types/Type.hs | 15 ++----- compiler/utils/Util.hs | 8 +++- 8 files changed, 94 insertions(+), 73 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc 1c686e6ca79b9ac2f1ba19d1abc215937fb562fc From git at git.haskell.org Mon Nov 26 17:50:14 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Nov 2018 17:50:14 +0000 (UTC) Subject: [commit: ghc] wip/T15809: More wibbles (7f9e428) Message-ID: <20181126175014.E944C3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/7f9e4281c86f2e69d0f85c67e4b268bc4851f3a9/ghc >--------------------------------------------------------------- commit 7f9e4281c86f2e69d0f85c67e4b268bc4851f3a9 Author: Simon Peyton Jones Date: Fri Nov 23 17:33:19 2018 +0000 More wibbles Plus rebased onto master >--------------------------------------------------------------- 7f9e4281c86f2e69d0f85c67e4b268bc4851f3a9 compiler/hsSyn/HsTypes.hs | 1 - compiler/typecheck/TcDeriv.hs | 23 ++++++++++++++-- compiler/typecheck/TcHsType.hs | 6 ++--- compiler/typecheck/TcInstDcls.hs | 40 ++++++++++++++++++++------- compiler/typecheck/TcTyClsDecls.hs | 55 ++++++++++++++++++++------------------ compiler/types/TyCoRep.hs | 6 ++++- compiler/types/Type.hs | 3 ++- 7 files changed, 90 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 7f9e4281c86f2e69d0f85c67e4b268bc4851f3a9 From git at git.haskell.org Mon Nov 26 17:50:17 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Nov 2018 17:50:17 +0000 (UTC) Subject: [commit: ghc] wip/T15809: Yet more on family-instance checking (832f058) Message-ID: <20181126175017.F2F0F3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/832f0589b1192ad0344a173dea4cdb91ccb0bffe/ghc >--------------------------------------------------------------- commit 832f0589b1192ad0344a173dea4cdb91ccb0bffe Author: Simon Peyton Jones Date: Thu Nov 22 14:24:28 2018 +0000 Yet more on family-instance checking Following conversation with Richard yesterday. Very close now. Comments to be written. >--------------------------------------------------------------- 832f0589b1192ad0344a173dea4cdb91ccb0bffe compiler/hsSyn/HsDecls.hs | 57 +++---- compiler/hsSyn/HsTypes.hs | 69 ++++---- compiler/nativeGen/CFG.hs | 1 - compiler/parser/RdrHsSyn.hs | 8 +- compiler/typecheck/Inst.hs | 2 +- compiler/typecheck/TcHsType.hs | 5 +- compiler/typecheck/TcInstDcls.hs | 125 ++++++++------- compiler/typecheck/TcMType.hs | 155 +++++++++--------- compiler/typecheck/TcSigs.hs | 21 +-- compiler/typecheck/TcTyClsDecls.hs | 173 +++++++++++++-------- compiler/types/Unify.hs | 43 +++-- .../should_fail/ExplicitForAllFams4b.hs | 1 + .../should_fail/ExplicitForAllFams4b.stderr | 54 +++++-- .../indexed-types/should_fail/SimpleFail9.stderr | 2 +- .../tests/indexed-types/should_fail/T12041.stderr | 11 +- .../tests/indexed-types/should_fail/T13972.hs | 6 + .../tests/indexed-types/should_fail/T13972.stderr | 7 - .../tests/indexed-types/should_fail/T14045a.hs | 5 + .../tests/indexed-types/should_fail/T14045a.stderr | 7 - testsuite/tests/indexed-types/should_fail/T9160.hs | 1 + .../tests/indexed-types/should_fail/T9160.stderr | 13 +- testsuite/tests/indexed-types/should_fail/all.T | 4 +- .../tests/partial-sigs/should_fail/T14040a.stderr | 8 +- testsuite/tests/polykinds/T14450.stderr | 12 +- testsuite/tests/polykinds/T14846.stderr | 36 +++-- 25 files changed, 446 insertions(+), 380 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 832f0589b1192ad0344a173dea4cdb91ccb0bffe From git at git.haskell.org Mon Nov 26 17:50:21 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Nov 2018 17:50:21 +0000 (UTC) Subject: [commit: ghc] wip/T15809: More wibbles to data families (129bf71) Message-ID: <20181126175021.12CE93A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/129bf71b1cc85965a449260ca1dc13e2951eaded/ghc >--------------------------------------------------------------- commit 129bf71b1cc85965a449260ca1dc13e2951eaded Author: Simon Peyton Jones Date: Mon Nov 26 09:39:31 2018 +0000 More wibbles to data families Including fixing Trac #15817 >--------------------------------------------------------------- 129bf71b1cc85965a449260ca1dc13e2951eaded compiler/basicTypes/DataCon.hs | 3 +- compiler/typecheck/TcHsType.hs | 119 +++++++++--------- compiler/typecheck/TcInstDcls.hs | 247 ++++++++++++++++++++++++++----------- compiler/typecheck/TcMType.hs | 4 +- compiler/typecheck/TcTyClsDecls.hs | 66 ++++++---- compiler/types/TyCon.hs | 15 ++- compiler/types/Type.hs | 8 +- 7 files changed, 298 insertions(+), 164 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 129bf71b1cc85965a449260ca1dc13e2951eaded From git at git.haskell.org Mon Nov 26 17:50:24 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Nov 2018 17:50:24 +0000 (UTC) Subject: [commit: ghc] wip/T15809: More wibbles (a58cbf1) Message-ID: <20181126175024.1E58C3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/T15809 Link : http://ghc.haskell.org/trac/ghc/changeset/a58cbf13979d9cd204f4b4b7c343b77fe838a90a/ghc >--------------------------------------------------------------- commit a58cbf13979d9cd204f4b4b7c343b77fe838a90a Author: Simon Peyton Jones Date: Mon Nov 26 17:47:02 2018 +0000 More wibbles and rebase on today's master >--------------------------------------------------------------- a58cbf13979d9cd204f4b4b7c343b77fe838a90a compiler/basicTypes/OccName.hs | 5 +++ compiler/typecheck/TcInstDcls.hs | 2 +- compiler/typecheck/TcSigs.hs | 4 +-- compiler/typecheck/TcSplice.hs | 3 +- compiler/typecheck/TcTyClsDecls.hs | 40 ++++++++++++---------- compiler/typecheck/TcValidity.hs | 3 +- compiler/types/Coercion.hs | 4 +-- compiler/types/FamInstEnv.hs | 21 ++++++++++-- compiler/types/Type.hs | 39 +++++++++++---------- compiler/utils/FastString.hs | 4 +++ testsuite/tests/dependent/should_compile/T13910.hs | 10 +----- testsuite/tests/dependent/should_compile/T15725.hs | 6 ++-- testsuite/tests/ghci/scripts/T6018ghcifail.stderr | 2 +- .../indexed-types/should_compile/T15852.stderr | 8 ++--- .../should_fail/ExplicitForAllFams4b.hs | 6 ++-- .../tests/indexed-types/should_fail/T12041.stderr | 5 ++- .../tests/indexed-types/should_fail/T9160.stderr | 5 ++- testsuite/tests/polykinds/T14450.stderr | 5 ++- .../tests/typecheck/should_fail/T6018fail.stderr | 2 +- 19 files changed, 98 insertions(+), 76 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc a58cbf13979d9cd204f4b4b7c343b77fe838a90a From git at git.haskell.org Mon Nov 26 17:50:26 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Nov 2018 17:50:26 +0000 (UTC) Subject: [commit: ghc] wip/T15809's head updated: More wibbles (a58cbf1) Message-ID: <20181126175026.846683A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc Branch 'wip/T15809' now includes: b2950e0 Implement late lambda lift 929363b configure: Use LLVM 7.0 0a126a3 distrib/configure: Set RanlibCmd 937d484 users guide: Clarify meanings of -g flags ee03ac4 Bump containers submodule c2be6d5 Bump text submodule f61f71c Revert "Simplify 'ExtBits' in the lexer" 7e7e846 Revert "'DynFlag'-free version of 'mkParserFlags'" ad2d761 Fix unused import warning 509d5be [TTG: Handling Source Locations] Foundation and Pat 6a70acf CircleCI: Clean up docker image bba2b9b Revert "Fix uninformative hp2ps error when the cmdline contains double quotes" 4ac7a94 CircleCI: More cleanup 9e47dd3 Remove unused declarations in MarkWeak.h 8a6aa87 Revert "Remove redundant check in cgCase" df570d9 Fix build on darwin c216a13 Tc-tracing, and order of arguments only ec716ec WIP on using level numbers for generalisation 7cc4706 More progress on using level numbers for gen 1394ef8 Further work on TyCon generalisation ccdcb58 Further progress ea20832 More progress fbb64e4 More progress 069307d More progress e5492e6 Comemnts only 2f02df6 Finally done 5104ded Comments and alpha-renaming 9980257 Comments only 326f87a Progress 7c61052 Combine kcImplicitTKBndrs and tcImplicitTKBndrs 0ba23e8 Get rid of kcLHsQTyVarBndrs a787fbb Start to eliminate tcFamTyPats 74f5b0e More progress on tcFamTyPats 1651c0a Wibbles f147f82 Much more progress on tcFamTyPats 98331d5 Data family instances working, I think 1288a96 Print tycon arity in -ddump-types 412a735 More progress with data instances 95544de Wibbles 3ff0120 More progress on reporting unbound variables df8140d Nearly there... e49adfb Better validity checks, simplification dc1457c Finally, validate-clean 82dfe01 Simplify typing of associated family instances a2b8905 Wibbles 7b20763 More wibbles 3baf793 More progress in tcFamTyPats 517805d Wibbles b728b32 Wibble, to fix build 832f058 Yet more on family-instance checking df516f2 Wibbles to checkConsistentFamInst 1c686e6 More wibbles on checkConsistentFamInst 7f9e428 More wibbles 129bf71 More wibbles to data families a58cbf1 More wibbles From git at git.haskell.org Mon Nov 26 18:57:30 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Nov 2018 18:57:30 +0000 (UTC) Subject: [commit: ghc] master: Print explicit foralls in type family eqns when appropriate (f932b1a) Message-ID: <20181126185730.B6D943A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f932b1aa42f45625658c8abaf862cc570507c5ca/ghc >--------------------------------------------------------------- commit f932b1aa42f45625658c8abaf862cc570507c5ca Author: Ryan Scott Date: Mon Nov 26 12:59:09 2018 -0500 Print explicit foralls in type family eqns when appropriate Summary: When `-fprint-explicit-foralls` is enabled, type family equations are either printed without an explict `forall` entirely, or with a bizarre square bracket syntax (in the case of closed type families). I find neither satisfying, so in this patch, I introduce support for printing explicit `forall`s in open type-family, closed type-family, and data-family equations when appropriate. (By "when appropriate", I refer to the conditions laid out in `Note [When to print foralls]` in `IfaceType`.) One tricky point in the implementation is that I had to pick a visibility for each type variable in a `CoAxiom`/`FamInst` in order to be able to pass it to `pprUserIfaceForAll` //et al.// Because the type variables in a type family instance equation can't be instantiated by the programmer anyway, the choice only really matters for pretty-printing purposes, so I simply went with good ol' trustworthy `Specified`. (This design choice is documented in `Note [Printing foralls in type family instances]` in `IfaceType`.) Test Plan: make test TEST=T15827 Reviewers: goldfire, bgamari, simonpj Reviewed By: simonpj Subscribers: simonpj, rwbarton, carter GHC Trac Issues: #15827 Differential Revision: https://phabricator.haskell.org/D5282 >--------------------------------------------------------------- f932b1aa42f45625658c8abaf862cc570507c5ca compiler/iface/IfaceSyn.hs | 46 +++++++++++++------------- compiler/iface/IfaceType.hs | 53 ++++++++++++++++++++++++++++++ compiler/main/PprTyThing.hs | 10 ++++-- testsuite/tests/ghci/scripts/T13420.stdout | 9 +++-- testsuite/tests/ghci/scripts/T15341.stdout | 8 ++--- testsuite/tests/ghci/scripts/T15827.hs | 16 +++++++++ testsuite/tests/ghci/scripts/T15827.script | 4 +++ testsuite/tests/ghci/scripts/T15827.stdout | 9 +++++ testsuite/tests/ghci/scripts/T4175.stdout | 7 ++-- testsuite/tests/ghci/scripts/T7939.stdout | 22 ++++++------- testsuite/tests/ghci/scripts/T8674.stdout | 3 +- testsuite/tests/ghci/scripts/T9181.stdout | 2 +- testsuite/tests/ghci/scripts/all.T | 1 + 13 files changed, 138 insertions(+), 52 deletions(-) Diff suppressed because of size. To see it, use: git diff-tree --root --patch-with-stat --no-color --find-copies-harder --ignore-space-at-eol --cc f932b1aa42f45625658c8abaf862cc570507c5ca From git at git.haskell.org Mon Nov 26 18:57:34 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Nov 2018 18:57:34 +0000 (UTC) Subject: [commit: ghc] master: Use autoconf to generate version numbers for libiserv and friends (8f9f52d) Message-ID: <20181126185734.3E9C43A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8f9f52d8e421ce544d5437a93117545d52d0eabd/ghc >--------------------------------------------------------------- commit 8f9f52d8e421ce544d5437a93117545d52d0eabd Author: Ryan Scott Date: Mon Nov 26 12:59:30 2018 -0500 Use autoconf to generate version numbers for libiserv and friends Summary: Currently, the version numbers for `libiserv`, `iserv`, and `iserv-proxy` are hard-coded directly into their `.cabal` files. These are easy to forget to update, and in fact, this has already happened once (see #15866). Let's use `autoconf` to do this for us so that it is not forgotten in the future. Test Plan: ./validate Reviewers: bgamari Reviewed By: bgamari Subscribers: rwbarton, erikd, carter GHC Trac Issues: #15866 Differential Revision: https://phabricator.haskell.org/D5302 >--------------------------------------------------------------- 8f9f52d8e421ce544d5437a93117545d52d0eabd .gitignore | 3 +++ configure.ac | 2 +- docs/users_guide/8.8.1-notes.rst | 1 + libraries/libiserv/{libiserv.cabal => libiserv.cabal.in} | 8 ++++++-- utils/iserv-proxy/{iserv-proxy.cabal => iserv-proxy.cabal.in} | 10 +++++++--- utils/iserv/{iserv.cabal => iserv.cabal.in} | 10 +++++++--- 6 files changed, 25 insertions(+), 9 deletions(-) diff --git a/.gitignore b/.gitignore index 59ca1cc..b205b24 100644 --- a/.gitignore +++ b/.gitignore @@ -153,6 +153,7 @@ _darcs/ /libraries/hslogo-16.png /libraries/index-frames.html /libraries/index.html +/libraries/libiserv/libiserv.cabal /libraries/minus.gif /libraries/ocean.css /libraries/plus.gif @@ -178,6 +179,8 @@ _darcs/ /testsuite_summary*.txt /testsuite*.xml /testlog* +/utils/iserv/iserv.cabal +/utils/iserv-proxy/iserv-proxy.cabal /utils/mkUserGuidePart/mkUserGuidePart.cabal /utils/runghc/runghc.cabal /utils/gen-dll/gen-dll.cabal diff --git a/configure.ac b/configure.ac index 5ae1c6a..88eddca 100644 --- a/configure.ac +++ b/configure.ac @@ -1334,7 +1334,7 @@ checkMake380() { checkMake380 make checkMake380 gmake -AC_CONFIG_FILES([mk/config.mk mk/install.mk mk/project.mk rts/rts.cabal compiler/ghc.cabal ghc/ghc-bin.cabal utils/runghc/runghc.cabal utils/gen-dll/gen-dll.cabal libraries/ghc-boot/ghc-boot.cabal libraries/ghc-boot-th/ghc-boot-th.cabal libraries/ghci/ghci.cabal libraries/ghc-heap/ghc-heap.cabal settings docs/users_guide/ghc_config.py docs/index.html libraries/prologue.txt distrib/configure.ac]) +AC_CONFIG_FILES([mk/config.mk mk/install.mk mk/project.mk rts/rts.cabal compiler/ghc.cabal ghc/ghc-bin.cabal utils/iserv/iserv.cabal utils/iserv-proxy/iserv-proxy.cabal utils/runghc/runghc.cabal utils/gen-dll/gen-dll.cabal libraries/ghc-boot/ghc-boot.cabal libraries/ghc-boot-th/ghc-boot-th.cabal libraries/ghci/ghci.cabal libraries/ghc-heap/ghc-heap.cabal libraries/libiserv/libiserv.cabal settings docs/users_guide/ghc_config.py docs/index.html libraries/prologue.txt distrib/configure.ac]) AC_OUTPUT [ if test "$print_make_warning" = "true"; then diff --git a/docs/users_guide/8.8.1-notes.rst b/docs/users_guide/8.8.1-notes.rst index 69b9c5d..6f6404e 100644 --- a/docs/users_guide/8.8.1-notes.rst +++ b/docs/users_guide/8.8.1-notes.rst @@ -176,6 +176,7 @@ for further change information. libraries/haskeline/haskeline.cabal: Dependency of ``ghci`` executable libraries/hpc/hpc.cabal: Dependency of ``hpc`` executable libraries/integer-gmp/integer-gmp.cabal: Core library + libraries/libiserv/libiserv.cabal: Internal compiler library libraries/mtl/mtl.cabal: Dependency of ``Cabal`` library libraries/parsec/parsec.cabal: Dependency of ``Cabal`` library libraries/process/process.cabal: Dependency of ``ghc`` library diff --git a/libraries/libiserv/libiserv.cabal b/libraries/libiserv/libiserv.cabal.in similarity index 80% rename from libraries/libiserv/libiserv.cabal rename to libraries/libiserv/libiserv.cabal.in index 196d36c..31eaaeb 100644 --- a/libraries/libiserv/libiserv.cabal +++ b/libraries/libiserv/libiserv.cabal.in @@ -1,5 +1,9 @@ +-- WARNING: libiserv.cabal is automatically generated from libiserv.cabal.in by +-- ../../configure. Make sure you are editing libiserv.cabal.in, not +-- libiserv.cabal. + Name: libiserv -Version: 8.7.1 +Version: @ProjectVersionMunged@ Copyright: XXX License: BSD3 License-File: LICENSE @@ -25,7 +29,7 @@ Library bytestring >= 0.10 && < 0.11, containers >= 0.5 && < 0.7, deepseq >= 1.4 && < 1.5, - ghci == 8.7.* + ghci == @ProjectVersionMunged@ if flag(network) Exposed-Modules: Remote.Message , Remote.Slave diff --git a/utils/iserv-proxy/iserv-proxy.cabal b/utils/iserv-proxy/iserv-proxy.cabal.in similarity index 90% rename from utils/iserv-proxy/iserv-proxy.cabal rename to utils/iserv-proxy/iserv-proxy.cabal.in index 5d276b2..0819064 100644 --- a/utils/iserv-proxy/iserv-proxy.cabal +++ b/utils/iserv-proxy/iserv-proxy.cabal.in @@ -1,5 +1,9 @@ +-- WARNING: iserv-proxy.cabal is automatically generated from iserv-proxy.cabal.in by +-- ../../configure. Make sure you are editing iserv-proxy.cabal.in, not +-- iserv-proxy.cabal. + Name: iserv-proxy -Version: 8.6 +Version: @ProjectVersion@ Copyright: XXX License: BSD3 -- XXX License-File: LICENSE @@ -74,5 +78,5 @@ Executable iserv-proxy directory >= 1.3 && < 1.4, network >= 2.6, filepath >= 1.4 && < 1.5, - ghci == 8.6.*, - libiserv == 8.6.* + ghci == @ProjectVersionMunged@, + libiserv == @ProjectVersionMunged@ diff --git a/utils/iserv/iserv.cabal b/utils/iserv/iserv.cabal.in similarity index 81% rename from utils/iserv/iserv.cabal rename to utils/iserv/iserv.cabal.in index 912734f..356c8a4 100644 --- a/utils/iserv/iserv.cabal +++ b/utils/iserv/iserv.cabal.in @@ -1,5 +1,9 @@ +-- WARNING: iserv.cabal is automatically generated from iserv.cabal.in by +-- ../../configure. Make sure you are editing iserv.cabal.in, not +-- iserv.cabal. + Name: iserv -Version: 8.7.1 +Version: @ProjectVersion@ Copyright: XXX License: BSD3 -- XXX License-File: LICENSE @@ -35,8 +39,8 @@ Executable iserv bytestring >= 0.10 && < 0.11, containers >= 0.5 && < 0.7, deepseq >= 1.4 && < 1.5, - ghci == 8.7.*, - libiserv == 8.7.* + ghci == @ProjectVersionMunged@, + libiserv == @ProjectVersionMunged@ if os(windows) Cpp-Options: -DWINDOWS From git at git.haskell.org Mon Nov 26 18:57:37 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Mon, 26 Nov 2018 18:57:37 +0000 (UTC) Subject: [commit: ghc] master: Fix #15941 by only special-casing visible infix applications (984b75d) Message-ID: <20181126185737.B709C3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/984b75de7082689ebcc6e9d17b37f2c9b3702f71/ghc >--------------------------------------------------------------- commit 984b75de7082689ebcc6e9d17b37f2c9b3702f71 Author: Ryan Scott Date: Mon Nov 26 12:59:50 2018 -0500 Fix #15941 by only special-casing visible infix applications Summary: The iface pretty-printer had a special case for an application of an infix type constructor to two arguments. But this didn't take the visibilities of the arguments into account, which could lead to strange output like `@{LiftedRep} -> @{LiftedRep}` when `-fprint-explicit-kinds` was enabled (#15941). The fix is relatively straightforward: simply plumb through the visibilities of each argument, and only trigger the special case for infix applications if both arguments are visible (i.e., required). Test Plan: make test TEST=T15941 Reviewers: goldfire, bgamari, monoidal Reviewed By: goldfire, monoidal Subscribers: simonpj, rwbarton, carter GHC Trac Issues: #15941 Differential Revision: https://phabricator.haskell.org/D5375 >--------------------------------------------------------------- 984b75de7082689ebcc6e9d17b37f2c9b3702f71 compiler/iface/IfaceType.hs | 28 +++++++++++++++++++++++----- testsuite/tests/ghci/scripts/T15941.script | 3 +++ testsuite/tests/ghci/scripts/T15941.stdout | 3 +++ testsuite/tests/ghci/scripts/all.T | 1 + 4 files changed, 30 insertions(+), 5 deletions(-) diff --git a/compiler/iface/IfaceType.hs b/compiler/iface/IfaceType.hs index 2500073..4a42afe 100644 --- a/compiler/iface/IfaceType.hs +++ b/compiler/iface/IfaceType.hs @@ -8,6 +8,7 @@ This module defines interface types and binders {-# LANGUAGE CPP, FlexibleInstances, BangPatterns #-} {-# LANGUAGE MultiWayIf #-} +{-# LANGUAGE TupleSections #-} -- FlexibleInstances for Binary (DefMethSpec IfaceType) module IfaceType ( @@ -1334,9 +1335,23 @@ ppr_equality ctxt_prec tc args pprIfaceCoTcApp :: PprPrec -> IfaceTyCon -> [IfaceCoercion] -> SDoc -pprIfaceCoTcApp ctxt_prec tc tys = ppr_iface_tc_app ppr_co ctxt_prec tc tys - -ppr_iface_tc_app :: (PprPrec -> a -> SDoc) -> PprPrec -> IfaceTyCon -> [a] -> SDoc +pprIfaceCoTcApp ctxt_prec tc tys = + ppr_iface_tc_app (\prec (co, _) -> ppr_co prec co) ctxt_prec tc + (map (, Required) tys) + -- We are trying to re-use ppr_iface_tc_app here, which requires its + -- arguments to be accompanied by visibilities. But visibility is + -- irrelevant when printing coercions, so just default everything to + -- Required. + +-- | Pretty-prints an application of a type constructor to some arguments +-- (whose visibilities are known). This is polymorphic (over @a@) since we use +-- this function to pretty-print two different things: +-- +-- 1. Types (from `pprTyTcApp'`) +-- +-- 2. Coercions (from 'pprIfaceCoTcApp') +ppr_iface_tc_app :: (PprPrec -> (a, ArgFlag) -> SDoc) + -> PprPrec -> IfaceTyCon -> [(a, ArgFlag)] -> SDoc ppr_iface_tc_app pp _ tc [ty] | tc `ifaceTyConHasKey` listTyConKey = pprPromotionQuote tc <> brackets (pp topPrec ty) @@ -1347,8 +1362,11 @@ ppr_iface_tc_app pp ctxt_prec tc tys | not (isSymOcc (nameOccName (ifaceTyConName tc))) = pprIfacePrefixApp ctxt_prec (ppr tc) (map (pp appPrec) tys) - | [ty1,ty2] <- tys -- Infix, two arguments; - -- we know nothing of precedence though + | [ ty1@(_, Required) + , ty2@(_, Required) ] <- tys + -- Infix, two visible arguments (we know nothing of precedence though). + -- Don't apply this special case if one of the arguments is invisible, + -- lest we print something like (@LiftedRep -> @LiftedRep) (#15941). = pprIfaceInfixApp ctxt_prec (ppr tc) (pp opPrec ty1) (pp opPrec ty2) diff --git a/testsuite/tests/ghci/scripts/T15941.script b/testsuite/tests/ghci/scripts/T15941.script new file mode 100644 index 0000000..b6f44e7 --- /dev/null +++ b/testsuite/tests/ghci/scripts/T15941.script @@ -0,0 +1,3 @@ +:set -XKindSignatures -fprint-explicit-runtime-reps -fprint-explicit-kinds +type T = (->) +:info T diff --git a/testsuite/tests/ghci/scripts/T15941.stdout b/testsuite/tests/ghci/scripts/T15941.stdout new file mode 100644 index 0000000..c6f31a7 --- /dev/null +++ b/testsuite/tests/ghci/scripts/T15941.stdout @@ -0,0 +1,3 @@ +type T = + (->) @{'GHC.Types.LiftedRep} @{'GHC.Types.LiftedRep} :: * -> * -> * + -- Defined at :2:1 diff --git a/testsuite/tests/ghci/scripts/all.T b/testsuite/tests/ghci/scripts/all.T index 8219707..0dc0e5b 100755 --- a/testsuite/tests/ghci/scripts/all.T +++ b/testsuite/tests/ghci/scripts/all.T @@ -290,3 +290,4 @@ test('T15591', normal, ghci_script, ['T15591.script']) test('T15743b', normal, ghci_script, ['T15743b.script']) test('T15827', normal, ghci_script, ['T15827.script']) test('T15898', normal, ghci_script, ['T15898.script']) +test('T15941', normal, ghci_script, ['T15941.script']) From git at git.haskell.org Tue Nov 27 12:19:21 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Nov 2018 12:19:21 +0000 (UTC) Subject: [commit: ghc] master: Hadrian: improve bindist rule (8f52ab9) Message-ID: <20181127121921.F16683A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8f52ab9223544b756010a7a92ea52fffdf1d1c71/ghc >--------------------------------------------------------------- commit 8f52ab9223544b756010a7a92ea52fffdf1d1c71 Author: Alp Mestanogullari Date: Tue Nov 27 13:17:53 2018 +0100 Hadrian: improve bindist rule As outlined in #15925, hadrian bindists had not made a clear choice with respect to relocatable GHCs and wrapper scripts. This commit implements the policy described in the ticket. That is: - the bindists ship {bin, lib} as they are, modulo the addition of haddock from stage2/bin - we now _always_ generate wrapper scripts for all the programs that are in the bindist's bin/ directory The idea being that anyone on Linux/Windows/OS X can just unpack the binary distribution anywhere and start using bin/ghc, while the installation process systematicaly generates wrapper scripts. Test Plan: hadrian/build.sh binary-dist ; cd _build/bindist/ghc-X.Y.Z-arch/; configure --prefix=/tmp/foo && make install Reviewers: snowleopard, bgamari, angerman Reviewed By: snowleopard, bgamari, angerman Subscribers: rwbarton, carter GHC Trac Issues: #15925 Differential Revision: https://phabricator.haskell.org/D5371 >--------------------------------------------------------------- 8f52ab9223544b756010a7a92ea52fffdf1d1c71 hadrian/src/Rules/BinaryDist.hs | 149 ++++++++++++++++++++++++++++++---------- 1 file changed, 111 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 8f52ab9223544b756010a7a92ea52fffdf1d1c71 From git at git.haskell.org Tue Nov 27 13:03:01 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Nov 2018 13:03:01 +0000 (UTC) Subject: [commit: ghc] wip/tdammers/T14375: Tests for T14375 (1090532) Message-ID: <20181127130301.BF11C3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tdammers/T14375 Link : http://ghc.haskell.org/trac/ghc/changeset/10905324cfe232218fa1afa2e98c61ff241b6c0e/ghc >--------------------------------------------------------------- commit 10905324cfe232218fa1afa2e98c61ff241b6c0e Author: Tobias Dammers Date: Tue Nov 27 13:16:57 2018 +0100 Tests for T14375 >--------------------------------------------------------------- 10905324cfe232218fa1afa2e98c61ff241b6c0e testsuite/tests/primops/should_run/T14375-2 | Bin 0 -> 9994904 bytes testsuite/tests/primops/should_run/T14375-2.hs | 38 +++++++++++++++ testsuite/tests/primops/should_run/T14375-2.stdout | 5 ++ testsuite/tests/primops/should_run/T14375.hs | 52 +++++++++++++++++++++ .../should_run/T14375.stdout} | 0 testsuite/tests/primops/should_run/all.T | 3 ++ 6 files changed, 98 insertions(+) diff --git a/testsuite/tests/primops/should_run/T14375-2 b/testsuite/tests/primops/should_run/T14375-2 new file mode 100755 index 0000000..eb35bd2 Binary files /dev/null and b/testsuite/tests/primops/should_run/T14375-2 differ diff --git a/testsuite/tests/primops/should_run/T14375-2.hs b/testsuite/tests/primops/should_run/T14375-2.hs new file mode 100644 index 0000000..8f53c5d --- /dev/null +++ b/testsuite/tests/primops/should_run/T14375-2.hs @@ -0,0 +1,38 @@ +-- Make sure @with#@ holds on to its argument, as promised, keeping it from +-- being garbage-collected. + +{-#LANGUAGE MagicHash #-} + +import System.Mem +import System.Mem.Weak +import GHC.Base +import GHC.IO +import GHC.Prim +import Control.Concurrent +import Control.Monad + +main = do + do + -- For reasons that are unclear to me, we have to nest the @let@ binding in + -- another @do@ block in order to make its scope smaller. If we scope @a@ + -- on the entire body of 'main', then the finalizer doesn't seem to run + -- at all. + let a = 2 + mkWeakPtr a (Just $ putStrLn "finalize") + with a $ do + putStrLn "with" + performMajorGC + threadDelay 10000 + putStrLn "without" + performMajorGC + threadDelay 10000 + putStrLn "going" + + performMajorGC + threadDelay 10000 + putStrLn "gone" + +-- | A simple wrapper for 'with#', making it more palatable to normal 'IO' +-- code. +with :: a -> IO () -> IO () +with thing action = IO (with# thing $ unIO action) diff --git a/testsuite/tests/primops/should_run/T14375-2.stdout b/testsuite/tests/primops/should_run/T14375-2.stdout new file mode 100644 index 0000000..006ff30 --- /dev/null +++ b/testsuite/tests/primops/should_run/T14375-2.stdout @@ -0,0 +1,5 @@ +with +without +finalize +going +gone diff --git a/testsuite/tests/primops/should_run/T14375.hs b/testsuite/tests/primops/should_run/T14375.hs new file mode 100644 index 0000000..a9a6424 --- /dev/null +++ b/testsuite/tests/primops/should_run/T14375.hs @@ -0,0 +1,52 @@ +-- Check that the bug from #14346 doesn't regress. +-- +-- We currently have (at least) two remedies in place: the workaround of +-- marking @allocaBytes(Aligned)@ as @INLINE@, and the new @with#@ primop +-- described in #14375, which should solve the root cause. +-- +-- To reproduce the problem, we need to trick the optimizer into considering +-- the end of the allocaBytes scope unreachable; we do this by using @forever@, +-- and then throwing an exception inside it after we have run enough iterations +-- to either trigger the bug or conclude that things are fine. + +{-#LANGUAGE LambdaCase #-} + +import System.Mem +import System.Mem.Weak +import Control.Concurrent +import Control.Monad +import System.IO +import Data.Maybe +import Data.Word +import GHC.Prim +import Foreign.Marshal.Alloc +import Foreign.Storable +import Control.Exception +import Text.Printf +import Numeric + +newtype Stop = Stop String + deriving (Show) + +instance Exception Stop where + +main = go `catch` handle + where + handle :: Stop -> IO () + handle (Stop e) = putStrLn e + +go :: IO () +go = do + replicateM_ 1000 $ threadDelay 1 + allocaBytes 4 $ \p -> do + performMajorGC + poke p (0xdeadbeef :: Word32) + forever $ do + replicateM_ 10000 $ do + threadDelay 10 + performMajorGC + x <- peek p + unless (x == 0xdeadbeef) $ do + putStrLn $ showHex x "" + throw (Stop "invalid") -- detected bug: abort. + throw (Stop "OK") -- probably no bug: abort. diff --git a/testsuite/tests/driver/T11763.stdout b/testsuite/tests/primops/should_run/T14375.stdout similarity index 100% copy from testsuite/tests/driver/T11763.stdout copy to testsuite/tests/primops/should_run/T14375.stdout diff --git a/testsuite/tests/primops/should_run/all.T b/testsuite/tests/primops/should_run/all.T index 46954e3..2872d2b 100644 --- a/testsuite/tests/primops/should_run/all.T +++ b/testsuite/tests/primops/should_run/all.T @@ -23,3 +23,6 @@ test('ArithInt16', normal, compile_and_run, ['']) test('ArithWord16', normal, compile_and_run, ['']) test('CmpInt16', normal, compile_and_run, ['']) test('CmpWord16', normal, compile_and_run, ['']) + +test('T14375', normal, compile_and_run, ['-threaded']) +test('T14375-2', normal, compile_and_run, ['']) From git at git.haskell.org Tue Nov 27 13:11:03 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Nov 2018 13:11:03 +0000 (UTC) Subject: [commit: ghc] wip/tdammers/T14375: Tests for T14375 (b98fb15) Message-ID: <20181127131103.D364A3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tdammers/T14375 Link : http://ghc.haskell.org/trac/ghc/changeset/b98fb15b3e6ee5bf01f37abe3598fa8145ed3c7b/ghc >--------------------------------------------------------------- commit b98fb15b3e6ee5bf01f37abe3598fa8145ed3c7b Author: Tobias Dammers Date: Tue Nov 27 13:16:57 2018 +0100 Tests for T14375 >--------------------------------------------------------------- b98fb15b3e6ee5bf01f37abe3598fa8145ed3c7b testsuite/tests/primops/should_run/T14375-2.hs | 38 ++++++++++++++++ testsuite/tests/primops/should_run/T14375-2.stdout | 5 +++ testsuite/tests/primops/should_run/T14375.hs | 52 ++++++++++++++++++++++ .../should_run/T14375.stdout} | 0 testsuite/tests/primops/should_run/all.T | 3 ++ 5 files changed, 98 insertions(+) diff --git a/testsuite/tests/primops/should_run/T14375-2.hs b/testsuite/tests/primops/should_run/T14375-2.hs new file mode 100644 index 0000000..8f53c5d --- /dev/null +++ b/testsuite/tests/primops/should_run/T14375-2.hs @@ -0,0 +1,38 @@ +-- Make sure @with#@ holds on to its argument, as promised, keeping it from +-- being garbage-collected. + +{-#LANGUAGE MagicHash #-} + +import System.Mem +import System.Mem.Weak +import GHC.Base +import GHC.IO +import GHC.Prim +import Control.Concurrent +import Control.Monad + +main = do + do + -- For reasons that are unclear to me, we have to nest the @let@ binding in + -- another @do@ block in order to make its scope smaller. If we scope @a@ + -- on the entire body of 'main', then the finalizer doesn't seem to run + -- at all. + let a = 2 + mkWeakPtr a (Just $ putStrLn "finalize") + with a $ do + putStrLn "with" + performMajorGC + threadDelay 10000 + putStrLn "without" + performMajorGC + threadDelay 10000 + putStrLn "going" + + performMajorGC + threadDelay 10000 + putStrLn "gone" + +-- | A simple wrapper for 'with#', making it more palatable to normal 'IO' +-- code. +with :: a -> IO () -> IO () +with thing action = IO (with# thing $ unIO action) diff --git a/testsuite/tests/primops/should_run/T14375-2.stdout b/testsuite/tests/primops/should_run/T14375-2.stdout new file mode 100644 index 0000000..006ff30 --- /dev/null +++ b/testsuite/tests/primops/should_run/T14375-2.stdout @@ -0,0 +1,5 @@ +with +without +finalize +going +gone diff --git a/testsuite/tests/primops/should_run/T14375.hs b/testsuite/tests/primops/should_run/T14375.hs new file mode 100644 index 0000000..a9a6424 --- /dev/null +++ b/testsuite/tests/primops/should_run/T14375.hs @@ -0,0 +1,52 @@ +-- Check that the bug from #14346 doesn't regress. +-- +-- We currently have (at least) two remedies in place: the workaround of +-- marking @allocaBytes(Aligned)@ as @INLINE@, and the new @with#@ primop +-- described in #14375, which should solve the root cause. +-- +-- To reproduce the problem, we need to trick the optimizer into considering +-- the end of the allocaBytes scope unreachable; we do this by using @forever@, +-- and then throwing an exception inside it after we have run enough iterations +-- to either trigger the bug or conclude that things are fine. + +{-#LANGUAGE LambdaCase #-} + +import System.Mem +import System.Mem.Weak +import Control.Concurrent +import Control.Monad +import System.IO +import Data.Maybe +import Data.Word +import GHC.Prim +import Foreign.Marshal.Alloc +import Foreign.Storable +import Control.Exception +import Text.Printf +import Numeric + +newtype Stop = Stop String + deriving (Show) + +instance Exception Stop where + +main = go `catch` handle + where + handle :: Stop -> IO () + handle (Stop e) = putStrLn e + +go :: IO () +go = do + replicateM_ 1000 $ threadDelay 1 + allocaBytes 4 $ \p -> do + performMajorGC + poke p (0xdeadbeef :: Word32) + forever $ do + replicateM_ 10000 $ do + threadDelay 10 + performMajorGC + x <- peek p + unless (x == 0xdeadbeef) $ do + putStrLn $ showHex x "" + throw (Stop "invalid") -- detected bug: abort. + throw (Stop "OK") -- probably no bug: abort. diff --git a/testsuite/tests/driver/T11763.stdout b/testsuite/tests/primops/should_run/T14375.stdout similarity index 100% copy from testsuite/tests/driver/T11763.stdout copy to testsuite/tests/primops/should_run/T14375.stdout diff --git a/testsuite/tests/primops/should_run/all.T b/testsuite/tests/primops/should_run/all.T index 46954e3..2872d2b 100644 --- a/testsuite/tests/primops/should_run/all.T +++ b/testsuite/tests/primops/should_run/all.T @@ -23,3 +23,6 @@ test('ArithInt16', normal, compile_and_run, ['']) test('ArithWord16', normal, compile_and_run, ['']) test('CmpInt16', normal, compile_and_run, ['']) test('CmpWord16', normal, compile_and_run, ['']) + +test('T14375', normal, compile_and_run, ['-threaded']) +test('T14375-2', normal, compile_and_run, ['']) From git at git.haskell.org Tue Nov 27 20:23:16 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Nov 2018 20:23:16 +0000 (UTC) Subject: [commit: packages/haskeline] master: Add an Appveyor build. (#92) (0d42f1c) Message-ID: <20181127202316.B06D83A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskeline On branch : master Link : http://git.haskell.org/packages/haskeline.git/commitdiff/0d42f1ce7f4d1f084ddf5987dffb306e3fede1b7 >--------------------------------------------------------------- commit 0d42f1ce7f4d1f084ddf5987dffb306e3fede1b7 Author: Judah Jacobson Date: Sat Oct 6 03:57:57 2018 -0700 Add an Appveyor build. (#92) >--------------------------------------------------------------- 0d42f1ce7f4d1f084ddf5987dffb306e3fede1b7 appveyor.yml | 26 ++++++++++++++++++++++++++ 1 file changed, 26 insertions(+) diff --git a/appveyor.yml b/appveyor.yml new file mode 100644 index 0000000..6cd2b7d --- /dev/null +++ b/appveyor.yml @@ -0,0 +1,26 @@ +build: off + +before_test: +# http://help.appveyor.com/discussions/problems/6312-curl-command-not-found +- set PATH=C:\Program Files\Git\mingw64\bin;%PATH% + +- curl -sS -ostack.zip -L --insecure https://get.haskellstack.org/stable/windows-x86_64.zip +- 7z x stack.zip stack.exe + +clone_folder: "c:\\stack" +environment: + global: + STACK_ROOT: "c:\\sr" + + # Override the temp directory to avoid sed escaping issues + # See https://github.com/haskell/cabal/issues/5386 + TMP: "c:\\tmp" + +test_script: + +# Install toolchain, but do it silently due to lots of output +- stack %ARGS% setup > nul + +# The ugly echo "" hack is to avoid complaints about 0 being an invalid file +# descriptor +- echo "" | stack --no-terminal test From git at git.haskell.org Tue Nov 27 20:23:18 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Nov 2018 20:23:18 +0000 (UTC) Subject: [commit: packages/haskeline] master: Don't check in CI that sdist works. (#93) (2d092c5) Message-ID: <20181127202318.B48623A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskeline On branch : master Link : http://git.haskell.org/packages/haskeline.git/commitdiff/2d092c5b24a7e02896b545a978e37f36ab518d44 >--------------------------------------------------------------- commit 2d092c5b24a7e02896b545a978e37f36ab518d44 Author: Judah Jacobson Date: Sat Oct 6 04:48:34 2018 -0700 Don't check in CI that sdist works. (#93) Haskeline doesn't have a custom Setup script, so that step isn't providing any value. >--------------------------------------------------------------- 2d092c5b24a7e02896b545a978e37f36ab518d44 .travis.yml | 11 ----------- 1 file changed, 11 deletions(-) diff --git a/.travis.yml b/.travis.yml index 775d0b0..4c4da28 100644 --- a/.travis.yml +++ b/.travis.yml @@ -35,14 +35,3 @@ script: - cabal configure -v2 # -v2 provides useful information for debugging - cabal build # this builds all libraries and executables (including tests/benchmarks) - cabal check - - cabal sdist # tests that a source-distribution can be generated - -# The following scriptlet checks that the resulting source distribution can be built & installed - - export SRC_TGZ=$(cabal info . | awk '{print $2 ".tar.gz";exit}') ; - cd dist/; - if [ -f "$SRC_TGZ" ]; then - cabal install --force-reinstalls "$SRC_TGZ"; - else - echo "expected '$SRC_TGZ' not found"; - exit 1; - fi From git at git.haskell.org Tue Nov 27 20:23:20 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Nov 2018 20:23:20 +0000 (UTC) Subject: [commit: packages/haskeline] master: Bump the lower bound to ghc-8.0. (#94) (9ad673c) Message-ID: <20181127202320.BB5693A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskeline On branch : master Link : http://git.haskell.org/packages/haskeline.git/commitdiff/9ad673ce45ebb8b739eb58b2a118956c65d4ed7c >--------------------------------------------------------------- commit 9ad673ce45ebb8b739eb58b2a118956c65d4ed7c Author: Judah Jacobson Date: Sat Oct 6 05:32:49 2018 -0700 Bump the lower bound to ghc-8.0. (#94) Also: - Add CI testing up to ghc-8.6.1 - Don't install explicit Cabal versions, now that we don't have a custom Setup script. >--------------------------------------------------------------- 9ad673ce45ebb8b739eb58b2a118956c65d4ed7c .travis.yml | 15 ++++----------- System/Console/Haskeline/Backend/Terminfo.hs | 1 - System/Console/Haskeline/Backend/Win32.hsc | 3 --- System/Console/Haskeline/InputT.hs | 2 -- System/Console/Haskeline/MonadException.hs | 3 --- System/Console/Haskeline/Monads.hs | 9 ++++----- System/Console/Haskeline/Term.hs | 4 ++-- haskeline.cabal | 6 +++--- 8 files changed, 13 insertions(+), 30 deletions(-) diff --git a/.travis.yml b/.travis.yml index 4c4da28..9bbfc7d 100644 --- a/.travis.yml +++ b/.travis.yml @@ -2,17 +2,11 @@ # # NB: don't set `language: haskell` here env: - - CABALVER=1.16 GHCVER=7.4.1 - - CABALVER=1.16 GHCVER=7.4.2 - - CABALVER=1.16 GHCVER=7.6.1 - - CABALVER=1.16 GHCVER=7.6.2 - - CABALVER=1.18 GHCVER=7.6.3 - - CABALVER=1.18 GHCVER=7.8.1 - - CABALVER=1.18 GHCVER=7.8.2 - - CABALVER=1.18 GHCVER=7.8.3 - - CABALVER=1.18 GHCVER=7.8.4 - - CABALVER=1.22 GHCVER=7.10.3 - CABALVER=1.24 GHCVER=8.0.1 + - CABALVER=1.24 GHCVER=8.0.2 + - CABALVER=2.0 GHCVER=8.2.2 + - CABALVER=2.2 GHCVER=8.4.3 + - CABALVER=2.4 GHCVER=8.6.1 # Note: the distinction between `before_install` and `install` is not important. before_install: @@ -26,7 +20,6 @@ install: - echo "$(ghc --version) [$(ghc --print-project-git-commit-id 2> /dev/null || echo '?')]" - travis_retry cabal update - cabal install --only-dependencies - - cabal install "Cabal == $CABALVER.*" # Use the same Cabal version for Setup.hs and cabal-install # Here starts the actual work to be performed for the package under test; any command which exits with a non-zero exit code causes the build to fail. script: diff --git a/System/Console/Haskeline/Backend/Terminfo.hs b/System/Console/Haskeline/Backend/Terminfo.hs index 20f996c..6a41c53 100644 --- a/System/Console/Haskeline/Backend/Terminfo.hs +++ b/System/Console/Haskeline/Backend/Terminfo.hs @@ -5,7 +5,6 @@ module System.Console.Haskeline.Backend.Terminfo( where import System.Console.Terminfo -import Control.Applicative import Control.Monad import Data.List(foldl') import System.IO diff --git a/System/Console/Haskeline/Backend/Win32.hsc b/System/Console/Haskeline/Backend/Win32.hsc index bb37a50..7ba41d4 100644 --- a/System/Console/Haskeline/Backend/Win32.hsc +++ b/System/Console/Haskeline/Backend/Win32.hsc @@ -166,9 +166,6 @@ getKeyEvent p = do data Coord = Coord {coordX, coordY :: Int} deriving Show -#if __GLASGOW_HASKELL__ < 711 -#let alignment t = "%lu", (unsigned long)offsetof(struct {char x__; t (y__); }, y__) -#endif instance Storable Coord where sizeOf _ = (#size COORD) alignment _ = (#alignment COORD) diff --git a/System/Console/Haskeline/InputT.hs b/System/Console/Haskeline/InputT.hs index 1fcd4cc..e23d35b 100644 --- a/System/Console/Haskeline/InputT.hs +++ b/System/Console/Haskeline/InputT.hs @@ -13,8 +13,6 @@ import System.Console.Haskeline.Term import System.Directory(getHomeDirectory) import System.FilePath -import Control.Applicative -import Control.Monad (liftM, ap) import Control.Monad.Fix import System.IO import Data.IORef diff --git a/System/Console/Haskeline/MonadException.hs b/System/Console/Haskeline/MonadException.hs index b796bf0..7ced927 100644 --- a/System/Console/Haskeline/MonadException.hs +++ b/System/Console/Haskeline/MonadException.hs @@ -28,9 +28,6 @@ module System.Console.Haskeline.MonadException( import qualified Control.Exception as E import Control.Exception (Exception,SomeException) -#if __GLASGOW_HASKELL__ < 705 -import Prelude hiding (catch) -#endif import Control.Monad(liftM, join) import Control.Monad.IO.Class import Control.Monad.Trans.Identity diff --git a/System/Console/Haskeline/Monads.hs b/System/Console/Haskeline/Monads.hs index d5fc1bb..b8e8369 100644 --- a/System/Console/Haskeline/Monads.hs +++ b/System/Console/Haskeline/Monads.hs @@ -29,9 +29,6 @@ import Control.Monad.Trans.Maybe (MaybeT(MaybeT),runMaybeT) import Control.Monad.Trans.Reader hiding (ask,asks) import qualified Control.Monad.Trans.Reader as Reader import Data.IORef -#if __GLASGOW_HASKELL__ < 705 -import Prelude hiding (catch) -#endif import System.Console.Haskeline.MonadException @@ -44,7 +41,8 @@ instance Monad m => MonadReader r (ReaderT r m) where instance Monad m => MonadReader s (StateT s m) where ask = get -instance (MonadReader r m, MonadTrans t, Monad (t m)) => MonadReader r (t m) where +instance {-# OVERLAPPABLE #-} (MonadReader r m, MonadTrans t, Monad (t m)) + => MonadReader r (t m) where ask = lift ask asks :: MonadReader r m => (r -> a) -> m a @@ -111,7 +109,8 @@ instance Monad m => MonadState s (StateT s m) where get = StateT $ \s -> return $ \f -> f s s put s = s `seq` StateT $ \_ -> return $ \f -> f () s -instance (MonadState s m, MonadTrans t, Monad (t m)) => MonadState s (t m) where +instance {-# OVERLAPPABLE #-} (MonadState s m, MonadTrans t, Monad (t m)) + => MonadState s (t m) where get = lift get put = lift . put diff --git a/System/Console/Haskeline/Term.hs b/System/Console/Haskeline/Term.hs index acdcf77..d1b5203 100644 --- a/System/Console/Haskeline/Term.hs +++ b/System/Console/Haskeline/Term.hs @@ -9,7 +9,7 @@ import System.Console.Haskeline.Completion(Completion) import Control.Concurrent import Control.Concurrent.STM import Data.Word -import Control.Exception (fromException, AsyncException(..),bracket_) +import Control.Exception (fromException, AsyncException(..)) import Data.Typeable import System.IO import Control.Monad(liftM,when,guard) @@ -104,7 +104,7 @@ class (MonadReader Prefs m , MonadReader Layout m, MonadException m) => CommandMonad m where runCompletion :: (String,String) -> m (String,[Completion]) -instance (MonadTrans t, CommandMonad m, MonadReader Prefs (t m), +instance {-# OVERLAPPABLE #-} (MonadTrans t, CommandMonad m, MonadReader Prefs (t m), MonadException (t m), MonadReader Layout (t m)) => CommandMonad (t m) where diff --git a/haskeline.cabal b/haskeline.cabal index 26bca84..a915766 100644 --- a/haskeline.cabal +++ b/haskeline.cabal @@ -42,9 +42,9 @@ Library -- We require ghc>=7.4.1 (base>=4.5) to use the base library encodings, even -- though it was implemented in earlier releases, due to GHC bug #5436 which -- wasn't fixed until 7.4.1 - Build-depends: base >=4.5 && < 4.13, containers>=0.4 && < 0.7, + Build-depends: base >=4.9 && < 4.13, containers>=0.4 && < 0.7, directory>=1.1 && < 1.4, bytestring>=0.9 && < 0.11, - filepath >= 1.2 && < 1.5, transformers >= 0.2 && < 0.6, + filepath >= 1.2 && < 1.5, transformers >= 0.4 && < 0.6, process >= 1.0 && < 1.7, stm >= 2.4 && < 2.6 Default-Language: Haskell98 Default-Extensions: @@ -53,7 +53,7 @@ Library FlexibleContexts, ExistentialQuantification ScopedTypeVariables, GeneralizedNewtypeDeriving StandaloneDeriving - MultiParamTypeClasses, OverlappingInstances + MultiParamTypeClasses, UndecidableInstances ScopedTypeVariables, CPP, DeriveDataTypeable, PatternGuards From git at git.haskell.org Tue Nov 27 20:23:22 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Nov 2018 20:23:22 +0000 (UTC) Subject: [commit: packages/haskeline] master: Simplify and speed up the Travis CI. (#95) (1067a3d) Message-ID: <20181127202322.C04363A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskeline On branch : master Link : http://git.haskell.org/packages/haskeline.git/commitdiff/1067a3d0e4766072d4dab31ac4131d2ed811c801 >--------------------------------------------------------------- commit 1067a3d0e4766072d4dab31ac4131d2ed811c801 Author: Judah Jacobson Date: Sat Oct 6 06:21:56 2018 -0700 Simplify and speed up the Travis CI. (#95) - Use Travis's build-in apt support - Use `language: c` explicitly - Remove unnecessary `cabal` invocations - Remove the separate `before_install` step >--------------------------------------------------------------- 1067a3d0e4766072d4dab31ac4131d2ed811c801 .travis.yml | 33 +++++++++++++++------------------ 1 file changed, 15 insertions(+), 18 deletions(-) diff --git a/.travis.yml b/.travis.yml index 9bbfc7d..e8ca54d 100644 --- a/.travis.yml +++ b/.travis.yml @@ -1,30 +1,27 @@ -# Based on https://github.com/hvr/multi-ghc-travis -# -# NB: don't set `language: haskell` here -env: - - CABALVER=1.24 GHCVER=8.0.1 - - CABALVER=1.24 GHCVER=8.0.2 - - CABALVER=2.0 GHCVER=8.2.2 - - CABALVER=2.2 GHCVER=8.4.3 - - CABALVER=2.4 GHCVER=8.6.1 +# Use a lightweight base image; we provide our own build tools. +language: c -# Note: the distinction between `before_install` and `install` is not important. -before_install: - - travis_retry sudo add-apt-repository -y ppa:hvr/ghc - - travis_retry sudo apt-get update - - travis_retry sudo apt-get install cabal-install-$CABALVER ghc-$GHCVER - - export PATH=/opt/ghc/$GHCVER/bin:/opt/cabal/$CABALVER/bin:$PATH +matrix: + include: + - env: CABALVER=1.24 GHCVER=8.0.1 + addons: {apt: {packages: [cabal-install-1.24, ghc-8.0.1], sources: [hvr-ghc]}} + - env: CABALVER=1.24 GHCVER=8.0.2 + addons: {apt: {packages: [cabal-install-1.24, ghc-8.0.2], sources: [hvr-ghc]}} + - env: CABALVER=2.0 GHCVER=8.2.2 + addons: {apt: {packages: [cabal-install-2.0, ghc-8.2.2], sources: [hvr-ghc]}} + - env: CABALVER=2.2 GHCVER=8.4.3 + addons: {apt: {packages: [cabal-install-2.2, ghc-8.4.3], sources: [hvr-ghc]}} + - env: CABALVER=2.4 GHCVER=8.6.1 + addons: {apt: {packages: [cabal-install-2.4, ghc-8.6.1], sources: [hvr-ghc]}} install: + - export PATH=/opt/ghc/$GHCVER/bin:/opt/cabal/$CABALVER/bin:$PATH - cabal --version - echo "$(ghc --version) [$(ghc --print-project-git-commit-id 2> /dev/null || echo '?')]" - travis_retry cabal update - cabal install --only-dependencies -# Here starts the actual work to be performed for the package under test; any command which exits with a non-zero exit code causes the build to fail. script: - - if [ -f configure.ac ]; then autoreconf -i; fi - - cabal --version - cabal configure -v2 # -v2 provides useful information for debugging - cabal build # this builds all libraries and executables (including tests/benchmarks) - cabal check From git at git.haskell.org Tue Nov 27 20:23:24 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Nov 2018 20:23:24 +0000 (UTC) Subject: [commit: packages/haskeline] master: Fix all warnings, and set `-Werror` in CI. (#96) (6a00113) Message-ID: <20181127202324.C77A03A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskeline On branch : master Link : http://git.haskell.org/packages/haskeline.git/commitdiff/6a00113ab77337b2838ee247013574544c3d4644 >--------------------------------------------------------------- commit 6a00113ab77337b2838ee247013574544c3d4644 Author: Judah Jacobson Date: Sat Oct 6 08:09:34 2018 -0700 Fix all warnings, and set `-Werror` in CI. (#96) >--------------------------------------------------------------- 6a00113ab77337b2838ee247013574544c3d4644 .travis.yml | 2 +- System/Console/Haskeline/Backend/Posix.hsc | 2 +- System/Console/Haskeline/Backend/Terminfo.hs | 3 +++ System/Console/Haskeline/Backend/Win32.hsc | 1 - System/Console/Haskeline/History.hs | 2 +- System/Console/Haskeline/MonadException.hs | 2 +- System/Console/Haskeline/Monads.hs | 2 +- System/Console/Haskeline/RunCommand.hs | 2 +- System/Console/Haskeline/Term.hs | 2 +- stack.yaml | 3 +++ 10 files changed, 13 insertions(+), 8 deletions(-) diff --git a/.travis.yml b/.travis.yml index e8ca54d..29407d4 100644 --- a/.travis.yml +++ b/.travis.yml @@ -22,6 +22,6 @@ install: - cabal install --only-dependencies script: - - cabal configure -v2 # -v2 provides useful information for debugging + - cabal configure -v2 --ghc-options='-Werror' # -v2 provides useful information for debugging - cabal build # this builds all libraries and executables (including tests/benchmarks) - cabal check diff --git a/System/Console/Haskeline/Backend/Posix.hsc b/System/Console/Haskeline/Backend/Posix.hsc index 846e227..678c97d 100644 --- a/System/Console/Haskeline/Backend/Posix.hsc +++ b/System/Console/Haskeline/Backend/Posix.hsc @@ -303,7 +303,7 @@ posixRunTerm hs layoutGetters keys wrapGetEvent evalBackend = do type PosixT m = ReaderT Handles m -runPosixT :: Monad m => Handles -> PosixT m a -> m a +runPosixT :: Handles -> PosixT m a -> m a runPosixT h = runReaderT' h fileRunTerm :: Handle -> IO RunTerm diff --git a/System/Console/Haskeline/Backend/Terminfo.hs b/System/Console/Haskeline/Backend/Terminfo.hs index 6a41c53..fb28553 100644 --- a/System/Console/Haskeline/Backend/Terminfo.hs +++ b/System/Console/Haskeline/Backend/Terminfo.hs @@ -1,3 +1,6 @@ +#if __GLASGOW_HASKELL__ <= 802 +{-# OPTIONS_GHC -Wno-redundant-constraints #-} +#endif module System.Console.Haskeline.Backend.Terminfo( Draw(), runTerminfoDraw diff --git a/System/Console/Haskeline/Backend/Win32.hsc b/System/Console/Haskeline/Backend/Win32.hsc index 7ba41d4..49bd0c6 100644 --- a/System/Console/Haskeline/Backend/Win32.hsc +++ b/System/Console/Haskeline/Backend/Win32.hsc @@ -15,7 +15,6 @@ import Control.Concurrent.STM import Control.Concurrent hiding (throwTo) import Data.Char(isPrint) import Data.Maybe(mapMaybe) -import Control.Applicative import Control.Monad import System.Console.Haskeline.Key diff --git a/System/Console/Haskeline/History.hs b/System/Console/Haskeline/History.hs index 3a92030..3328b03 100644 --- a/System/Console/Haskeline/History.hs +++ b/System/Console/Haskeline/History.hs @@ -86,7 +86,7 @@ addHistory :: String -> History -> History addHistory s h = h {histLines = maybeDropLast (stifleAmt h) (s <| (histLines h))} -- If the sequence is too big, drop the last entry. -maybeDropLast :: Ord a => Maybe Int -> Seq a -> Seq a +maybeDropLast :: Maybe Int -> Seq a -> Seq a maybeDropLast maxAmt hs | rightSize = hs | otherwise = case viewr hs of diff --git a/System/Console/Haskeline/MonadException.hs b/System/Console/Haskeline/MonadException.hs index 7ced927..aa939d3 100644 --- a/System/Console/Haskeline/MonadException.hs +++ b/System/Console/Haskeline/MonadException.hs @@ -1,3 +1,4 @@ +{-# OPTIONS_GHC -fno-warn-warnings-deprecations #-} {- | This module redefines some of the functions in "Control.Exception" to work for more general monads built on top of 'IO'. -} @@ -38,7 +39,6 @@ import Control.Monad.Trans.List import Control.Monad.Trans.Maybe import Control.Monad.Trans.RWS import Control.Monad.Trans.Writer -import Data.Monoid import Control.Concurrent(ThreadId) -- This approach is based on that of the monad-control package. diff --git a/System/Console/Haskeline/Monads.hs b/System/Console/Haskeline/Monads.hs index b8e8369..008c7a8 100644 --- a/System/Console/Haskeline/Monads.hs +++ b/System/Console/Haskeline/Monads.hs @@ -65,7 +65,7 @@ update f = do put s' return x -runReaderT' :: Monad m => r -> ReaderT r m a -> m a +runReaderT' :: r -> ReaderT r m a -> m a runReaderT' = flip runReaderT newtype StateT s m a = StateT { getStateTFunc diff --git a/System/Console/Haskeline/RunCommand.hs b/System/Console/Haskeline/RunCommand.hs index 45472f6..879b2ef 100644 --- a/System/Console/Haskeline/RunCommand.hs +++ b/System/Console/Haskeline/RunCommand.hs @@ -20,7 +20,7 @@ runCommandLoop tops at TermOps{evalTerm = e} prefix cmds initState cmds runCommandLoop' :: forall m n s a . (Term n, CommandMonad n, - MonadState Layout m, MonadReader Prefs n, LineState s) + MonadState Layout m, LineState s) => (forall b . m b -> n b) -> TermOps -> Prefix -> s -> KeyCommand m s a -> n Event -> n a runCommandLoop' liftE tops prefix initState cmds getEvent = do diff --git a/System/Console/Haskeline/Term.hs b/System/Console/Haskeline/Term.hs index d1b5203..1f3d9d6 100644 --- a/System/Console/Haskeline/Term.hs +++ b/System/Console/Haskeline/Term.hs @@ -160,7 +160,7 @@ hWithBinaryMode h = bracket (liftIO $ hGetEncoding h) -- | Utility function for changing a property of a terminal for the duration of -- a computation. -bracketSet :: (Eq a, MonadException m) => IO a -> (a -> IO ()) -> a -> m b -> m b +bracketSet :: MonadException m => IO a -> (a -> IO ()) -> a -> m b -> m b bracketSet getState set newState f = bracket (liftIO getState) (liftIO . set) (\_ -> liftIO (set newState) >> f) diff --git a/stack.yaml b/stack.yaml index bb59f14..a17f99f 100644 --- a/stack.yaml +++ b/stack.yaml @@ -2,3 +2,6 @@ resolver: lts-9.14 packages: - . + +ghc-options: + "$locals": -Wall -Werror From git at git.haskell.org Tue Nov 27 20:23:26 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Nov 2018 20:23:26 +0000 (UTC) Subject: [commit: packages/haskeline] master: Depend on the `exceptions` package. (#97) (f61f592) Message-ID: <20181127202326.D17783A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskeline On branch : master Link : http://git.haskell.org/packages/haskeline.git/commitdiff/f61f592988c2de16c1ab10c617b8c4f6db851f3f >--------------------------------------------------------------- commit f61f592988c2de16c1ab10c617b8c4f6db851f3f Author: Judah Jacobson Date: Sat Oct 20 09:20:37 2018 -0700 Depend on the `exceptions` package. (#97) Removes `System.Console.Haskeline.MonadException`; now we use class constraints from `Control.Monad.Catch`. >--------------------------------------------------------------- f61f592988c2de16c1ab10c617b8c4f6db851f3f System/Console/Haskeline.hs | 28 ++-- System/Console/Haskeline/Backend/DumbTerm.hs | 6 +- System/Console/Haskeline/Backend/Posix.hsc | 22 +-- System/Console/Haskeline/Backend/Posix/Encoder.hs | 5 +- System/Console/Haskeline/Backend/Terminfo.hs | 10 +- System/Console/Haskeline/Backend/Win32.hsc | 21 ++- System/Console/Haskeline/Backend/Win32/Echo.hs | 8 +- System/Console/Haskeline/Command/History.hs | 3 +- System/Console/Haskeline/Emacs.hs | 8 +- System/Console/Haskeline/IO.hs | 1 + System/Console/Haskeline/InputT.hs | 23 +-- System/Console/Haskeline/MonadException.hs | 180 ---------------------- System/Console/Haskeline/Monads.hs | 59 +------ System/Console/Haskeline/Prefs.hs | 3 +- System/Console/Haskeline/RunCommand.hs | 8 +- System/Console/Haskeline/Term.hs | 26 ++-- System/Console/Haskeline/Vi.hs | 8 +- haskeline.cabal | 8 +- stack.yaml | 3 + 19 files changed, 124 insertions(+), 306 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 f61f592988c2de16c1ab10c617b8c4f6db851f3f From git at git.haskell.org Tue Nov 27 20:23:28 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Tue, 27 Nov 2018 20:23:28 +0000 (UTC) Subject: [commit: packages/haskeline] master: Add fallbackCompletion to support module completion in ghci :add (#91) (3281767) Message-ID: <20181127202328.D75193A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/haskeline On branch : master Link : http://git.haskell.org/packages/haskeline.git/commitdiff/328176735bf68e1e6523648dee04b6af73d2bee2 >--------------------------------------------------------------- commit 328176735bf68e1e6523648dee04b6af73d2bee2 Author: Ken Micklas Date: Sat Oct 20 12:23:08 2018 -0400 Add fallbackCompletion to support module completion in ghci :add (#91) >--------------------------------------------------------------- 328176735bf68e1e6523648dee04b6af73d2bee2 System/Console/Haskeline/Completion.hs | 10 ++++++++++ 1 file changed, 10 insertions(+) diff --git a/System/Console/Haskeline/Completion.hs b/System/Console/Haskeline/Completion.hs index b17bb0c..04b8e9a 100644 --- a/System/Console/Haskeline/Completion.hs +++ b/System/Console/Haskeline/Completion.hs @@ -3,6 +3,7 @@ module System.Console.Haskeline.Completion( Completion(..), noCompletion, simpleCompletion, + fallbackCompletion, -- * Word completion completeWord, completeWordWithPrev, @@ -188,3 +189,12 @@ fixPath ('~':c:path) | isPathSeparator c = do home <- getHomeDirectory return (home path) fixPath path = return path + +-- | If the first completer produces no suggestions, fallback to the second +-- completer's output. +fallbackCompletion :: Monad m => CompletionFunc m -> CompletionFunc m -> CompletionFunc m +fallbackCompletion a b input = do + aCompletions <- a input + if null (snd aCompletions) + then b input + else return aCompletions From git at git.haskell.org Wed Nov 28 10:16:16 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 28 Nov 2018 10:16:16 +0000 (UTC) Subject: [commit: ghc] wip/tdammers/T14375: Remove NOINLINE on allocaBytes... functions (9692dc1) Message-ID: <20181128101616.2D18E3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : wip/tdammers/T14375 Link : http://ghc.haskell.org/trac/ghc/changeset/9692dc1d1c3264b8be321990178ea503a4be7f01/ghc >--------------------------------------------------------------- commit 9692dc1d1c3264b8be321990178ea503a4be7f01 Author: Tobias Dammers Date: Wed Nov 28 11:13:43 2018 +0100 Remove NOINLINE on allocaBytes... functions These pragmas were needed as a hack, to prevent dead code elimination from snatching away touch#; but now that we have rewritten these functions using with#, this is no longer necessary. >--------------------------------------------------------------- 9692dc1d1c3264b8be321990178ea503a4be7f01 libraries/base/Foreign/Marshal/Alloc.hs | 19 +------------------ 1 file changed, 1 insertion(+), 18 deletions(-) diff --git a/libraries/base/Foreign/Marshal/Alloc.hs b/libraries/base/Foreign/Marshal/Alloc.hs index aaf6912..94a5363 100644 --- a/libraries/base/Foreign/Marshal/Alloc.hs +++ b/libraries/base/Foreign/Marshal/Alloc.hs @@ -99,7 +99,7 @@ calloc = callocBytes (sizeOf (undefined :: a)) mallocBytes :: Int -> IO (Ptr a) mallocBytes size = failWhenNULL "malloc" (_malloc (fromIntegral size)) --- |Llike 'mallocBytes' but memory is filled with bytes of value zero. +-- |Like 'mallocBytes' but memory is filled with bytes of value zero. -- callocBytes :: Int -> IO (Ptr a) callocBytes size = failWhenNULL "calloc" $ _calloc 1 (fromIntegral size) @@ -116,19 +116,6 @@ alloca :: forall a b . Storable a => (Ptr a -> IO b) -> IO b alloca = allocaBytesAligned (sizeOf (undefined :: a)) (alignment (undefined :: a)) --- Note [NOINLINE for touch#] --- ~~~~~~~~~~~~~~~~~~~~~~~~~~ --- Both allocaBytes and allocaBytesAligned use the touch#, which is notoriously --- fragile in the presence of simplification (see #14346). In particular, the --- simplifier may drop the continuation containing the touch# if it can prove --- that the action passed to allocaBytes will not return. The hack introduced to --- fix this for 8.2.2 is to mark allocaBytes as NOINLINE, ensuring that the --- simplifier can't see the divergence. --- --- These can be removed once #14375 is fixed, which suggests that we instead do --- away with touch# in favor of a primitive that will capture the scoping left --- implicit in the case of touch#. - -- |@'allocaBytes' n f@ executes the computation @f@, passing as argument -- a pointer to a temporarily allocated block of memory of @n@ bytes. -- The block of memory is sufficiently aligned for any of the basic @@ -145,8 +132,6 @@ allocaBytes (I# size) action = IO $ \ s0 -> case action addr of { IO action' -> with# barr# action' s2 }}} --- See Note [NOINLINE for touch#] -{-# NOINLINE allocaBytes #-} allocaBytesAligned :: Int -> Int -> (Ptr a -> IO b) -> IO b allocaBytesAligned (I# size) (I# align) action = IO $ \ s0 -> @@ -156,8 +141,6 @@ allocaBytesAligned (I# size) (I# align) action = IO $ \ s0 -> case action addr of { IO action' -> with# barr# action' s2 }}} --- See Note [NOINLINE for touch#] -{-# NOINLINE allocaBytesAligned #-} -- |Resize a memory area that was allocated with 'malloc' or 'mallocBytes' -- to the size needed to store values of type @b at . The returned pointer From git at git.haskell.org Wed Nov 28 12:32:24 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 28 Nov 2018 12:32:24 +0000 (UTC) Subject: [commit: ghc] master: Add Note [Dead case binders in -O0] (4c8bf63) Message-ID: <20181128123224.13D823A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/4c8bf63b78f2fea56a184ef2a40e616f4b8bc59b/ghc >--------------------------------------------------------------- commit 4c8bf63b78f2fea56a184ef2a40e616f4b8bc59b Author: Sebastian Graf Date: Wed Nov 28 13:28:29 2018 +0100 Add Note [Dead case binders in -O0] After reverting Phab:D5358, Simon (Peyton Jones) asked for a Note summarising why we want to keep the dead case binder check in `cgCase`. Summary from mail conversation: * Phab:D5324 means that we no longer /recompute/ dead-ness of case-binders in STG-land * But TidyPgm preserves dead-ness info (see CoreTidy.tidyIdBndr) * And so we can take advantage of it to avoid a redundant load. This load would be eliminated by CmmSink, but that only happens with -O >--------------------------------------------------------------- 4c8bf63b78f2fea56a184ef2a40e616f4b8bc59b compiler/codeGen/StgCmmExpr.hs | 14 +++++++++++++- 1 file changed, 13 insertions(+), 1 deletion(-) diff --git a/compiler/codeGen/StgCmmExpr.hs b/compiler/codeGen/StgCmmExpr.hs index ea64e45..30603ee 100644 --- a/compiler/codeGen/StgCmmExpr.hs +++ b/compiler/codeGen/StgCmmExpr.hs @@ -305,7 +305,7 @@ cgCase (StgOpApp (StgPrimOp op) args _) bndr (AlgAlt tycon) alts = do { tag_expr <- do_enum_primop op args -- If the binder is not dead, convert the tag to a constructor - -- and assign it. + -- and assign it. See Note [Dead case binders in -O0] ; unless (isDeadBinder bndr) $ do { dflags <- getDynFlags ; tmp_reg <- bindArgToReg (NonVoid bndr) @@ -385,6 +385,18 @@ Now the trouble is that 's' has VoidRep, and we do not bind void arguments in the environment; they don't live anywhere. See the calls to nonVoidIds in various places. So we must not look up 's' in the environment. Instead, just evaluate the RHS! Simple. + +Note [Dead case binders in -O0] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Before CmmSink came to eliminate dead assignments, omitting assignment of dead +case binders was a cheap and worthwhile optimisation. This probably also was the +reason for occurrence hacks such as in Phab:D5339 to exist, because the +occurrence information preserved by 'CoreTidy.tidyIdBndr' was insufficient. + +Nowadays, with CmmSink there's little reason to complicate the code by checking +for dead case binders, except that CmmSink won't run with -O0. Since the +majority of case binders are dead, this optimisation probably still has a great +benefit-cost ratio and we want to keep it for -O0. See also Phab:D5358. -} cgCase (StgApp v []) _ (PrimAlt _) alts From git at git.haskell.org Wed Nov 28 17:09:51 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Wed, 28 Nov 2018 17:09:51 +0000 (UTC) Subject: [commit: ghc] master: Comments only (e08d34b) Message-ID: <20181128170951.E9B3C3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/e08d34bbb4e68cd2c14e8e94ca3933ce5407d65b/ghc >--------------------------------------------------------------- commit e08d34bbb4e68cd2c14e8e94ca3933ce5407d65b Author: Simon Peyton Jones Date: Wed Nov 28 15:30:10 2018 +0000 Comments only >--------------------------------------------------------------- e08d34bbb4e68cd2c14e8e94ca3933ce5407d65b compiler/codeGen/StgCmmCon.hs | 14 ++++++-------- compiler/codeGen/StgCmmExpr.hs | 28 +++++++++++++++++----------- 2 files changed, 23 insertions(+), 19 deletions(-) diff --git a/compiler/codeGen/StgCmmCon.hs b/compiler/codeGen/StgCmmCon.hs index 2ddeceb..258896f 100644 --- a/compiler/codeGen/StgCmmCon.hs +++ b/compiler/codeGen/StgCmmCon.hs @@ -272,14 +272,12 @@ bindConArgs (DataAlt con) base args -- when accessing the constructor field. bind_arg :: (NonVoid Id, ByteOff) -> FCode (Maybe LocalReg) bind_arg (arg@(NonVoid b), offset) - | isDeadBinder b = - -- Do not load unused fields from objects to local variables. - -- (CmmSink can optimize this, but it's cheap and common enough - -- to handle here) - return Nothing - | otherwise = do - emit $ mkTaggedObjectLoad dflags (idToReg dflags arg) base offset tag - Just <$> bindArgToReg arg + | isDeadBinder b -- See Note [Dead-binder optimisation] in StgCmmExpr + = return Nothing + | otherwise + = do { emit $ mkTaggedObjectLoad dflags (idToReg dflags arg) + base offset tag + ; Just <$> bindArgToReg arg } mapMaybeM bind_arg args_w_offsets diff --git a/compiler/codeGen/StgCmmExpr.hs b/compiler/codeGen/StgCmmExpr.hs index 30603ee..7a2340e 100644 --- a/compiler/codeGen/StgCmmExpr.hs +++ b/compiler/codeGen/StgCmmExpr.hs @@ -305,7 +305,7 @@ cgCase (StgOpApp (StgPrimOp op) args _) bndr (AlgAlt tycon) alts = do { tag_expr <- do_enum_primop op args -- If the binder is not dead, convert the tag to a constructor - -- and assign it. See Note [Dead case binders in -O0] + -- and assign it. See Note [Dead-binder optimisation] ; unless (isDeadBinder bndr) $ do { dflags <- getDynFlags ; tmp_reg <- bindArgToReg (NonVoid bndr) @@ -386,17 +386,23 @@ arguments in the environment; they don't live anywhere. See the calls to nonVoidIds in various places. So we must not look up 's' in the environment. Instead, just evaluate the RHS! Simple. -Note [Dead case binders in -O0] +Note [Dead-binder optimisation] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -Before CmmSink came to eliminate dead assignments, omitting assignment of dead -case binders was a cheap and worthwhile optimisation. This probably also was the -reason for occurrence hacks such as in Phab:D5339 to exist, because the -occurrence information preserved by 'CoreTidy.tidyIdBndr' was insufficient. - -Nowadays, with CmmSink there's little reason to complicate the code by checking -for dead case binders, except that CmmSink won't run with -O0. Since the -majority of case binders are dead, this optimisation probably still has a great -benefit-cost ratio and we want to keep it for -O0. See also Phab:D5358. +A case-binder, or data-constructor argument, may be marked as dead, +because we preserve occurrence-info on binders in CoreTidy (see +CoreTidy.tidyIdBndr). + +If the binder is dead, we can sometimes eliminate a load. While +CmmSink will eliminate that load, it's very easy to kill it at source +(giving CmmSink less work to do), and in any case CmmSink only runs +with -O. Since the majority of case binders are dead, this +optimisation probably still has a great benefit-cost ratio and we want +to keep it for -O0. See also Phab:D5358. + +This probably also was the reason for occurrence hack in Phab:D5339 to +exist, perhaps because the occurrence information preserved by +'CoreTidy.tidyIdBndr' was insufficient. But now that CmmSink does the +job we deleted the hacks. -} cgCase (StgApp v []) _ (PrimAlt _) alts From git at git.haskell.org Thu Nov 29 03:41:58 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 29 Nov 2018 03:41:58 +0000 (UTC) Subject: [commit: ghc] tag 'ghc-8.4.4-release' created Message-ID: <20181129034158.3B6C93A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc New tag : ghc-8.4.4-release Referencing: 51283a1ab83040004ff4bffcfd6d5ca2a0101b76 From git at git.haskell.org Thu Nov 29 11:43:43 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 29 Nov 2018 11:43:43 +0000 (UTC) Subject: [commit: ghc] master: Test Trac #15943 (1235ca9) Message-ID: <20181129114343.097933A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/1235ca956c80d7035e1a6c50501a97de66d32b92/ghc >--------------------------------------------------------------- commit 1235ca956c80d7035e1a6c50501a97de66d32b92 Author: Simon Peyton Jones Date: Thu Nov 29 11:42:58 2018 +0000 Test Trac #15943 This test seems to work in HEAD >--------------------------------------------------------------- 1235ca956c80d7035e1a6c50501a97de66d32b92 .../tests/indexed-types/should_compile/T15943.hs | 33 ++++++++++++++++++++++ testsuite/tests/indexed-types/should_compile/all.T | 1 + 2 files changed, 34 insertions(+) diff --git a/testsuite/tests/indexed-types/should_compile/T15943.hs b/testsuite/tests/indexed-types/should_compile/T15943.hs new file mode 100644 index 0000000..36edbbc --- /dev/null +++ b/testsuite/tests/indexed-types/should_compile/T15943.hs @@ -0,0 +1,33 @@ +{-# Language RankNTypes #-} +{-# Language DataKinds #-} +{-# Language KindSignatures #-} +{-# Language PolyKinds #-} +{-# Language TypeFamilyDependencies #-} +{-# Language GADTs #-} +{-# Language TypeSynonymInstances #-} +{-# Language FlexibleInstances #-} +{-# Language QuantifiedConstraints #-} + +module T15943 where + +import Data.Type.Equality +import Data.Coerce +import Data.Type.Coercion +import Data.Kind + +newtype WrapFalse a b = WrapFalse (Hom False a b) +newtype WrapTrue a b = WrapTrue (Hom True a b) + +class + (forall (x :: ob) (y :: ob). Coercible (WrapFalse x y) (WrapTrue y x)) + => + Ríki ob where + + type Hom (or::Bool) = (res :: ob -> ob -> Type) | res -> or + +instance Ríki Type where + type Hom False = (->) + type Hom True = Op + +newtype Op :: Type -> Type -> Type where + Op :: (b -> a) -> Op a b diff --git a/testsuite/tests/indexed-types/should_compile/all.T b/testsuite/tests/indexed-types/should_compile/all.T index 551d382..409e1ef 100644 --- a/testsuite/tests/indexed-types/should_compile/all.T +++ b/testsuite/tests/indexed-types/should_compile/all.T @@ -294,6 +294,7 @@ test('T15322a', normal, compile_fail, ['']) test('T15142', normal, compile, ['']) test('T15352', normal, compile, ['']) test('T15664', normal, compile, ['']) +test('T15943', normal, compile, ['']) test('T15704', normal, compile, ['']) test('T15711', normal, compile, ['-ddump-types']) test('T15852', normal, compile, ['-ddump-types']) From git at git.haskell.org Thu Nov 29 16:16:21 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 29 Nov 2018 16:16:21 +0000 (UTC) Subject: [commit: ghc] master: Hadrian: bump Cabal submodule, install extra dynamic flavours of RTS (fb99716) Message-ID: <20181129161621.A20B73A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/fb9971607c5a41ade71338188c683ee9cb8ca6fc/ghc >--------------------------------------------------------------- commit fb9971607c5a41ade71338188c683ee9cb8ca6fc Author: Alp Mestanogullari Date: Thu Nov 29 17:14:57 2018 +0100 Hadrian: bump Cabal submodule, install extra dynamic flavours of RTS Previously, Hadrian was building all the appropriate dynamic ways for libHSrts but they were not picked up and installed in the package database when we register the rts library. Since we use Cabal for registering packages and the .cabal files of packages as sources of truth for configuring and installing, we ended up patching Cabal to add a new field, 'extra-dynamic-library-flavours', to specify those extra flavours to install in .cabal files: https://github.com/haskell/cabal/pull/5606 We now make use of this in rts.cabal.in to expose dynamic flavours behind a Cabal flag, which Hadrian will use whenever we are building a GHC flavour that requires dynamic libraries. This is all part of a larger plan to build a dynamic stage 2 GHC by default, like with make, which in turn will fix a lot of test failures. See Test Plan: hadrian/build.sh _build/stage1/lib/package.conf.d/rts-1.0.conf _build/stage1/lib/x86_64-.../ should contain many libHSrts-*.so Reviewers: snowleopard, DavidEichmann, bgamari, erikd, simonmar Reviewed By: snowleopard, DavidEichmann Subscribers: rwbarton, carter GHC Trac Issues: #15837 Differential Revision: https://phabricator.haskell.org/D5385 >--------------------------------------------------------------- fb9971607c5a41ade71338188c683ee9cb8ca6fc hadrian/src/Oracles/Setting.hs | 2 +- hadrian/src/Rules/Library.hs | 4 ++-- hadrian/src/Settings/Packages.hs | 1 + libraries/Cabal | 2 +- rts/rts.cabal.in | 10 +++++++++- 5 files changed, 14 insertions(+), 5 deletions(-) diff --git a/hadrian/src/Oracles/Setting.hs b/hadrian/src/Oracles/Setting.hs index 1cdcddf..5197b8e 100644 --- a/hadrian/src/Oracles/Setting.hs +++ b/hadrian/src/Oracles/Setting.hs @@ -218,4 +218,4 @@ libsuf way extension <- setting DynamicExtension -- e.g., .dll or .so version <- setting ProjectVersion -- e.g., 7.11.20141222 let suffix = waySuffix (removeWayUnit Dynamic way) - return ("-ghc" ++ version ++ suffix ++ extension) + return (suffix ++ "-ghc" ++ version ++ extension) diff --git a/hadrian/src/Rules/Library.hs b/hadrian/src/Rules/Library.hs index b53bcc8..334d687 100644 --- a/hadrian/src/Rules/Library.hs +++ b/hadrian/src/Rules/Library.hs @@ -134,7 +134,7 @@ data LibA = LibA String [Integer] Way deriving (Eq, Show) -- | > data DynLibExt = So | Dylib deriving (Eq, Show) --- | > libHS--ghc[_]. +-- | > libHS-[_]-ghc. data LibDyn = LibDyn String [Integer] Way DynLibExt deriving (Eq, Show) -- | > HS-[_].o @@ -231,8 +231,8 @@ parseLibDynFilename :: String -> Parsec.Parsec String () LibDyn parseLibDynFilename ext = do _ <- Parsec.string "libHS" (pkgname, pkgver) <- parsePkgId - _ <- optional $ Parsec.string "-ghc" *> parsePkgVersion way <- addWayUnit Dynamic <$> parseWaySuffix dynamic + _ <- optional $ Parsec.string "-ghc" *> parsePkgVersion _ <- Parsec.string ("." ++ ext) return (LibDyn pkgname pkgver way $ if ext == "so" then So else Dylib) diff --git a/hadrian/src/Settings/Packages.hs b/hadrian/src/Settings/Packages.hs index 4d75e32..51a980c 100644 --- a/hadrian/src/Settings/Packages.hs +++ b/hadrian/src/Settings/Packages.hs @@ -285,6 +285,7 @@ rtsPackageArgs = package rts ? do [ any (wayUnit Profiling) rtsWays ? arg "profiling" , any (wayUnit Debug) rtsWays ? arg "debug" , any (wayUnit Logging) rtsWays ? arg "logging" + , any (wayUnit Dynamic) rtsWays ? arg "dynamic" ] , builder (Cc FindCDependencies) ? cArgs , builder (Ghc CompileCWithGhc) ? map ("-optc" ++) <$> cArgs diff --git a/libraries/Cabal b/libraries/Cabal index 3da088e..064d9e9 160000 --- a/libraries/Cabal +++ b/libraries/Cabal @@ -1 +1 @@ -Subproject commit 3da088e281f5cbc8a731e18ceb698cfea2e45004 +Subproject commit 064d9e9082c825f538655db1868108c48240377e diff --git a/rts/rts.cabal.in b/rts/rts.cabal.in index a20aa57..e9cc7d1 100644 --- a/rts/rts.cabal.in +++ b/rts/rts.cabal.in @@ -1,4 +1,4 @@ -cabal-version: 2.1 +cabal-version: 2.5 name: rts version: 1.0 license: BSD-3-Clause @@ -39,6 +39,8 @@ flag debug default: False flag logging default: False +flag dynamic + default: False library -- rts is a wired in package and @@ -65,8 +67,14 @@ library extra-library-flavours: _debug_p _thr_debug_p if flag(debug) extra-library-flavours: _debug _thr_debug + if flag(dynamic) + extra-dynamic-library-flavours: _debug _thr_debug if flag(logging) extra-library-flavours: _l _thr_l + if flag(dynamic) + extra-dynamic-library-flavours: _l _thr_l + if flag(dynamic) + extra-dynamic-library-flavours: _thr exposed: True exposed-modules: From git at git.haskell.org Thu Nov 29 17:23:06 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 29 Nov 2018 17:23:06 +0000 (UTC) Subject: [commit: ghc] master: Hadrian: support dynamically linking ghc (79d5427) Message-ID: <20181129172306.4E2533A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/79d5427e1f9de02c0b171bf5db46b6b49c6f85e3/ghc >--------------------------------------------------------------- commit 79d5427e1f9de02c0b171bf5db46b6b49c6f85e3 Author: David Eichmann Date: Thu Nov 29 18:22:16 2018 +0100 Hadrian: support dynamically linking ghc * (#15837 point 5) Use the -rpath gcc option and using the $ORIGIN variable which the dynamic linker sets to the location of the ghc binary. * (#15837 point 4) "-fPIC -dynamic" options are used when building ghc when either ghc or the rts have a dynamic way. * (#15837 point 7) "-shared -dynload deploy" options are only used when linking a library (no longer when linking a program). Reviewers: bgamari, alpmestan Reviewed By: alpmestan Subscribers: adamse, rwbarton, carter Differential Revision: https://phabricator.haskell.org/D5281 >--------------------------------------------------------------- 79d5427e1f9de02c0b171bf5db46b6b49c6f85e3 hadrian/src/Context.hs | 13 ++++++- hadrian/src/Hadrian/Utilities.hs | 71 +++++++++++++++++++++++++++++++++++- hadrian/src/Settings/Builders/Ghc.hs | 45 ++++++++++++++++++++--- 3 files changed, 120 insertions(+), 9 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 79d5427e1f9de02c0b171bf5db46b6b49c6f85e3 From git at git.haskell.org Thu Nov 29 17:28:14 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Thu, 29 Nov 2018 17:28:14 +0000 (UTC) Subject: [commit: ghc] master: Taming the Kind Inference Monster (2257a86) Message-ID: <20181129172814.60B383A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/2257a86daa72db382eb927df12a718669d5491f8/ghc >--------------------------------------------------------------- commit 2257a86daa72db382eb927df12a718669d5491f8 Author: Simon Peyton Jones Date: Wed Nov 28 16:06:15 2018 +0000 Taming the Kind Inference Monster My original goal was (Trac #15809) to move towards using level numbers as the basis for deciding which type variables to generalise, rather than searching for the free varaibles of the environment. However it has turned into a truly major refactoring of the kind inference engine. Let's deal with the level-numbers part first: * Augment quantifyTyVars to calculate the type variables to quantify using level numbers, and compare the result with the existing approach. That is; no change in behaviour, just a WARNing if the two approaches give different answers. * To do this I had to get the level number right when calling quantifyTyVars, and this entailed a bit of care, especially in the code for kind-checking type declarations. * However, on the way I was able to eliminate or simplify a number of calls to solveEqualities. This work is incomplete: I'm not /using/ level numbers yet. When I subsequently get rid of any remaining WARNings in quantifyTyVars, that the level-number answers differ from the current answers, then I can rip out the current "free vars of the environment" stuff. Anyway, this led me into deep dive into kind inference for type and class declarations, which is an increasingly soggy part of GHC. Richard already did some good work recently in commit 5e45ad10ffca1ad175b10f6ef3327e1ed8ba25f3 Date: Thu Sep 13 09:56:02 2018 +0200 Finish fix for #14880. The real change that fixes the ticket is described in Note [Naughty quantification candidates] in TcMType. but I kept turning over stones. So this patch has ended up with a pretty significant refactoring of that code too. Kind inference for types and classes ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ * Major refactoring in the way we generalise the inferred kind of a TyCon, in kcTyClGroup. Indeed, I made it into a new top-level function, generaliseTcTyCon. Plus a new Note to explain it Note [Inferring kinds for type declarations]. * We decided (Trac #15592) not to treat class type variables specially when dealing with Inferred/Specified/Required for associated types. That simplifies things quite a bit. I also rewrote Note [Required, Specified, and Inferred for types] * Major refactoring of the crucial function kcLHsQTyVars: I split it into kcLHsQTyVars_Cusk and kcLHsQTyVars_NonCusk because the two are really quite different. The CUSK case is almost entirely rewritten, and is much easier because of our new decision not to treat the class variables specially * I moved all the error checks from tcTyClTyVars (which was a bizarre place for it) into generaliseTcTyCon and/or the CUSK case of kcLHsQTyVars. Now tcTyClTyVars is extremely simple. * I got rid of all the all the subtleties in tcImplicitTKBndrs. Indeed now there is no difference between tcImplicitTKBndrs and kcImplicitTKBndrs; there is now a single bindImplicitTKBndrs. Same for kc/tcExplicitTKBndrs. None of them monkey with level numbers, nor build implication constraints. scopeTyVars is gone entirely, as is kcLHsQTyVarBndrs. It's vastly simpler. I found I could get rid of kcLHsQTyVarBndrs entirely, in favour of the bnew bindExplicitTKBndrs. Quantification ~~~~~~~~~~~~~~ * I now deal with the "naughty quantification candidates" of the previous patch in candidateQTyVars, rather than in quantifyTyVars; see Note [Naughty quantification candidates] in TcMType. I also killed off closeOverKindsCQTvs in favour of the same strategy that we use for tyCoVarsOfType: namely, close over kinds at the occurrences. And candidateQTyVars no longer needs a gbl_tvs argument. * Passing the ContextKind, rather than the expected kind itself, to tc_hs_sig_type_and_gen makes it easy to allocate the expected result kind (when we are in inference mode) at the right level. Type families ~~~~~~~~~~~~~~ * I did a major rewrite of the impenetrable tcFamTyPats. The result is vastly more comprehensible. * I got rid of kcDataDefn entirely, quite a big function. * I re-did the way that checkConsistentFamInst works, so that it allows alpha-renaming of invisible arguments. * The interaction of kind signatures and family instances is tricky. Type families: see Note [Apparently-nullary families] Data families: see Note [Result kind signature for a data family instance] and Note [Eta-reduction for data families] * The consistent instantation of an associated type family is tricky. See Note [Checking consistent instantiation] and Note [Matching in the consistent-instantation check] in TcTyClsDecls. It's now checked in TcTyClsDecls because that is when we have the relevant info to hand. * I got tired of the compromises in etaExpandFamInst, so I did the job properly by adding a field cab_eta_tvs to CoAxBranch. See Coercion.etaExpandCoAxBranch. tcInferApps and friends ~~~~~~~~~~~~~~~~~~~~~~~ * I got rid of the mysterious and horrible ClsInstInfo argument to tcInferApps, checkExpectedKindX, and various checkValid functions. It was horrible! * I got rid of [Type] result of tcInferApps. This list was used only in tcFamTyPats, when checking the LHS of a type instance; and if there is a cast in the middle, the list is meaningless. So I made tcInferApps simpler, and moved the complexity (not much) to tcInferApps. Result: tcInferApps is now pretty comprehensible again. * I refactored the many function in TcMType that instantiate skolems. Smaller things * I rejigged the error message in checkValidTelescope; I think it's quite a bit better now. * checkValidType was not rejecting constraints in a kind signature forall (a :: Eq b => blah). blah2 That led to further errors when we then do an ambiguity check. So I make checkValidType reject it more aggressively. * I killed off quantifyConDecl, instead calling kindGeneralize directly. * I fixed an outright bug in tyCoVarsOfImplic, where we were not colleting the tyvar of the kind of the skolems * Renamed ClsInstInfo to AssocInstInfo, and made it into its own data type * Some fiddling around with pretty-printing of family instances which was trickier than I thought. I wanted wildcards to print as plain "_" in user messages, although they each need a unique identity in the CoAxBranch. Some other oddments * Refactoring around the trace messages from reportUnsolved. * A bit of extra tc-tracing in TcHsSyn.commitFlexi This patch fixes a raft of bugs, and includes tests for them. * #14887 * #15740 * #15764 * #15789 * #15804 * #15817 * #15870 * #15874 * #15881 >--------------------------------------------------------------- 2257a86daa72db382eb927df12a718669d5491f8 compiler/basicTypes/DataCon.hs | 3 +- compiler/basicTypes/OccName.hs | 34 +- compiler/basicTypes/VarEnv.hs | 5 +- compiler/coreSyn/CoreLint.hs | 5 +- compiler/hsSyn/HsDecls.hs | 62 +- compiler/hsSyn/HsTypes.hs | 68 +- compiler/iface/IfaceSyn.hs | 47 +- compiler/iface/MkIface.hs | 33 +- compiler/iface/TcIface.hs | 22 +- compiler/nativeGen/CFG.hs | 1 - compiler/parser/RdrHsSyn.hs | 8 +- compiler/prelude/TysPrim.hs | 19 +- compiler/typecheck/ClsInst.hs | 28 +- compiler/typecheck/FamInst.hs | 44 +- compiler/typecheck/Inst.hs | 31 +- compiler/typecheck/TcBackpack.hs | 2 +- compiler/typecheck/TcBinds.hs | 24 - compiler/typecheck/TcClassDcl.hs | 5 +- compiler/typecheck/TcDeriv.hs | 56 +- compiler/typecheck/TcDerivInfer.hs | 2 +- compiler/typecheck/TcEnv.hs | 10 +- compiler/typecheck/TcErrors.hs | 36 +- compiler/typecheck/TcGenDeriv.hs | 9 +- compiler/typecheck/TcGenGenerics.hs | 2 +- compiler/typecheck/TcHsSyn.hs | 35 +- compiler/typecheck/TcHsType.hs | 1319 +++++++++---------- compiler/typecheck/TcInstDcls.hs | 504 +++++--- compiler/typecheck/TcMType.hs | 509 ++++---- compiler/typecheck/TcPat.hs | 2 +- compiler/typecheck/TcPatSyn.hs | 56 +- compiler/typecheck/TcRnDriver.hs | 13 +- compiler/typecheck/TcRnMonad.hs | 6 +- compiler/typecheck/TcRnTypes.hs | 16 +- compiler/typecheck/TcRules.hs | 36 +- compiler/typecheck/TcSMonad.hs | 4 +- compiler/typecheck/TcSigs.hs | 69 +- compiler/typecheck/TcSimplify.hs | 64 +- compiler/typecheck/TcSplice.hs | 29 +- compiler/typecheck/TcTyClsDecls.hs | 1339 ++++++++++---------- compiler/typecheck/TcUnify.hs | 33 +- compiler/typecheck/TcValidity.hs | 707 ++++++----- compiler/types/CoAxiom.hs | 63 +- compiler/types/Coercion.hs | 140 +- compiler/types/FamInstEnv.hs | 181 ++- compiler/types/TyCoRep.hs | 78 +- compiler/types/TyCon.hs | 15 +- compiler/types/Type.hs | 126 +- compiler/types/Type.hs-boot | 4 +- compiler/types/Unify.hs | 43 +- compiler/utils/FastString.hs | 4 + compiler/utils/Util.hs | 8 +- .../tests/dependent/should_compile/T15743.stderr | 2 +- .../tests/dependent/should_compile/T15743e.stderr | 8 +- .../dependent/should_fail/BadTelescope.stderr | 7 +- .../dependent/should_fail/BadTelescope3.stderr | 6 +- .../dependent/should_fail/BadTelescope4.stderr | 13 +- .../tests/dependent/should_fail/T13895.stderr | 37 +- .../tests/dependent/should_fail/T14066f.stderr | 6 +- .../tests/dependent/should_fail/T14066g.stderr | 8 +- .../tests/dependent/should_fail/T15591b.stderr | 9 +- .../tests/dependent/should_fail/T15591c.stderr | 9 +- .../tests/dependent/should_fail/T15743c.stderr | 13 +- .../tests/dependent/should_fail/T15743d.stderr | 13 +- testsuite/tests/ghci/scripts/T10059.stdout | 6 +- testsuite/tests/ghci/scripts/T15591.hs | 8 +- testsuite/tests/ghci/scripts/T15591.stdout | 6 +- testsuite/tests/ghci/scripts/T15743b.stdout | 2 +- testsuite/tests/ghci/scripts/T6018ghcifail.stderr | 4 +- testsuite/tests/ghci/scripts/T7873.stderr | 2 +- testsuite/tests/ghci/scripts/ghci059.stdout | 2 +- .../indexed-types/should_compile/T15711.stderr | 4 +- .../tests/indexed-types/should_compile/T15740a.hs | 12 + .../tests/indexed-types/should_compile/T15764a.hs | 14 + .../indexed-types/should_compile/T15852.stderr | 11 +- .../indexed-types/should_compile/T3017.stderr | 11 +- testsuite/tests/indexed-types/should_compile/all.T | 2 + .../should_fail/ExplicitForAllFams4a.stderr | 12 +- .../should_fail/ExplicitForAllFams4b.hs | 1 + .../should_fail/ExplicitForAllFams4b.stderr | 87 +- .../indexed-types/should_fail/SimpleFail13.stderr | 2 +- .../indexed-types/should_fail/SimpleFail2a.hs | 2 +- .../indexed-types/should_fail/SimpleFail2a.stderr | 7 +- .../tests/indexed-types/should_fail/SimpleFail9.hs | 4 +- .../indexed-types/should_fail/SimpleFail9.stderr | 4 +- .../tests/indexed-types/should_fail/T10817.stderr | 9 +- .../tests/indexed-types/should_fail/T10899.stderr | 3 +- .../tests/indexed-types/should_fail/T11450.stderr | 4 +- .../tests/indexed-types/should_fail/T12041.stderr | 10 +- .../indexed-types/should_fail/T13092/T13092.stderr | 2 +- .../should_fail/T13092c/T13092c.stderr | 2 +- .../tests/indexed-types/should_fail/T13972.hs | 6 + .../tests/indexed-types/should_fail/T13972.stderr | 7 - .../tests/indexed-types/should_fail/T14045a.hs | 5 + .../tests/indexed-types/should_fail/T14045a.stderr | 7 - .../tests/indexed-types/should_fail/T14179.stderr | 4 +- .../tests/indexed-types/should_fail/T14887.hs | 14 + .../tests/indexed-types/should_fail/T14887.stderr | 12 + .../tests/indexed-types/should_fail/T15740.hs | 12 + .../tests/indexed-types/should_fail/T15740.stderr | 11 + .../tests/indexed-types/should_fail/T15764.hs | 14 + .../tests/indexed-types/should_fail/T15764.stderr | 11 + .../tests/indexed-types/should_fail/T15870.hs | 32 + .../tests/indexed-types/should_fail/T15870.stderr | 6 + .../tests/indexed-types/should_fail/T7536.stderr | 9 +- testsuite/tests/indexed-types/should_fail/T7938.hs | 0 .../tests/indexed-types/should_fail/T7938.stderr | 2 +- .../tests/indexed-types/should_fail/T9160.stderr | 12 +- testsuite/tests/indexed-types/should_fail/all.T | 8 +- .../tests/partial-sigs/should_compile/ADT.stderr | 2 +- .../should_compile/DataFamilyInstanceLHS.stderr | 10 +- .../partial-sigs/should_compile/Meltdown.stderr | 2 +- .../NamedWildcardInDataFamilyInstanceLHS.stderr | 9 +- .../NamedWildcardInTypeFamilyInstanceLHS.stderr | 6 +- .../partial-sigs/should_compile/SkipMany.stderr | 2 +- .../should_compile/TypeFamilyInstanceLHS.stderr | 14 +- .../tests/partial-sigs/should_fail/T14040a.stderr | 8 +- testsuite/tests/polykinds/T11203.stderr | 2 +- testsuite/tests/polykinds/T11821a.stderr | 2 +- testsuite/tests/polykinds/T12593.stderr | 8 +- testsuite/tests/polykinds/T13985.hs | 1 + testsuite/tests/polykinds/T13985.stderr | 41 +- testsuite/tests/polykinds/T14450.stderr | 11 +- testsuite/tests/polykinds/T14846.stderr | 36 +- testsuite/tests/polykinds/T14887a.hs | 16 + .../T9730.stderr => polykinds/T14887a.stderr} | 0 testsuite/tests/polykinds/T15592.stderr | 2 +- testsuite/tests/polykinds/T15592b.stderr | 4 +- testsuite/tests/polykinds/T15789.hs | 10 + testsuite/tests/polykinds/T15789.stderr | 6 + testsuite/tests/polykinds/T15804.hs | 5 + testsuite/tests/polykinds/T15804.stderr | 4 + testsuite/tests/polykinds/T15817.hs | 10 + testsuite/tests/polykinds/T15874.hs | 18 + testsuite/tests/polykinds/T15881.hs | 8 + testsuite/tests/polykinds/T15881.stderr | 5 + testsuite/tests/polykinds/T15881a.hs | 8 + testsuite/tests/polykinds/T15881a.stderr | 4 + testsuite/tests/polykinds/T8616.stderr | 9 + testsuite/tests/polykinds/all.T | 7 + testsuite/tests/roles/should_compile/Roles1.stderr | 14 +- .../tests/roles/should_compile/Roles14.stderr | 4 +- testsuite/tests/roles/should_compile/Roles2.stderr | 4 +- testsuite/tests/roles/should_compile/Roles3.stderr | 27 +- testsuite/tests/roles/should_compile/Roles4.stderr | 11 +- testsuite/tests/roles/should_compile/T8958.stderr | 8 +- testsuite/tests/showIface/Orphans.stdout | 4 +- testsuite/tests/th/TH_Roles2.stderr | 2 +- .../tests/th/TH_reifyExplicitForAllFams.stderr | 0 .../tests/typecheck/should_compile/T12763.stderr | 4 +- .../tests/typecheck/should_compile/tc231.stderr | 10 +- .../typecheck/should_fail/LevPolyBounded.stderr | 5 + .../tests/typecheck/should_fail/T13983.stderr | 2 +- testsuite/tests/typecheck/should_fail/T14607.hs | 2 +- .../tests/typecheck/should_fail/T14607.stderr | 17 +- testsuite/tests/typecheck/should_fail/T2688.stderr | 6 +- .../tests/typecheck/should_fail/T6018fail.stderr | 4 +- testsuite/tests/typecheck/should_fail/all.T | 2 +- 157 files changed, 3781 insertions(+), 3110 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 2257a86daa72db382eb927df12a718669d5491f8 From git at git.haskell.org Fri Nov 30 00:45:33 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 30 Nov 2018 00:45:33 +0000 (UTC) Subject: [commit: ghc] master: Fix #15828, from `More explicit foralls` (fe57a5b) Message-ID: <20181130004533.730323A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/fe57a5bae3f8cb87637359f615c77f4afae86d46/ghc >--------------------------------------------------------------- commit fe57a5bae3f8cb87637359f615c77f4afae86d46 Author: Matthew Yacavone Date: Thu Nov 29 18:42:39 2018 -0500 Fix #15828, from `More explicit foralls` Summary: Fix a bug in commit 12eeb9 which permits the following: ``` class C a where type T a b instance C (Maybe a) where type forall a b. T (Maybe a) b = b ``` where instead, the user should write: ``` instance C (Maybe a) where type forall b. T (Maybe a) b = b ``` Update the users guide to discuss scoping of type variables in explicit foralls in type family instances. Test Plan: validate Reviewers: bgamari, goldfire, monoidal Reviewed By: goldfire Subscribers: monoidal, rwbarton, carter GHC Trac Issues: #15828 Differential Revision: https://phabricator.haskell.org/D5283 >--------------------------------------------------------------- fe57a5bae3f8cb87637359f615c77f4afae86d46 compiler/rename/RnSource.hs | 7 ++++++- docs/users_guide/glasgow_exts.rst | 6 +++--- testsuite/tests/rename/should_fail/T15828.hs | 9 +++++++++ testsuite/tests/rename/should_fail/T15828.stderr | 9 +++++++++ testsuite/tests/rename/should_fail/all.T | 1 + 5 files changed, 28 insertions(+), 4 deletions(-) diff --git a/compiler/rename/RnSource.hs b/compiler/rename/RnSource.hs index 7a205ba..6027110 100644 --- a/compiler/rename/RnSource.hs +++ b/compiler/rename/RnSource.hs @@ -738,7 +738,12 @@ rnFamInstEqn doc mb_cls rhs_kvars ; ((bndrs', pats', payload'), fvs) <- bindLocalNamesFV all_imp_var_names $ bindLHsTyVarBndrs doc (Just $ inHsDocContext doc) - mb_cls bndrs $ \bndrs' -> + Nothing bndrs $ \bndrs' -> + -- Note: If we pass mb_cls instead of Nothing here, + -- bindLHsTyVarBndrs will use class variables for any names + -- the user meant to bring in scope here. This is an explicit + -- forall, so we want fresh names, not class variables. + -- Thus: always pass Nothing do { (pats', pat_fvs) <- rnLHsTypes (FamPatCtx tycon) pats ; (payload', rhs_fvs) <- rn_payload doc payload diff --git a/docs/users_guide/glasgow_exts.rst b/docs/users_guide/glasgow_exts.rst index a07adf3..9b8df91 100644 --- a/docs/users_guide/glasgow_exts.rst +++ b/docs/users_guide/glasgow_exts.rst @@ -7577,9 +7577,9 @@ the left hand side can be explicitly bound. For example: :: data instance forall a (b :: Proxy a). F (Proxy b) = FProxy Bool -When an explicit ``forall`` is present, all *type* variables mentioned must -be bound by the ``forall``. Kind variables will be implicitly bound if -necessary, for example: :: +When an explicit ``forall`` is present, all *type* variables mentioned which +are not already in scope must be bound by the ``forall``. Kind variables will +be implicitly bound if necessary, for example: :: data instance forall (a :: k). F a = FOtherwise diff --git a/testsuite/tests/rename/should_fail/T15828.hs b/testsuite/tests/rename/should_fail/T15828.hs new file mode 100644 index 0000000..90c0621 --- /dev/null +++ b/testsuite/tests/rename/should_fail/T15828.hs @@ -0,0 +1,9 @@ +{-# LANGUAGE TypeFamilies, ExplicitForAll #-} + +module T15828 where + +class C a where + type T a b + +instance C (Maybe a) where + type forall a b. T (Maybe a) b = b diff --git a/testsuite/tests/rename/should_fail/T15828.stderr b/testsuite/tests/rename/should_fail/T15828.stderr new file mode 100644 index 0000000..aca2542 --- /dev/null +++ b/testsuite/tests/rename/should_fail/T15828.stderr @@ -0,0 +1,9 @@ + +T15828.hs:9:20: error: + • Type indexes must match class instance head + Expected: T (Maybe a1) + Actual: T (Maybe a) b + where the `' arguments are type variables, + distinct from each other and from the instance variables + • In the type instance declaration for ‘T’ + In the instance declaration for ‘C (Maybe a)’ \ No newline at end of file diff --git a/testsuite/tests/rename/should_fail/all.T b/testsuite/tests/rename/should_fail/all.T index 9ca330f..6fd0143 100644 --- a/testsuite/tests/rename/should_fail/all.T +++ b/testsuite/tests/rename/should_fail/all.T @@ -140,5 +140,6 @@ test('T15659', normal, compile_fail, ['']) test('T15607', normal, compile_fail, ['']) test('T15611a', normal, compile_fail, ['']) test('T15611b', normal, ghci_script, ['T15611b.script']) +test('T15828', normal, compile_fail, ['']) test('ExplicitForAllRules2', normal, compile_fail, ['']) From git at git.haskell.org Fri Nov 30 00:45:36 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 30 Nov 2018 00:45:36 +0000 (UTC) Subject: [commit: ghc] master: Add missing since annotations (9e3aaf8) Message-ID: <20181130004536.668C33A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/9e3aaf8b58d0f0e12e2d19b6928b6c2461d58dda/ghc >--------------------------------------------------------------- commit 9e3aaf8b58d0f0e12e2d19b6928b6c2461d58dda Author: Victor Nawothnig Date: Thu Nov 29 18:44:36 2018 -0500 Add missing since annotations Reviewers: hvr, bgamari, RyanGlScott Reviewed By: RyanGlScott Subscribers: RyanGlScott, rwbarton, carter GHC Trac Issues: #15930 Differential Revision: https://phabricator.haskell.org/D5379 >--------------------------------------------------------------- 9e3aaf8b58d0f0e12e2d19b6928b6c2461d58dda libraries/base/Data/Foldable.hs | 18 ++++++++++++++++++ 1 file changed, 18 insertions(+) diff --git a/libraries/base/Data/Foldable.hs b/libraries/base/Data/Foldable.hs index cc0f348..7134b05 100644 --- a/libraries/base/Data/Foldable.hs +++ b/libraries/base/Data/Foldable.hs @@ -159,6 +159,7 @@ class Foldable t where -- | Right-associative fold of a structure, but with strict application of -- the operator. -- + -- @since 4.6.0.0 foldr' :: (a -> b -> b) -> b -> t a -> b foldr' f z0 xs = foldl f' id xs z0 where f' k x z = k $! f x z @@ -206,6 +207,7 @@ class Foldable t where -- -- @foldl f z = 'List.foldl'' f z . 'toList'@ -- + -- @since 4.6.0.0 foldl' :: (b -> a -> b) -> b -> t a -> b foldl' f z0 xs = foldr f' id xs z0 where f' x k z = k $! f z x @@ -235,6 +237,8 @@ class Foldable t where Just x -> f x y) -- | List of elements of a structure, from left to right. + -- + -- @since 4.8.0.0 toList :: t a -> [a] {-# INLINE toList #-} toList t = build (\ c n -> foldr c n t) @@ -242,35 +246,49 @@ class Foldable t where -- | Test whether the structure is empty. The default implementation is -- optimized for structures that are similar to cons-lists, because there -- is no general way to do better. + -- + -- @since 4.8.0.0 null :: t a -> Bool null = foldr (\_ _ -> False) True -- | Returns the size/length of a finite structure as an 'Int'. The -- default implementation is optimized for structures that are similar to -- cons-lists, because there is no general way to do better. + -- + -- @since 4.8.0.0 length :: t a -> Int length = foldl' (\c _ -> c+1) 0 -- | Does the element occur in the structure? + -- + -- @since 4.8.0.0 elem :: Eq a => a -> t a -> Bool elem = any . (==) -- | The largest element of a non-empty structure. + -- + -- @since 4.8.0.0 maximum :: forall a . Ord a => t a -> a maximum = fromMaybe (errorWithoutStackTrace "maximum: empty structure") . getMax . foldMap (Max #. (Just :: a -> Maybe a)) -- | The least element of a non-empty structure. + -- + -- @since 4.8.0.0 minimum :: forall a . Ord a => t a -> a minimum = fromMaybe (errorWithoutStackTrace "minimum: empty structure") . getMin . foldMap (Min #. (Just :: a -> Maybe a)) -- | The 'sum' function computes the sum of the numbers of a structure. + -- + -- @since 4.8.0.0 sum :: Num a => t a -> a sum = getSum #. foldMap Sum -- | The 'product' function computes the product of the numbers of a -- structure. + -- + -- @since 4.8.0.0 product :: Num a => t a -> a product = getProduct #. foldMap Product From git at git.haskell.org Fri Nov 30 00:45:40 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 30 Nov 2018 00:45:40 +0000 (UTC) Subject: [commit: ghc] master: Fix #15953 by consistently using dumpIfSet_dyn to print debug output (dcf1f92) Message-ID: <20181130004540.3B1A53A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/dcf1f9268f6b338997f2c03891d7bc57da2ee78a/ghc >--------------------------------------------------------------- commit dcf1f9268f6b338997f2c03891d7bc57da2ee78a Author: Chaitanya Koparkar Date: Thu Nov 29 18:45:07 2018 -0500 Fix #15953 by consistently using dumpIfSet_dyn to print debug output Summary: In some modules we directly dump the debugging output to STDOUT via 'putLogMsg', 'printInfoForUser' etc. However, if `-ddump-to-file` is enabled, that output should be written to a file. Easily fixed. Certain tests (T3017, Roles3, T12763 etc.) expect part of the output generated by `-ddump-types` to be in 'PprUser' style. However, generally we want all other debugging output to use 'PprDump' style. `traceTcRn` and `traceTcRnForUser` help us accomplish this. This patch also documents some missing flags in the users guide. Reviewers: RyanGlScott, bgamari, hvr Reviewed By: RyanGlScott Subscribers: rwbarton, carter GHC Trac Issues: #15953 Differential Revision: https://phabricator.haskell.org/D5382 >--------------------------------------------------------------- dcf1f9268f6b338997f2c03891d7bc57da2ee78a compiler/deSugar/Coverage.hs | 6 ++--- compiler/ghci/Debugger.hs | 16 ++++-------- compiler/main/ErrUtils.hs | 27 ++++++++++++++----- compiler/main/InteractiveEval.hs | 6 ++--- compiler/main/Packages.hs | 7 +++-- compiler/main/TidyPgm.hs | 16 +++++------- compiler/simplCore/SimplMonad.hs | 9 +++---- compiler/typecheck/TcRnDriver.hs | 2 +- compiler/typecheck/TcRnMonad.hs | 32 ++++++++++++++++++----- docs/users_guide/debugging.rst | 42 ++++++++++++++++++++++++++++++ testsuite/tests/utils/should_run/Makefile | 10 +++++++ testsuite/tests/utils/should_run/T15953.hs | 9 +++++++ testsuite/tests/utils/should_run/all.T | 2 ++ 13 files changed, 133 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 dcf1f9268f6b338997f2c03891d7bc57da2ee78a From git at git.haskell.org Fri Nov 30 00:45:43 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 30 Nov 2018 00:45:43 +0000 (UTC) Subject: [commit: ghc] master: Allow containers-0.6, QuickCheck-2.12 in Hadrian (8bffd58) Message-ID: <20181130004543.31E563A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8bffd58009baba940497736bd935d924c50dc505/ghc >--------------------------------------------------------------- commit 8bffd58009baba940497736bd935d924c50dc505 Author: Ryan Scott Date: Thu Nov 29 18:46:16 2018 -0500 Allow containers-0.6, QuickCheck-2.12 in Hadrian Summary: Currently, Hadrian has restrictive upper bounds on `containers` and `QuickCheck` that prevents it from building with the latest versions of each respective library (0.6.0.1 and 2.12.6.1). There doesn't appear to be any good reason to do so, since Hadrian builds fine with them, so let's bump the upper version bounds accordingly. Test Plan: ./build/hadrian.sh Reviewers: bgamari, alpmestan, snowleopard Reviewed By: snowleopard Subscribers: rwbarton, carter Differential Revision: https://phabricator.haskell.org/D5389 >--------------------------------------------------------------- 8bffd58009baba940497736bd935d924c50dc505 hadrian/hadrian.cabal | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/hadrian/hadrian.cabal b/hadrian/hadrian.cabal index 422217b..7d54301 100644 --- a/hadrian/hadrian.cabal +++ b/hadrian/hadrian.cabal @@ -115,12 +115,12 @@ executable hadrian , TypeFamilies build-depends: base >= 4.8 && < 5 , Cabal >= 2.5 && < 2.6 - , containers == 0.5.* + , containers >= 0.5 && < 0.7 , directory >= 1.2 && < 1.4 , extra >= 1.4.7 , mtl == 2.2.* , parsec >= 3.1 && < 3.2 - , QuickCheck >= 2.6 && < 2.12 + , QuickCheck >= 2.6 && < 2.13 , shake >= 0.16.4 , transformers >= 0.4 && < 0.6 , unordered-containers >= 0.2.1 && < 0.3 From git at git.haskell.org Fri Nov 30 00:45:46 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 30 Nov 2018 00:45:46 +0000 (UTC) Subject: [commit: ghc] master: Make ghc-in-ghci support Hadrian (30a363a) Message-ID: <20181130004546.276863A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/30a363ae4cbb22127959e98971a188de2b40f788/ghc >--------------------------------------------------------------- commit 30a363ae4cbb22127959e98971a188de2b40f788 Author: Ryan Scott Date: Thu Nov 29 18:46:39 2018 -0500 Make ghc-in-ghci support Hadrian Summary: Currently, `ghc-in-ghci` is hard-coded to only support the installation path of the `make`-based build system. There isn't a fundamental reason why this must be the case, however—it's just a matter of communicating which directories to look into. For the time being, I've hacked `utils/ghc-in-ghci/run.sh` to just check the default Hadrian installation path in addition to the `make` one. Disclaimer: I'm not well-versed in `bash`-fu, so it's possible that there is a better way to accomplish what I'm setting out to do. Suggestions welcome. Test Plan: ./utils/ghc-in-ghci/run.sh Reviewers: alpmestan, bgamari Reviewed By: alpmestan Subscribers: rwbarton, carter Differential Revision: https://phabricator.haskell.org/D5390 >--------------------------------------------------------------- 30a363ae4cbb22127959e98971a188de2b40f788 utils/ghc-in-ghci/run.sh | 18 ++++++++++++++---- 1 file changed, 14 insertions(+), 4 deletions(-) diff --git a/utils/ghc-in-ghci/run.sh b/utils/ghc-in-ghci/run.sh index 521458f..cb0ab07 100755 --- a/utils/ghc-in-ghci/run.sh +++ b/utils/ghc-in-ghci/run.sh @@ -23,10 +23,20 @@ # If you don't want to wait for `:load Main`, since you want to load some other # module, then you can use `Ctrl+C` to cancel the initial load. - -export _GHC_TOP_DIR=./inplace/lib - -exec ./inplace/bin/ghc-stage2 \ +# Look in two common locations for a GHC installation (the results of using +# the make- and Hadrian-based build systems, respectively). +if [ -d ./inplace/lib ]; then + GHC_BIN=./inplace/bin/ghc-stage2 + _GHC_TOP_DIR=./inplace/lib +elif [ -d ./_build/stage1/lib ]; then + GHC_BIN=./_build/stage1/bin/ghc + _GHC_TOP_DIR=./_build/stage1/lib +else + echo "Could not find GHC installation" + exit 1 +fi + +exec ${GHC_BIN} \ --interactive \ -ghci-script ./utils/ghc-in-ghci/settings.ghci \ -ghci-script ./utils/ghc-in-ghci/load-main.ghci \ From git at git.haskell.org Fri Nov 30 00:45:49 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 30 Nov 2018 00:45:49 +0000 (UTC) Subject: [commit: ghc] master: Add a test case for #15962 (8d7496c) Message-ID: <20181130004549.9C6443A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/8d7496c42f049578187c4e5be08963cb497c2fac/ghc >--------------------------------------------------------------- commit 8d7496c42f049578187c4e5be08963cb497c2fac Author: Chaitanya Koparkar Date: Thu Nov 29 18:47:33 2018 -0500 Add a test case for #15962 Test Plan: make test TEST=T15962 Reviewers: RyanGlScott, bgamari Reviewed By: RyanGlScott Subscribers: rwbarton, carter GHC Trac Issues: #15962 Differential Revision: https://phabricator.haskell.org/D5393 >--------------------------------------------------------------- 8d7496c42f049578187c4e5be08963cb497c2fac testsuite/tests/typecheck/should_fail/T15962.hs | 36 ++++++++++++++++++++++ .../tests/typecheck/should_fail/T15962.stderr | 18 +++++++++++ testsuite/tests/typecheck/should_fail/all.T | 1 + 3 files changed, 55 insertions(+) diff --git a/testsuite/tests/typecheck/should_fail/T15962.hs b/testsuite/tests/typecheck/should_fail/T15962.hs new file mode 100644 index 0000000..e42fcde --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T15962.hs @@ -0,0 +1,36 @@ +{-# LANGUAGE GADTs #-} +{-# LANGUAGE TypeInType #-} +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE TypeOperators #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE FlexibleInstances #-} + +module T15962 where + +import Data.Kind (Type) + +type Exp a = a -> Type +type family Eval (e :: Exp a) :: a + +data OpKind = Conjunction + +data Dual (k :: OpKind) :: Exp OpKind + +data Map :: (a -> Exp b) -> [ a ] -> Exp [ b ] + +type instance Eval (Map f (a ': as)) = Eval (f a) ': Eval (Map f as) + +data Big :: [ OpKind ] -> Type where + Big :: [ Big ks ] -> Big ('Conjunction ': ks) + +dualBig :: Big ks -> Big (Eval (Map Dual ks)) +dualBig = _ + +instance Semigroup (Big a) where + Big xs <> Big ys = Big (xs <> ys) + +instance Monoid (Big ('Conjunction ': ks)) where + mempty = iDontExist + +flatten :: Monoid (Big ks) => Big (k ': k ': ks) -> Big ks +flatten = undefined diff --git a/testsuite/tests/typecheck/should_fail/T15962.stderr b/testsuite/tests/typecheck/should_fail/T15962.stderr new file mode 100644 index 0000000..ffab68c --- /dev/null +++ b/testsuite/tests/typecheck/should_fail/T15962.stderr @@ -0,0 +1,18 @@ +T15962.hs:27:11: + Found hole: _ :: Big ks -> Big (Eval (Map Dual ks)) + Where: ‘ks’ is a rigid type variable bound by + the type signature for: + dualBig :: forall (ks :: [OpKind]). + Big ks -> Big (Eval (Map Dual ks)) + at T15962.hs:26:1-45 + In the expression: _ + In an equation for ‘dualBig’: dualBig = _ + Relevant bindings include + dualBig :: Big ks -> Big (Eval (Map Dual ks)) + (bound at T15962.hs:27:1) + Valid hole fits include + dualBig :: Big ks -> Big (Eval (Map Dual ks)) + (bound at T15962.hs:27:1) + +T15962.hs:33:12: + Variable not in scope: iDontExist :: Big ('Conjunction : ks) diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T index 7dca65b..e033f17 100644 --- a/testsuite/tests/typecheck/should_fail/all.T +++ b/testsuite/tests/typecheck/should_fail/all.T @@ -489,3 +489,4 @@ test('T15629', normal, compile_fail, ['']) test('T15767', normal, compile_fail, ['']) test('T15648', [extra_files(['T15648a.hs'])], multimod_compile_fail, ['T15648', '-v0 -fprint-equality-relations']) test('T15796', normal, compile_fail, ['']) +test('T15962', normal, compile_fail, ['']) From git at git.haskell.org Fri Nov 30 00:45:52 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 30 Nov 2018 00:45:52 +0000 (UTC) Subject: [commit: ghc] master: Accept T15828 test output (b1af0ae) Message-ID: <20181130004552.90A2F3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/b1af0aed08c78f42c7dd2505ed9b96d0cbf1d076/ghc >--------------------------------------------------------------- commit b1af0aed08c78f42c7dd2505ed9b96d0cbf1d076 Author: Ryan Scott Date: Thu Nov 29 19:43:32 2018 -0500 Accept T15828 test output This test output changed slightly due to commit 2257a86daa72db382eb927df12a718669d5491f8 (which is expected). >--------------------------------------------------------------- b1af0aed08c78f42c7dd2505ed9b96d0cbf1d076 testsuite/tests/rename/should_fail/T15828.stderr | 8 +++----- 1 file changed, 3 insertions(+), 5 deletions(-) diff --git a/testsuite/tests/rename/should_fail/T15828.stderr b/testsuite/tests/rename/should_fail/T15828.stderr index aca2542..9ca6366 100644 --- a/testsuite/tests/rename/should_fail/T15828.stderr +++ b/testsuite/tests/rename/should_fail/T15828.stderr @@ -1,9 +1,7 @@ -T15828.hs:9:20: error: +T15828.hs:9:3: error: • Type indexes must match class instance head - Expected: T (Maybe a1) - Actual: T (Maybe a) b - where the `' arguments are type variables, - distinct from each other and from the instance variables + Expected: T (Maybe a) _ + Actual: T (Maybe a) b -- Defined at T15828.hs:9:20 • In the type instance declaration for ‘T’ In the instance declaration for ‘C (Maybe a)’ From git at git.haskell.org Fri Nov 30 14:39:05 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 30 Nov 2018 14:39:05 +0000 (UTC) Subject: [commit: ghc] master: Two tests for Trac #14230 (80d665a) Message-ID: <20181130143905.906B03A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/80d665a123305721c58a3d7652c64e2b3c69b70e/ghc >--------------------------------------------------------------- commit 80d665a123305721c58a3d7652c64e2b3c69b70e Author: Simon Peyton Jones Date: Fri Nov 30 14:00:14 2018 +0000 Two tests for Trac #14230 >--------------------------------------------------------------- 80d665a123305721c58a3d7652c64e2b3c69b70e testsuite/tests/indexed-types/should_fail/T14230.hs | 11 +++++++++++ testsuite/tests/indexed-types/should_fail/T14230.stderr | 7 +++++++ testsuite/tests/indexed-types/should_fail/T14230a.hs | 13 +++++++++++++ testsuite/tests/indexed-types/should_fail/T14230a.stderr | 6 ++++++ testsuite/tests/indexed-types/should_fail/all.T | 2 ++ 5 files changed, 39 insertions(+) diff --git a/testsuite/tests/indexed-types/should_fail/T14230.hs b/testsuite/tests/indexed-types/should_fail/T14230.hs new file mode 100644 index 0000000..d409ba6 --- /dev/null +++ b/testsuite/tests/indexed-types/should_fail/T14230.hs @@ -0,0 +1,11 @@ +{-# LANGUAGE GADTs #-} +{-# LANGUAGE PolyKinds #-} +{-# LANGUAGE RankNTypes #-} +{-# LANGUAGE TypeFamilies #-} +module T14230 where + +class C k where + data CD :: k -> k -> * + +instance C (Maybe a) where + data CD :: (k -> *) -> (k -> *) -> * diff --git a/testsuite/tests/indexed-types/should_fail/T14230.stderr b/testsuite/tests/indexed-types/should_fail/T14230.stderr new file mode 100644 index 0000000..174a15a --- /dev/null +++ b/testsuite/tests/indexed-types/should_fail/T14230.stderr @@ -0,0 +1,7 @@ + +T14230.hs:11:3: error: + • Type indexes must match class instance head + Expected: CD @(Maybe a) + Actual: CD @(k -> *) -- Defined at T14230.hs:11:8 + • In the data instance declaration for ‘CD’ + In the instance declaration for ‘C (Maybe a)’ diff --git a/testsuite/tests/indexed-types/should_fail/T14230a.hs b/testsuite/tests/indexed-types/should_fail/T14230a.hs new file mode 100644 index 0000000..84cd6f1 --- /dev/null +++ b/testsuite/tests/indexed-types/should_fail/T14230a.hs @@ -0,0 +1,13 @@ +{-# LANGUAGE GADTs #-} +{-# LANGUAGE RankNTypes #-} +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE TypeInType #-} +module T14230a where + +import Data.Kind + +class C a where + data CD k (a :: k) :: k -> * + +instance C (Maybe a) where + data CD k (a :: k -> *) :: (k -> *) -> * diff --git a/testsuite/tests/indexed-types/should_fail/T14230a.stderr b/testsuite/tests/indexed-types/should_fail/T14230a.stderr new file mode 100644 index 0000000..726764a --- /dev/null +++ b/testsuite/tests/indexed-types/should_fail/T14230a.stderr @@ -0,0 +1,6 @@ + +T14230a.hs:13:14: error: + • Expected kind ‘k -> *’, but ‘a’ has kind ‘*’ + • In the second argument of ‘CD’, namely ‘(a :: k -> *)’ + In the data instance declaration for ‘CD’ + In the instance declaration for ‘C (Maybe a)’ diff --git a/testsuite/tests/indexed-types/should_fail/all.T b/testsuite/tests/indexed-types/should_fail/all.T index 6273f59..4f6863b 100644 --- a/testsuite/tests/indexed-types/should_fail/all.T +++ b/testsuite/tests/indexed-types/should_fail/all.T @@ -152,3 +152,5 @@ test('T15740', normal, compile_fail, ['']) test('T15764', normal, compile_fail, ['']) test('T15870', normal, compile_fail, ['']) test('T14887', normal, compile_fail, ['']) +test('T14230', normal, compile_fail, ['']) +test('T14230a', normal, compile_fail, ['']) From git at git.haskell.org Fri Nov 30 14:47:48 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 30 Nov 2018 14:47:48 +0000 (UTC) Subject: [commit: ghc] master: Add 'Lift' instances for 'NonEmpty' and 'Void' (47875bd) Message-ID: <20181130144748.6C0363A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/47875bd4d79ca633b589e63e320aa5a5c631d096/ghc >--------------------------------------------------------------- commit 47875bd4d79ca633b589e63e320aa5a5c631d096 Author: Alec Theriault Date: Fri Nov 30 09:18:10 2018 -0500 Add 'Lift' instances for 'NonEmpty' and 'Void' Summary: Since 'NonEmpty' and 'Void' are now part of 'base', it makes sense that we put 'Lift' instances for them in 'template-haskell'. Not doing so is going to force users to define their own (possibly colliding) orphan instances downstream. Test Plan: ./validate Reviewers: goldfire, bgamari, RyanGlScott Reviewed By: RyanGlScott Subscribers: RyanGlScott, rwbarton, carter GHC Trac Issues: #15961 Differential Revision: https://phabricator.haskell.org/D5391 >--------------------------------------------------------------- 47875bd4d79ca633b589e63e320aa5a5c631d096 libraries/template-haskell/Language/Haskell/TH/Syntax.hs | 16 ++++++++++++++++ libraries/template-haskell/changelog.md | 2 ++ testsuite/tests/quotes/TH_localname.stderr | 2 +- testsuite/tests/th/TH_Lift.hs | 3 +++ 4 files changed, 22 insertions(+), 1 deletion(-) diff --git a/libraries/template-haskell/Language/Haskell/TH/Syntax.hs b/libraries/template-haskell/Language/Haskell/TH/Syntax.hs index b75a048..ef44a5c 100644 --- a/libraries/template-haskell/Language/Haskell/TH/Syntax.hs +++ b/libraries/template-haskell/Language/Haskell/TH/Syntax.hs @@ -34,6 +34,8 @@ import Control.Monad.IO.Class (MonadIO (..)) import System.IO ( hPutStrLn, stderr ) import Data.Char ( isAlpha, isAlphaNum, isUpper ) import Data.Int +import Data.List.NonEmpty ( NonEmpty(..) ) +import Data.Void ( Void, absurd ) import Data.Word import Data.Ratio import GHC.Generics ( Generic ) @@ -701,6 +703,17 @@ liftString :: String -> Q Exp -- Used in TcExpr to short-circuit the lifting for strings liftString s = return (LitE (StringL s)) +-- | @since 2.15.0.0 +instance Lift a => Lift (NonEmpty a) where + lift (x :| xs) = do + x' <- lift x + xs' <- lift xs + return (InfixE (Just x') (ConE nonemptyName) (Just xs')) + +-- | @since 2.15.0.0 +instance Lift Void where + lift = pure . absurd + instance Lift () where lift () = return (ConE (tupleDataName 0)) @@ -752,6 +765,9 @@ leftName, rightName :: Name leftName = mkNameG DataName "base" "Data.Either" "Left" rightName = mkNameG DataName "base" "Data.Either" "Right" +nonemptyName :: Name +nonemptyName = mkNameG DataName "base" "GHC.Base" ":|" + ----------------------------------------------------- -- -- Generic Lift implementations diff --git a/libraries/template-haskell/changelog.md b/libraries/template-haskell/changelog.md index de8b96f..5dca983 100644 --- a/libraries/template-haskell/changelog.md +++ b/libraries/template-haskell/changelog.md @@ -12,6 +12,8 @@ `Maybe [TyVarBndrQ]` argument. Non-API-breaking versions of these functions can be found in `Language.Haskell.TH.Lib`. + * Add `Lift` instances for `NonEmpty` and `Void` + ## 2.14.0.0 *TBA* * Introduce an `addForeignFilePath` function, as well as a corresponding diff --git a/testsuite/tests/quotes/TH_localname.stderr b/testsuite/tests/quotes/TH_localname.stderr index 41eb988..df38597 100644 --- a/testsuite/tests/quotes/TH_localname.stderr +++ b/testsuite/tests/quotes/TH_localname.stderr @@ -19,7 +19,7 @@ TH_localname.hs:3:11: error: Language.Haskell.TH.Syntax.Lift (Maybe a) -- Defined in ‘Language.Haskell.TH.Syntax’ ...plus 14 others - ...plus 10 instances involving out-of-scope types + ...plus 12 instances involving out-of-scope types (use -fprint-potential-instances to see them all) • In the expression: Language.Haskell.TH.Syntax.lift y In the expression: diff --git a/testsuite/tests/th/TH_Lift.hs b/testsuite/tests/th/TH_Lift.hs index eff0f1b..87bd47b 100644 --- a/testsuite/tests/th/TH_Lift.hs +++ b/testsuite/tests/th/TH_Lift.hs @@ -9,6 +9,7 @@ import Data.Ratio import Data.Word import Data.Int import Numeric.Natural +import Data.List.NonEmpty a :: Integer a = $( (\x -> [| x |]) (5 :: Integer) ) @@ -76,4 +77,6 @@ n = $( (\x -> [| x |]) () ) o :: (Bool, Char, Int) o = $( (\x -> [| x |]) (True, 'x', 4 :: Int) ) +p :: NonEmpty Char +p = $( (\x -> [| x |]) ('a' :| "bcde") ) From git at git.haskell.org Fri Nov 30 16:19:06 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 30 Nov 2018 16:19:06 +0000 (UTC) Subject: [commit: ghc] master: Deduplicate decision to count thunks in `-ticky` (f10df65) Message-ID: <20181130161906.63AA53A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/f10df65fa2c9a5ec2f4c09b97e02e87c377beac3/ghc >--------------------------------------------------------------- commit f10df65fa2c9a5ec2f4c09b97e02e87c377beac3 Author: Sebastian Graf Date: Fri Nov 30 17:18:45 2018 +0100 Deduplicate decision to count thunks in `-ticky` Summary: Previously, the logic that checks whether a thunk has a counter or not was duplicated in multiple functions. This led to thunk enters being accounted to their enclosing functions in `StgCmmTicky.tickyEnterThunk`, because the outer call to `withNewTickyCounterThunk` didn't set the counter label for the thunk. And rightly so! `tickyEnterThunk` should only account thunk enters to a counter if `-ticky-dyn-thunk` is on. This patch extracts the logic that was already present in its most general form in `withNewTickyCounterThunk` into its own functions and lets all other call sites checking for `-ticky-dyn-thunk` call this new function named `thunkHasCounter` instead. Reviewers: bgamari, simonmar Reviewed By: simonmar Subscribers: rwbarton, carter Differential Revision: https://phabricator.haskell.org/D5392 >--------------------------------------------------------------- f10df65fa2c9a5ec2f4c09b97e02e87c377beac3 compiler/codeGen/StgCmmTicky.hs | 22 ++++++++++++++-------- 1 file changed, 14 insertions(+), 8 deletions(-) diff --git a/compiler/codeGen/StgCmmTicky.hs b/compiler/codeGen/StgCmmTicky.hs index 8f30748..e673d21 100644 --- a/compiler/codeGen/StgCmmTicky.hs +++ b/compiler/codeGen/StgCmmTicky.hs @@ -136,7 +136,7 @@ import TyCon import Data.Maybe import qualified Data.Char -import Control.Monad ( unless, when ) +import Control.Monad ( when ) ----------------------------------------------------------------------------- -- @@ -161,6 +161,11 @@ withNewTickyCounterLNE nm args code = do b <- tickyLNEIsOn if not b then code else withNewTickyCounter TickyLNE nm args code +thunkHasCounter :: Bool -> FCode Bool +thunkHasCounter isStatic = do + b <- tickyDynThunkIsOn + pure (not isStatic && b) + withNewTickyCounterThunk :: Bool -- ^ static -> Bool -- ^ updateable @@ -168,8 +173,8 @@ withNewTickyCounterThunk -> FCode a -> FCode a withNewTickyCounterThunk isStatic isUpdatable name code = do - b <- tickyDynThunkIsOn - if isStatic || not b -- ignore static thunks + has_ctr <- thunkHasCounter isStatic + if not has_ctr then code else withNewTickyCounter (TickyThunk isUpdatable False) name [] code @@ -179,8 +184,8 @@ withNewTickyCounterStdThunk -> FCode a -> FCode a withNewTickyCounterStdThunk isUpdatable name code = do - b <- tickyDynThunkIsOn - if not b + has_ctr <- thunkHasCounter False + if not has_ctr then code else withNewTickyCounter (TickyThunk isUpdatable True) name [] code @@ -189,8 +194,8 @@ withNewTickyCounterCon -> FCode a -> FCode a withNewTickyCounterCon name code = do - b <- tickyDynThunkIsOn - if not b + has_ctr <- thunkHasCounter False + if not has_ctr then code else withNewTickyCounter TickyCon name [] code @@ -277,7 +282,8 @@ tickyEnterThunk :: ClosureInfo -> FCode () tickyEnterThunk cl_info = ifTicky $ do { bumpTickyCounter ctr - ; unless static $ do + ; has_ctr <- thunkHasCounter static + ; when has_ctr $ do ticky_ctr_lbl <- getTickyCtrLabel registerTickyCtrAtEntryDyn ticky_ctr_lbl bumpTickyEntryCount ticky_ctr_lbl } From git at git.haskell.org Fri Nov 30 16:55:31 2018 From: git at git.haskell.org (git at git.haskell.org) Date: Fri, 30 Nov 2018 16:55:31 +0000 (UTC) Subject: [commit: ghc] master: Skip all performance tests if not in a git repo. (6e24a0b) Message-ID: <20181130165531.10BCF3A8E4@ghc.haskell.org> Repository : ssh://git at git.haskell.org/ghc On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/6e24a0bee0d0be8da040c3d5a1e90141abd89852/ghc >--------------------------------------------------------------- commit 6e24a0bee0d0be8da040c3d5a1e90141abd89852 Author: David Eichmann Date: Fri Nov 30 16:48:25 2018 +0000 Skip all performance tests if not in a git repo. Reviewers: bgamari, tdammers, osa1 Reviewed By: tdammers Subscribers: osa1, tdammers, rwbarton, carter GHC Trac Issues: #15923 Differential Revision: https://phabricator.haskell.org/D5367 >--------------------------------------------------------------- 6e24a0bee0d0be8da040c3d5a1e90141abd89852 testsuite/driver/perf_notes.py | 9 +++++++++ testsuite/driver/runtests.py | 32 ++++++++++++++++++++++++++------ 2 files changed, 35 insertions(+), 6 deletions(-) diff --git a/testsuite/driver/perf_notes.py b/testsuite/driver/perf_notes.py index f162164..c275041 100644 --- a/testsuite/driver/perf_notes.py +++ b/testsuite/driver/perf_notes.py @@ -20,6 +20,15 @@ from math import ceil, trunc from testutil import passed, failBecause +# Check if "git status" can be run successfully. +# True implies the current directory is a git repo. +def can_git_status(): + try: + subprocess.check_call(['git', 'status']) + return True + except subprocess.CalledProcessError: + return False + # # Some data access functions. A the moment this uses git notes. # diff --git a/testsuite/driver/runtests.py b/testsuite/driver/runtests.py index fb3fe6a..c8966b4 100644 --- a/testsuite/driver/runtests.py +++ b/testsuite/driver/runtests.py @@ -25,7 +25,7 @@ import subprocess from testutil import getStdout, Watcher, str_warn, str_info from testglobals import getConfig, ghc_env, getTestRun, TestOptions, brokens -from perf_notes import MetricChange +from perf_notes import MetricChange, can_git_status from junit import junit # Readline sometimes spews out ANSI escapes for some values of TERM, @@ -84,6 +84,7 @@ if args.rootdir: config.rootdirs = args.rootdir config.metrics_file = args.metrics_file +hasMetricsFile = bool(config.metrics_file) config.summary_file = args.summary_file config.no_print_summary = args.no_print_summary @@ -117,7 +118,12 @@ if args.threads: if args.verbose is not None: config.verbose = args.verbose -config.skip_perf_tests = args.skip_perf_tests +# Note force skip perf tests: skip if this is not a git repo (estimated with can_git_status) +# and no metrics file is given. In this case there is no way to read the previous commit's +# perf test results, nor a way to store new perf test results. +canGitStatus = can_git_status() +forceSkipPerfTests = not hasMetricsFile and not canGitStatus +config.skip_perf_tests = args.skip_perf_tests or forceSkipPerfTests config.only_perf_tests = args.only_perf_tests if args.test_env: @@ -351,12 +357,24 @@ else: # flush everything before we continue sys.stdout.flush() + # Warn if had to force skip perf tests (see Note force skip perf tests). + spacing = " " + if forceSkipPerfTests and not args.skip_perf_tests: + print() + print(str_warn('Skipping All Performance Tests') + ' `git status` exited with non-zero exit code.') + print(spacing + 'Git is required because performance test results are compared with the previous git commit\'s results (stored with git notes).') + print(spacing + 'You can still run the tests without git by specifying an output file with --metrics-file FILE.') + # Warn of new metrics. new_metrics = [metric for (change, metric) in t.metrics if change == MetricChange.NewMetric] - spacing = " " if any(new_metrics): + if canGitStatus: + reason = 'the previous git commit doesn\'t have recorded metrics for the following tests.' + \ + ' If the tests exist on the previous commit, then check it out and run the tests to generate the missing metrics.' + else: + reason = 'this is not a git repo so the previous git commit\'s metrics cannot be loaded from git notes:' print() - print(str_warn('New Metrics') + ' the previous git commit doesn\'t have metrics for the following tests:') + print(str_warn('New Metrics') + ' these metrics trivially pass because ' + reason) print(spacing + ('\n' + spacing).join(set([metric.test for metric in new_metrics]))) # Inform of how to accept metric changes. @@ -369,14 +387,16 @@ else: summary(t, sys.stdout, config.no_print_summary, True) + # Write perf stats if any exist or if a metrics file is specified. stats = [stat for (_, stat) in t.metrics] - if config.metrics_file: + if hasMetricsFile: print('Appending ' + str(len(stats)) + ' stats to file: ' + config.metrics_file) with open(config.metrics_file, 'a') as file: file.write("\n" + Perf.format_perf_stat(stats)) - else: + elif canGitStatus and any(stats): Perf.append_perf_stat(stats) + # Write summary if config.summary_file: with open(config.summary_file, 'w') as file: summary(t, file)